aboutsummaryrefslogtreecommitdiff
path: root/server/src/Thermoprint/Server
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2016-02-27 02:13:06 +0100
committerGregor Kleen <gkleen@yggdrasil.li>2016-02-27 02:13:06 +0100
commit844f5e96097f8fcced94220487a7c5ad40c1e97f (patch)
treee7a9dc0715893a692ef56107cce399bacd17b9a2 /server/src/Thermoprint/Server
parentd7787ee41ec261db9152d548a9ebbffb4c44c52d (diff)
downloadthermoprint-844f5e96097f8fcced94220487a7c5ad40c1e97f.tar
thermoprint-844f5e96097f8fcced94220487a7c5ad40c1e97f.tar.gz
thermoprint-844f5e96097f8fcced94220487a7c5ad40c1e97f.tar.bz2
thermoprint-844f5e96097f8fcced94220487a7c5ad40c1e97f.tar.xz
thermoprint-844f5e96097f8fcced94220487a7c5ad40c1e97f.zip
QMConfig tools stuck at combineQM
Diffstat (limited to 'server/src/Thermoprint/Server')
-rw-r--r--server/src/Thermoprint/Server/QMConfig.hs75
1 files changed, 72 insertions, 3 deletions
diff --git a/server/src/Thermoprint/Server/QMConfig.hs b/server/src/Thermoprint/Server/QMConfig.hs
index 0cf7beb..8f08faf 100644
--- a/server/src/Thermoprint/Server/QMConfig.hs
+++ b/server/src/Thermoprint/Server/QMConfig.hs
@@ -2,9 +2,16 @@
2{-# LANGUAGE FlexibleContexts #-} 2{-# LANGUAGE FlexibleContexts #-}
3{-# LANGUAGE ImpredicativeTypes #-} 3{-# LANGUAGE ImpredicativeTypes #-}
4{-# LANGUAGE TypeOperators #-} 4{-# LANGUAGE TypeOperators #-}
5{-# LANGUAGE RecordWildCards #-}
6{-# LANGUAGE ViewPatterns #-}
5 7
6module Thermoprint.Server.QMConfig 8module Thermoprint.Server.QMConfig
7 ( QMConfig(..) 9 ( QMConfig(..)
10 , nullQM
11 , idQM
12 , standardSleep
13 , limitHistorySize
14 , limitHistoryAge
8 ) where 15 ) where
9 16
10import Control.Monad.Trans.Resource 17import Control.Monad.Trans.Resource
@@ -14,15 +21,23 @@ import Control.Monad.Logger
14import Control.Monad.Reader 21import Control.Monad.Reader
15import Control.Monad.IO.Class 22import Control.Monad.IO.Class
16import Control.Monad.Morph 23import Control.Monad.Morph
24import Control.Monad.State
17import Control.Category 25import Control.Category
18import Prelude hiding (id, (.))
19import Servant.Server.Internal.Enter (enter, (:~>)(..)) 26import Servant.Server.Internal.Enter (enter, (:~>)(..))
20 27
21import Data.Default.Class 28import Data.Default.Class
22 29
30import Data.Sequence (Seq)
31import qualified Data.Sequence as Seq
32import Data.Time
33import Data.Foldable
34
23import Control.Concurrent.STM 35import Control.Concurrent.STM
24 36
25import Thermoprint.Server.Queue 37import Thermoprint.Server.Queue hiding (idQM, intersection, nullQM, union, runQM)
38import qualified Thermoprint.Server.Queue as Q
39
40import Prelude hiding (length, maximum, id, (.))
26 41
27data QMConfig m where 42data QMConfig m where
28 QMConfig :: ( MonadTrans t 43 QMConfig :: ( MonadTrans t
@@ -35,8 +50,62 @@ data QMConfig m where
35 , MFunctor t 50 , MFunctor t
36 , Monad (t STM) 51 , Monad (t STM)
37 , MonadIO (t IO) 52 , MonadIO (t IO)
53 , Monad (QueueManagerM t)
38 ) => QueueManager t 54 ) => QueueManager t
39 ) -> QMConfig m 55 ) -> QMConfig m
40 56
41instance MonadIO m => Default (QMConfig m) where 57instance MonadIO m => Default (QMConfig m) where
42 def = QMConfig idQM $ Nat (liftIO . runIdentityT) 58 def = idQM
59
60intersection :: (Functor f, Foldable f, MonadIO m) => f (QMConfig m) -> QMConfig m
61intersection = foldr' (qmCombine Q.intersection) idQM
62
63idQM :: MonadIO m => QMConfig m
64idQM = QMConfig' Q.idQM
65
66union :: (Foldable f, MonadIO m) => f (QMConfig m) -> QMConfig m
67union = foldr' (qmCombine Q.union) idQM
68
69nullQM :: MonadIO m => QMConfig m
70nullQM = QMConfig' Q.nullQM
71
72qmCombine :: ([QueueManager t] -> QueueManager t) -> QMConfig m -> QMConfig m -> QMConfig m
73qmCombine qmCombine' (QMConfig a natA) (QMConfig b natB) = undefined
74 where
75 natA :: t IO :~> m
76 natB :: t' IO :~> m
77 ---
78 hoistNat natB :: t (t' IO) :~> t m
79 --
80 ? :: t m :~> m
81 natAB :: ComposeT t t' IO :~> m
82
83runQM :: ( HasQueue q ) => TChan JobId -> QMConfig m -> q -> t IO ()
84runQM gcChan (QMConfig qm nat) q = unNat nat $ runQM gcChan qm q
85runQM gcChan (QMConfig' qm) q = hoist liftIO $ runQM gcChan qm q
86
87standardSleep :: Monad (QueueManagerM t) => QueueManager t
88-- ^ Instruct 'runQM' to sleep some standard amount of time
89--
90-- /TODO/: Investigate implementing a smarter algorithm (PID-controller)
91standardSleep = return $ 20
92
93limitHistorySize :: MonadIO m => Int -> QMConfig m
94-- ^ Limit a 'Queue's 'history's size to some number of 'QueueEntry's
95limitHistorySize max = QMConfig' $ modify' limitSize >> standardSleep
96 where
97 limitSize :: Queue -> Queue
98 limitSize q@Queue{..} = q { history = Seq.take max history }
99
100limitHistoryAge :: MonadIO m => NominalDiffTime -- ^ Maximum age relative to the youngest 'QueueEntry'
101 -> QMConfig m
102-- ^ Limit a 'Queue's 'history's contents to 'QueueEntry's below a certain age
103limitHistoryAge maxAge = QMConfig' $ modify' limitAge >> standardSleep
104 where
105 limitAge :: Queue -> Queue
106 limitAge q@Queue{..} = q { history = Seq.filter (filterAge . created . fst) history}
107 where
108 youngest :: UTCTime
109 youngest = maximum $ created . fst <$> history
110 filterAge :: UTCTime -> Bool
111 filterAge time = not $ (youngest `diffUTCTime` time) > maxAge