aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2016-02-26 22:57:30 +0000
committerGregor Kleen <gkleen@yggdrasil.li>2016-02-26 22:57:30 +0000
commitf64e26726ce5468069093aa86fe973ad4be4816c (patch)
tree28a982cf177434c798c49a23142f8502521e03d2
parent022a5a69dfcfc7b62a940d9c3070e6ae37cc993e (diff)
downloadthermoprint-f64e26726ce5468069093aa86fe973ad4be4816c.tar
thermoprint-f64e26726ce5468069093aa86fe973ad4be4816c.tar.gz
thermoprint-f64e26726ce5468069093aa86fe973ad4be4816c.tar.bz2
thermoprint-f64e26726ce5468069093aa86fe973ad4be4816c.tar.xz
thermoprint-f64e26726ce5468069093aa86fe973ad4be4816c.zip
Split QMConfig into own module
-rw-r--r--server/src/Thermoprint/Server.hs15
-rw-r--r--server/src/Thermoprint/Server/QMConfig.hs42
-rw-r--r--server/thermoprint-server.cabal1
3 files changed, 46 insertions, 12 deletions
diff --git a/server/src/Thermoprint/Server.hs b/server/src/Thermoprint/Server.hs
index 446c63e..cd3a4ed 100644
--- a/server/src/Thermoprint/Server.hs
+++ b/server/src/Thermoprint/Server.hs
@@ -4,7 +4,6 @@
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{-# LANGUAGE ViewPatterns #-}
9{-# LANGUAGE DataKinds #-} 8{-# LANGUAGE DataKinds #-}
10 9
@@ -16,6 +15,7 @@ module Thermoprint.Server
16 , module Servant.Server.Internal.Enter 15 , module Servant.Server.Internal.Enter
17 , module Thermoprint.Server.Printer 16 , module Thermoprint.Server.Printer
18 , module Thermoprint.Server.Queue 17 , module Thermoprint.Server.Queue
18 , module Thermoprint.Server.QMConfig
19 ) where 19 ) where
20 20
21import Data.Default.Class 21import Data.Default.Class
@@ -79,6 +79,7 @@ import Thermoprint.Server.Push
79import Thermoprint.Server.Database 79import Thermoprint.Server.Database
80import Thermoprint.Server.Printer 80import Thermoprint.Server.Printer
81import Thermoprint.Server.Queue 81import Thermoprint.Server.Queue
82import Thermoprint.Server.QMConfig
82import qualified Thermoprint.Server.API as API (thermoprintServer) 83import qualified Thermoprint.Server.API as API (thermoprintServer)
83import Thermoprint.Server.API hiding (thermoprintServer) 84import Thermoprint.Server.API hiding (thermoprintServer)
84 85
@@ -91,14 +92,6 @@ data Config m = Config { dyreError :: Maybe String -- ^ Set by 'Dyre' -- sen
91 , queueManagers :: API.PrinterId -> QMConfig m 92 , queueManagers :: API.PrinterId -> QMConfig m
92 } 93 }
93 94
94data QMConfig m = forall t. ( MonadTrans t
95 , MFunctor t
96 , Monad (t STM)
97 , MonadIO (t IO)
98 ) => QMConfig { manager :: QueueManager t
99 , collapse :: (t IO) :~> m
100 }
101
102instance MonadIO m => Default (Config m) where 95instance MonadIO m => Default (Config m) where
103 def = Config { dyreError = Nothing 96 def = Config { dyreError = Nothing
104 , warpSettings = Warp.defaultSettings 97 , warpSettings = Warp.defaultSettings
@@ -106,9 +99,6 @@ instance MonadIO m => Default (Config m) where
106 , queueManagers = const def 99 , queueManagers = const def
107 } 100 }
108 101
109instance MonadIO m => Default (QMConfig m) where
110 def = QMConfig idQM $ Nat (liftIO . runIdentityT)
111
112withPrinters :: MonadResource m => Config m -> [(m PrinterMethod, QMConfig m)] -> m (Config m) 102withPrinters :: MonadResource m => Config m -> [(m PrinterMethod, QMConfig m)] -> m (Config m)
113-- ^ Add a list of printers to a 'Config' 103-- ^ Add a list of printers to a 'Config'
114withPrinters cfg = fmap updateCfg . foldlM mapInsert (Map.mapWithKey (\k a -> (a, queueManagers cfg k)) $ printers cfg) 104withPrinters cfg = fmap updateCfg . foldlM mapInsert (Map.mapWithKey (\k a -> (a, queueManagers cfg k)) $ printers cfg)
@@ -151,6 +141,7 @@ thermoprintServer dyre io = Dyre.wrapMain $ Dyre.defaultParams
151 fork tMgr $ jobGC gcChan 141 fork tMgr $ jobGC gcChan
152 let 142 let
153 runQM' (queueManagers -> QMConfig qm nat) printer = unNat nat $ runQM gcChan qm printer 143 runQM' (queueManagers -> QMConfig qm nat) printer = unNat nat $ runQM gcChan qm printer
144 runQM' (queueManagers -> QMConfig' qm) printer = hoist liftIO $ runQM gcChan qm printer
154 mapM_ (fork tMgr . uncurry runQM') $ Map.toList printers 145 mapM_ (fork tMgr . uncurry runQM') $ Map.toList printers
155 nChan <- liftIO $ newBroadcastTChanIO 146 nChan <- liftIO $ newBroadcastTChanIO
156 let 147 let
diff --git a/server/src/Thermoprint/Server/QMConfig.hs b/server/src/Thermoprint/Server/QMConfig.hs
new file mode 100644
index 0000000..0cf7beb
--- /dev/null
+++ b/server/src/Thermoprint/Server/QMConfig.hs
@@ -0,0 +1,42 @@
1{-# LANGUAGE GADTs #-}
2{-# LANGUAGE FlexibleContexts #-}
3{-# LANGUAGE ImpredicativeTypes #-}
4{-# LANGUAGE TypeOperators #-}
5
6module Thermoprint.Server.QMConfig
7 ( QMConfig(..)
8 ) where
9
10import Control.Monad.Trans.Resource
11import Control.Monad.Trans.Control
12import Control.Monad.Trans.Identity
13import Control.Monad.Logger
14import Control.Monad.Reader
15import Control.Monad.IO.Class
16import Control.Monad.Morph
17import Control.Category
18import Prelude hiding (id, (.))
19import Servant.Server.Internal.Enter (enter, (:~>)(..))
20
21import Data.Default.Class
22
23import Control.Concurrent.STM
24
25import Thermoprint.Server.Queue
26
27data QMConfig m where
28 QMConfig :: ( MonadTrans t
29 , MFunctor t
30 , Monad (t STM)
31 , MonadIO (t IO)
32 ) => QueueManager t -> (t IO) :~> m -> QMConfig m
33 QMConfig' :: ( MonadIO m
34 ) => ( forall t. ( MonadTrans t
35 , MFunctor t
36 , Monad (t STM)
37 , MonadIO (t IO)
38 ) => QueueManager t
39 ) -> QMConfig m
40
41instance MonadIO m => Default (QMConfig m) where
42 def = QMConfig idQM $ Nat (liftIO . runIdentityT)
diff --git a/server/thermoprint-server.cabal b/server/thermoprint-server.cabal
index 89f636c..34e4bee 100644
--- a/server/thermoprint-server.cabal
+++ b/server/thermoprint-server.cabal
@@ -18,6 +18,7 @@ cabal-version: >=1.10
18 18
19library 19library
20 exposed-modules: Thermoprint.Server 20 exposed-modules: Thermoprint.Server
21 , Thermoprint.Server.QMConfig
21 , Thermoprint.Server.Fork 22 , Thermoprint.Server.Fork
22 , Thermoprint.Server.Database 23 , Thermoprint.Server.Database
23 , Thermoprint.Server.API 24 , Thermoprint.Server.API