aboutsummaryrefslogtreecommitdiff
path: root/server/src
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2016-02-12 00:54:43 +0000
committerGregor Kleen <gkleen@yggdrasil.li>2016-02-12 00:54:43 +0000
commitf4aa09d615a9cb77f1d13cbbc516be23a2d3cc69 (patch)
tree5161dd00d07b976864d800bc5dbd3ae560498141 /server/src
parent6e89aaceb65815380f31674801dfebc084737ea2 (diff)
downloadthermoprint-f4aa09d615a9cb77f1d13cbbc516be23a2d3cc69.tar
thermoprint-f4aa09d615a9cb77f1d13cbbc516be23a2d3cc69.tar.gz
thermoprint-f4aa09d615a9cb77f1d13cbbc516be23a2d3cc69.tar.bz2
thermoprint-f4aa09d615a9cb77f1d13cbbc516be23a2d3cc69.tar.xz
thermoprint-f4aa09d615a9cb77f1d13cbbc516be23a2d3cc69.zip
Prototype queue manager configuration
Diffstat (limited to 'server/src')
-rw-r--r--server/src/Thermoprint/Server.hs71
1 files changed, 51 insertions, 20 deletions
diff --git a/server/src/Thermoprint/Server.hs b/server/src/Thermoprint/Server.hs
index 2dcb8e9..2413b2a 100644
--- a/server/src/Thermoprint/Server.hs
+++ b/server/src/Thermoprint/Server.hs
@@ -1,13 +1,15 @@
1{-# LANGUAGE RecordWildCards #-} 1{-# LANGUAGE RecordWildCards #-}
2{-# LANGUAGE TemplateHaskell #-} 2{-# LANGUAGE TemplateHaskell #-}
3{-# LANGUAGE OverloadedStrings #-} 3{-# LANGUAGE OverloadedStrings #-}
4{-# LANGUAGE TypeOperators #-} 4{-# LANGUAGE TypeOperators #-}
5{-# LANGUAGE FlexibleContexts #-} 5{-# LANGUAGE FlexibleContexts #-}
6{-# LANGUAGE ImpredicativeTypes #-} 6{-# LANGUAGE ImpredicativeTypes #-}
7{-# LANGUAGE ExistentialQuantification #-}
8{-# LANGUAGE ViewPatterns #-}
7 9
8module Thermoprint.Server 10module Thermoprint.Server
9 ( thermoprintServer 11 ( thermoprintServer
10 , Config(..) 12 , Config(..), QMConfig(..)
11 , withPrinters 13 , withPrinters
12 , module Data.Default.Class 14 , module Data.Default.Class
13 , module Servant.Server.Internal.Enter 15 , module Servant.Server.Internal.Enter
@@ -26,13 +28,18 @@ import Data.Foldable (mapM_, forM_, foldlM)
26 28
27import Control.Monad.Trans.Resource 29import Control.Monad.Trans.Resource
28import Control.Monad.Trans.Control 30import Control.Monad.Trans.Control
31import Control.Monad.Trans.Identity
29import Control.Monad.Logger 32import Control.Monad.Logger
30import Control.Monad.Reader 33import Control.Monad.Reader
31import Control.Monad.IO.Class 34import Control.Monad.IO.Class
35import Control.Monad.Morph
32import Control.Category 36import Control.Category
33import Prelude hiding (id, (.)) 37import Prelude hiding (id, (.))
34 38
39import qualified Control.Monad as M
40
35import Control.Concurrent 41import Control.Concurrent
42import Control.Concurrent.STM
36 43
37import Data.Text (Text) 44import Data.Text (Text)
38import qualified Data.Text as T (pack) 45import qualified Data.Text as T (pack)
@@ -55,21 +62,42 @@ import qualified Thermoprint.Server.API as API (thermoprintServer)
55import Thermoprint.Server.API hiding (thermoprintServer) 62import Thermoprint.Server.API hiding (thermoprintServer)
56 63
57-- | Compile-time configuration for 'thermoprintServer' 64-- | Compile-time configuration for 'thermoprintServer'
58data Config = Config { dyreError :: Maybe String -- ^ Set by 'Dyre' -- sent to log as an error 65data Config m = Config { dyreError :: Maybe String -- ^ Set by 'Dyre' -- sent to log as an error
59 , warpSettings :: Warp.Settings -- ^ Configure 'Warp's behaviour 66 , warpSettings :: Warp.Settings -- ^ Configure 'Warp's behaviour
60 , printers :: Map PrinterId Printer 67 , printers :: Map PrinterId Printer
61 } 68 , queueManagers :: PrinterId -> QMConfig m
62 69 }
63instance Default Config where 70
64 def = Config { dyreError = Nothing 71data QMConfig m = forall t. ( MonadTrans t
65 , warpSettings = Warp.defaultSettings 72 , MFunctor t
66 , printers = Map.empty 73 , Monad (t STM)
74 , MonadIO (t IO)
75 ) => QMConfig { manager :: QueueManager t
76 , collapse :: (t IO) :~> m
77 }
78
79instance MonadIO m => Default (Config m) where
80 def = Config { dyreError = Nothing
81 , warpSettings = Warp.defaultSettings
82 , printers = Map.empty
83 , queueManagers = const def
67 } 84 }
68 85
69withPrinters :: MonadResource m => Config -> [m PrinterMethod] -> m Config 86instance MonadIO m => Default (QMConfig m) where
87 def = QMConfig idQM $ Nat (liftIO . runIdentityT)
88
89withPrinters :: MonadResource m => Config m -> [(m PrinterMethod, QMConfig m)] -> m (Config m)
70-- ^ Add a list of printers to a 'Config' 90-- ^ Add a list of printers to a 'Config'
71withPrinters cfg pss = (\map -> cfg { printers = map }) <$> foldlM (\map spec -> Map.insert (nextKey map) <$> printer spec <*> pure map) Map.empty pss 91withPrinters cfg = fmap updateCfg . foldlM mapInsert (Map.mapWithKey (\k a -> (a, queueManagers cfg k)) $ printers cfg)
72 where 92 where
93 mapInsert map (spec, qm) = Map.insert (nextKey map) <$> ((,) <$> printer spec <*> pure qm) <*> pure map
94 updateCfg map = let
95 printerMap = fmap fst map
96 qmMap = fmap snd map
97 qmMap' id
98 | (Just qm) <- (Map.lookup id qmMap) = qm
99 | otherwise = queueManagers cfg id
100 in cfg { printers = printerMap, queueManagers = qmMap' }
73 nextKey map 101 nextKey map
74 | Map.null map = 0 102 | Map.null map = 0
75 | otherwise = succ . fst $ Map.findMax map 103 | otherwise = succ . fst $ Map.findMax map
@@ -77,8 +105,8 @@ withPrinters cfg pss = (\map -> cfg { printers = map }) <$> foldlM (\map spec ->
77thermoprintServer :: ( MonadLoggerIO m 105thermoprintServer :: ( MonadLoggerIO m
78 , MonadReader ConnectionPool m 106 , MonadReader ConnectionPool m
79 , MonadResourceBase m 107 , MonadResourceBase m
80 ) => (m :~> IO) -- ^ 'dyre' controls the base of the monad-transformer-stack ('IO') but we let the user specify the rest of it. Therefore we require a specification of how to collapse the stack. 108 ) => (m :~> IO) -- ^ 'dyre' controls the base of the monad-transformer-stack ('IO') but we let the user specify much of the rest of it (we handle 'ResourceT' ourselves, since we need it to fork properly). Therefore we require a specification of how to collapse the stack.
81 -> ResourceT m Config -> IO () 109 -> ResourceT m (Config (ResourceT m)) -> IO ()
82-- ^ Run the server 110-- ^ Run the server
83thermoprintServer io = Dyre.wrapMain $ Dyre.defaultParams 111thermoprintServer io = Dyre.wrapMain $ Dyre.defaultParams
84 { Dyre.projectName = "thermoprint-server" 112 { Dyre.projectName = "thermoprint-server"
@@ -91,4 +119,7 @@ thermoprintServer io = Dyre.wrapMain $ Dyre.defaultParams
91 maybe (return ()) ($(logErrorS) "Dyre" . T.pack) dyreError 119 maybe (return ()) ($(logErrorS) "Dyre" . T.pack) dyreError
92 mapM_ ($(logWarnS) "DB") =<< runSqlPool (runMigrationSilent migrateAll) =<< ask 120 mapM_ ($(logWarnS) "DB") =<< runSqlPool (runMigrationSilent migrateAll) =<< ask
93 forM_ printers $ resourceForkIO . runPrinter 121 forM_ printers $ resourceForkIO . runPrinter
122 let
123 runQM' (queueManagers -> QMConfig qm nat) printer = unNat nat $ runQM qm printer
124 Map.foldrWithKey (\k p a -> resourceForkIO (runQM' k p) >> a) (return ()) printers
94 liftIO . Warp.runSettings warpSettings . serve thermoprintAPI . flip enter API.thermoprintServer =<< handlerNat printers 125 liftIO . Warp.runSettings warpSettings . serve thermoprintAPI . flip enter API.thermoprintServer =<< handlerNat printers