Base.hs.template 4.0 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120
  1. -- vim: ft=haskell
  2. {-# LANGUAGE RecordWildCards #-}
  3. {-# LANGUAGE OverloadedStrings #-}
  4. module $module_path$.Base where
  5. import Data.Word (Word32)
  6. import Data.Map.Strict (Map)
  7. import qualified Data.Map.Strict as Map
  8. import Control.Concurrent (forkIO)
  9. import Control.Concurrent.STM
  10. (atomically,STM,retry,TVar,newTVar,writeTVar,readTVar
  11. ,TQueue,readTQueue,writeTQueue
  12. ,TMVar,newEmptyTMVarIO,takeTMVar,putTMVar,newTVarIO
  13. ,modifyTVar)
  14. import Control.Monad (forever)
  15. import Snap.Core (Snap,route)
  16. import qualified Snap.Http.Server as HTTP
  17. import Snap.Util.FileServe (serveDirectory)
  18. data Config = Config { cfgPort :: !Int
  19. -- ^ The port to run on
  20. , cfgStaticDir :: Maybe FilePath
  21. -- ^ Content to be served off of the root, relative to
  22. -- the directory that the server was started in
  23. } deriving (Show)
  24. -- | A default @Config@ value that will produce a server that runs on port 8080,
  25. -- and serves no static content.
  26. defaultConfig :: Config
  27. defaultConfig = Config { cfgPort = 8080, cfgStaticDir = Nothing }
  28. -- | Spawn a snap server, and run the given RPC action.
  29. runServer :: Config -> Snap () -> IO ()
  30. runServer Config { .. } serveRpc =
  31. do let snapCfg :: HTTP.Config Snap ()
  32. snapCfg = HTTP.setPort cfgPort HTTP.defaultConfig
  33. HTTP.simpleHttpServe snapCfg body
  34. where
  35. body =
  36. do serveRpc
  37. case cfgStaticDir of
  38. Just path -> route [ ("", serveDirectory path) ]
  39. Nothing -> return ()
  40. data Request req resp = ReadRequest req (resp -> IO ())
  41. | WriteRequest req
  42. -- Sample Variables ------------------------------------------------------------
  43. -- | A TVar that blocks when it's empty, but allows writes even when it's full.
  44. newtype TSampleVar a = TSampleVar (TVar (Maybe a))
  45. newTSampleVar :: STM (TSampleVar a)
  46. newTSampleVar = TSampleVar `fmap` newTVar Nothing
  47. newTSampleVarIO :: IO (TSampleVar a)
  48. newTSampleVarIO = atomically (TSampleVar `fmap` newTVar Nothing)
  49. writeTSampleVar :: TSampleVar a -> a -> STM ()
  50. writeTSampleVar (TSampleVar tv) a = writeTVar tv (Just a)
  51. readTSampleVar :: TSampleVar a -> STM a
  52. readTSampleVar (TSampleVar tv) =
  53. do mb <- readTVar tv
  54. case mb of
  55. Just a -> return a
  56. Nothing -> retry
  57. -- Response Handling -----------------------------------------------------------
  58. data Conn req resp = Conn { connRequests :: TQueue req
  59. , connWaiting :: TVar (Map Word32 (TMVar resp))
  60. , connSeqNum :: TVar Word32
  61. }
  62. -- | Fork a handler thread that will apply handlers to incoming messages. If
  63. -- the handler queue is empty when a response arrives, the response is dropped.
  64. newConn :: TQueue req -> TQueue resp -> (resp -> Word32) -> IO (Conn req resp)
  65. newConn connRequests connResps toSeqNum =
  66. do connWaiting <- newTVarIO Map.empty
  67. connSeqNum <- newTVarIO 0
  68. _ <- forkIO (forever
  69. (do resp <- atomically (readTQueue connResps)
  70. let snum = toSeqNum resp
  71. mb <- atomically (do
  72. m <- readTVar connWaiting
  73. let (mb, m') = Map.updateLookupWithKey (\\_ _ -> Nothing) snum m
  74. writeTVar connWaiting m'
  75. return mb)
  76. case mb of
  77. Just var -> atomically (putTMVar var resp)
  78. Nothing -> return ()))
  79. return Conn { .. }
  80. -- | Send a request, and block until a response is received.
  81. sendRequest :: Conn req resp -> (Word32 -> req) -> IO resp
  82. sendRequest Conn { .. } req =
  83. do var <- newEmptyTMVarIO
  84. atomically (do snum <- readTVar connSeqNum
  85. writeTVar connSeqNum (snum + 1)
  86. modifyTVar connWaiting (Map.insert snum var)
  87. writeTQueue connRequests (req snum))
  88. atomically (takeTMVar var)