aboutsummaryrefslogtreecommitdiff
path: root/server/src/Thermoprint/Server.hs
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2016-02-22 20:22:42 +0000
committerGregor Kleen <gkleen@yggdrasil.li>2016-02-22 20:22:42 +0000
commit760027dbcd7185be038299efb18e0cc37c8088c4 (patch)
tree818a7b5700c904530a633da5139d1a0ee237eba4 /server/src/Thermoprint/Server.hs
parent6dfb26d6f2966b98c278afd3e269826c96c0ab26 (diff)
downloadthermoprint-760027dbcd7185be038299efb18e0cc37c8088c4.tar
thermoprint-760027dbcd7185be038299efb18e0cc37c8088c4.tar.gz
thermoprint-760027dbcd7185be038299efb18e0cc37c8088c4.tar.bz2
thermoprint-760027dbcd7185be038299efb18e0cc37c8088c4.tar.xz
thermoprint-760027dbcd7185be038299efb18e0cc37c8088c4.zip
Websocket based push notifications
Diffstat (limited to 'server/src/Thermoprint/Server.hs')
-rw-r--r--server/src/Thermoprint/Server.hs28
1 files changed, 24 insertions, 4 deletions
diff --git a/server/src/Thermoprint/Server.hs b/server/src/Thermoprint/Server.hs
index df2d8e9..446c63e 100644
--- a/server/src/Thermoprint/Server.hs
+++ b/server/src/Thermoprint/Server.hs
@@ -6,6 +6,7 @@
6{-# LANGUAGE ImpredicativeTypes #-} 6{-# LANGUAGE ImpredicativeTypes #-}
7{-# LANGUAGE ExistentialQuantification #-} 7{-# LANGUAGE ExistentialQuantification #-}
8{-# LANGUAGE ViewPatterns #-} 8{-# LANGUAGE ViewPatterns #-}
9{-# LANGUAGE DataKinds #-}
9 10
10module Thermoprint.Server 11module Thermoprint.Server
11 ( thermoprintServer 12 ( thermoprintServer
@@ -25,9 +26,17 @@ import qualified Data.Map as Map
25 26
26import Data.Set (Set) 27import Data.Set (Set)
27import qualified Data.Set as Set 28import qualified Data.Set as Set
29
30import Data.Sequence (Seq)
31import qualified Data.Sequence as Seq
32
33import Data.Time (UTCTime)
28 34
29import Data.Maybe (maybe) 35import Data.Maybe (maybe)
30import Data.Foldable (mapM_, forM_, foldlM) 36import Data.Foldable (mapM_, forM_, foldlM)
37import Data.Function hiding (id, (.))
38import Data.Bifunctor
39import Data.Proxy
31 40
32import Control.Monad.Trans.Resource 41import Control.Monad.Trans.Resource
33import Control.Monad.Trans.Control 42import Control.Monad.Trans.Control
@@ -53,14 +62,20 @@ import Network.Wai (Application)
53 62
54import Servant.Server (serve) 63import Servant.Server (serve)
55import Servant.Server.Internal.Enter (enter, (:~>)(..)) 64import Servant.Server.Internal.Enter (enter, (:~>)(..))
65import Servant.API
66import Servant.Utils.Links
67import Network.URI
56 68
57import Database.Persist.Sql (runMigrationSilent, ConnectionPool, runSqlPool) 69import Database.Persist.Sql (runMigrationSilent, ConnectionPool, runSqlPool)
58 70
59 71
60import Thermoprint.API (thermoprintAPI, PrinterId) 72import Thermoprint.API (thermoprintAPI, PrinterStatus, JobStatus)
73import qualified Thermoprint.API as API (PrinterId, JobId)
61 74
62import Thermoprint.Server.Fork 75import Thermoprint.Server.Fork
63 76
77import Thermoprint.Server.Push
78
64import Thermoprint.Server.Database 79import Thermoprint.Server.Database
65import Thermoprint.Server.Printer 80import Thermoprint.Server.Printer
66import Thermoprint.Server.Queue 81import Thermoprint.Server.Queue
@@ -72,8 +87,8 @@ import Debug.Trace
72-- | Compile-time configuration for 'thermoprintServer' 87-- | Compile-time configuration for 'thermoprintServer'
73data Config m = Config { dyreError :: Maybe String -- ^ Set by 'Dyre' -- sent to log as an error 88data Config m = Config { dyreError :: Maybe String -- ^ Set by 'Dyre' -- sent to log as an error
74 , warpSettings :: Warp.Settings -- ^ Configure 'Warp's behaviour 89 , warpSettings :: Warp.Settings -- ^ Configure 'Warp's behaviour
75 , printers :: Map PrinterId Printer 90 , printers :: Map API.PrinterId Printer
76 , queueManagers :: PrinterId -> QMConfig m 91 , queueManagers :: API.PrinterId -> QMConfig m
77 } 92 }
78 93
79data QMConfig m = forall t. ( MonadTrans t 94data QMConfig m = forall t. ( MonadTrans t
@@ -137,4 +152,9 @@ thermoprintServer dyre io = Dyre.wrapMain $ Dyre.defaultParams
137 let 152 let
138 runQM' (queueManagers -> QMConfig qm nat) printer = unNat nat $ runQM gcChan qm printer 153 runQM' (queueManagers -> QMConfig qm nat) printer = unNat nat $ runQM gcChan qm printer
139 mapM_ (fork tMgr . uncurry runQM') $ Map.toList printers 154 mapM_ (fork tMgr . uncurry runQM') $ Map.toList printers
140 liftIO . Warp.runSettings warpSettings . serve thermoprintAPI . flip enter API.thermoprintServer =<< handlerNat printers 155 nChan <- liftIO $ newBroadcastTChanIO
156 let
157 printerUrl :: API.PrinterId -> URI
158 printerUrl = safeLink thermoprintAPI (Proxy :: Proxy ("jobs" :> QueryParam "printer" API.PrinterId :> Get '[JSON] (Seq (API.JobId, UTCTime, JobStatus))))
159 mapM_ (fork tMgr . uncurry (notifyOnChange nChan ((==) `on` fromZipper)) . bimap printerUrl queue) $ Map.toList printers
160 liftIO . Warp.runSettings warpSettings . withPush nChan . serve thermoprintAPI . flip enter API.thermoprintServer =<< handlerNat printers nChan