diff options
-rw-r--r-- | server/src/Thermoprint/Server.hs | 2 | ||||
-rw-r--r-- | server/src/Thermoprint/Server/Queue/Utils.hs | 52 | ||||
-rw-r--r-- | server/thermoprint-server.cabal | 1 |
3 files changed, 55 insertions, 0 deletions
diff --git a/server/src/Thermoprint/Server.hs b/server/src/Thermoprint/Server.hs index 446c63e..f73a418 100644 --- a/server/src/Thermoprint/Server.hs +++ b/server/src/Thermoprint/Server.hs | |||
@@ -16,6 +16,7 @@ module Thermoprint.Server | |||
16 | , module Servant.Server.Internal.Enter | 16 | , module Servant.Server.Internal.Enter |
17 | , module Thermoprint.Server.Printer | 17 | , module Thermoprint.Server.Printer |
18 | , module Thermoprint.Server.Queue | 18 | , module Thermoprint.Server.Queue |
19 | , module Thermoprint.Server.Queue.Utils | ||
19 | ) where | 20 | ) where |
20 | 21 | ||
21 | import Data.Default.Class | 22 | import Data.Default.Class |
@@ -79,6 +80,7 @@ import Thermoprint.Server.Push | |||
79 | import Thermoprint.Server.Database | 80 | import Thermoprint.Server.Database |
80 | import Thermoprint.Server.Printer | 81 | import Thermoprint.Server.Printer |
81 | import Thermoprint.Server.Queue | 82 | import Thermoprint.Server.Queue |
83 | import Thermoprint.Server.Queue.Utils | ||
82 | import qualified Thermoprint.Server.API as API (thermoprintServer) | 84 | import qualified Thermoprint.Server.API as API (thermoprintServer) |
83 | import Thermoprint.Server.API hiding (thermoprintServer) | 85 | import Thermoprint.Server.API hiding (thermoprintServer) |
84 | 86 | ||
diff --git a/server/src/Thermoprint/Server/Queue/Utils.hs b/server/src/Thermoprint/Server/Queue/Utils.hs new file mode 100644 index 0000000..86b0162 --- /dev/null +++ b/server/src/Thermoprint/Server/Queue/Utils.hs | |||
@@ -0,0 +1,52 @@ | |||
1 | {-# LANGUAGE RecordWildCards #-} | ||
2 | {-# LANGUAGE FlexibleContexts #-} | ||
3 | {-# LANGUAGE TypeOperators #-} | ||
4 | |||
5 | module Thermoprint.Server.Queue.Utils | ||
6 | ( standardCollapse | ||
7 | , standardSleep | ||
8 | , limitHistorySize | ||
9 | , limitHistoryAge | ||
10 | ) where | ||
11 | |||
12 | import Data.Sequence (Seq) | ||
13 | import qualified Data.Sequence as Seq | ||
14 | |||
15 | import Data.Time | ||
16 | |||
17 | import Control.Monad.State | ||
18 | import Control.Monad.IO.Class | ||
19 | import Control.Monad.Trans.Identity | ||
20 | import Servant.Server.Internal.Enter | ||
21 | |||
22 | import Thermoprint.Server.Queue | ||
23 | |||
24 | standardCollapse :: MonadIO m => IdentityT IO :~> m | ||
25 | standardCollapse = Nat $ liftIO . runIdentityT | ||
26 | |||
27 | standardSleep :: Monad (QueueManagerM t) => QueueManager t | ||
28 | -- ^ Instruct 'runQM' to sleep some standard amount of time | ||
29 | -- | ||
30 | -- /TODO/: Investigate implementing a smarter algorithm (PID-controller) | ||
31 | standardSleep = return $ 20 | ||
32 | |||
33 | limitHistorySize :: MonadState Queue (QueueManagerM t) => Int -> QueueManager t | ||
34 | -- ^ Limit a 'Queue's 'history's size to some number of 'QueueEntry's | ||
35 | limitHistorySize max = modify' limitSize >> standardSleep | ||
36 | where | ||
37 | limitSize :: Queue -> Queue | ||
38 | limitSize q@Queue{..} = q { history = Seq.take max history } | ||
39 | |||
40 | limitHistoryAge :: ( MonadState Queue (QueueManagerM t) | ||
41 | ) => NominalDiffTime -- ^ Maximum age relative to the youngest 'QueueEntry' | ||
42 | -> QueueManager t | ||
43 | -- ^ Limit a 'Queue's 'history's contents to 'QueueEntry's below a certain age | ||
44 | limitHistoryAge maxAge = modify' limitAge >> standardSleep | ||
45 | where | ||
46 | limitAge :: Queue -> Queue | ||
47 | limitAge q@Queue{..} = q { history = Seq.filter (filterAge . created . fst) history} | ||
48 | where | ||
49 | youngest :: UTCTime | ||
50 | youngest = maximum $ created . fst <$> history | ||
51 | filterAge :: UTCTime -> Bool | ||
52 | filterAge time = not $ (youngest `diffUTCTime` time) > maxAge | ||
diff --git a/server/thermoprint-server.cabal b/server/thermoprint-server.cabal index 3f0f832..62eb0ca 100644 --- a/server/thermoprint-server.cabal +++ b/server/thermoprint-server.cabal | |||
@@ -23,6 +23,7 @@ library | |||
23 | , Thermoprint.Server.API | 23 | , Thermoprint.Server.API |
24 | , Thermoprint.Server.Push | 24 | , Thermoprint.Server.Push |
25 | , Thermoprint.Server.Queue | 25 | , Thermoprint.Server.Queue |
26 | , Thermoprint.Server.Queue.Utils | ||
26 | , Thermoprint.Server.Printer | 27 | , Thermoprint.Server.Printer |
27 | , Thermoprint.Server.Printer.Debug | 28 | , Thermoprint.Server.Printer.Debug |
28 | , Thermoprint.Server.Printer.Debug.Delayed | 29 | , Thermoprint.Server.Printer.Debug.Delayed |