diff options
-rw-r--r-- | server/src/Thermoprint/Server.hs | 16 | ||||
-rw-r--r-- | server/src/Thermoprint/Server/API.hs | 24 | ||||
-rw-r--r-- | server/src/Thermoprint/Server/Printer.hs | 5 | ||||
-rw-r--r-- | server/thermoprint-server.cabal | 1 | ||||
-rw-r--r-- | server/thermoprint-server.nix | 13 |
5 files changed, 43 insertions, 16 deletions
diff --git a/server/src/Thermoprint/Server.hs b/server/src/Thermoprint/Server.hs index 0d96de0..39bf0a1 100644 --- a/server/src/Thermoprint/Server.hs +++ b/server/src/Thermoprint/Server.hs | |||
@@ -9,19 +9,25 @@ module Thermoprint.Server | |||
9 | , Config(..) | 9 | , Config(..) |
10 | , module Data.Default.Class | 10 | , module Data.Default.Class |
11 | , module Servant.Server.Internal.Enter | 11 | , module Servant.Server.Internal.Enter |
12 | , module Thermoprint.Server.Printer | ||
12 | ) where | 13 | ) where |
13 | 14 | ||
14 | import Data.Default.Class | 15 | import Data.Default.Class |
15 | import qualified Config.Dyre as Dyre | 16 | import qualified Config.Dyre as Dyre |
16 | 17 | ||
17 | import Control.Monad (mapM_) | 18 | import Data.Map (Map) |
19 | import qualified Data.Map as Map | ||
18 | 20 | ||
19 | import Data.Maybe (maybe) | 21 | import Data.Maybe (maybe) |
22 | import Data.Foldable (mapM_, forM_) | ||
20 | 23 | ||
21 | import Control.Monad.Trans.Resource | 24 | import Control.Monad.Trans.Resource |
25 | import Control.Monad.Trans.Control | ||
22 | import Control.Monad.Logger | 26 | import Control.Monad.Logger |
23 | import Control.Monad.Reader | 27 | import Control.Monad.Reader |
24 | import Control.Monad.IO.Class | 28 | import Control.Monad.IO.Class |
29 | |||
30 | import Control.Concurrent | ||
25 | 31 | ||
26 | import Data.Text (Text) | 32 | import Data.Text (Text) |
27 | import qualified Data.Text as T (pack) | 33 | import qualified Data.Text as T (pack) |
@@ -35,20 +41,23 @@ import Servant.Server.Internal.Enter (enter, (:~>)(..)) | |||
35 | import Database.Persist.Sql (runMigrationSilent, ConnectionPool, runSqlPool) | 41 | import Database.Persist.Sql (runMigrationSilent, ConnectionPool, runSqlPool) |
36 | 42 | ||
37 | 43 | ||
38 | import Thermoprint.API (thermoprintAPI) | 44 | import Thermoprint.API (thermoprintAPI, PrinterId) |
39 | 45 | ||
40 | import Thermoprint.Server.Database | 46 | import Thermoprint.Server.Database |
47 | import Thermoprint.Server.Printer | ||
41 | import qualified Thermoprint.Server.API as API (thermoprintServer) | 48 | import qualified Thermoprint.Server.API as API (thermoprintServer) |
42 | import Thermoprint.Server.API hiding (thermoprintServer) | 49 | import Thermoprint.Server.API hiding (thermoprintServer) |
43 | 50 | ||
44 | -- | Compile-time configuration for 'thermoprintServer' | 51 | -- | Compile-time configuration for 'thermoprintServer' |
45 | data Config = Config { dyreError :: Maybe String -- ^ Set by 'Dyre' -- sent to log as an error | 52 | data Config = Config { dyreError :: Maybe String -- ^ Set by 'Dyre' -- sent to log as an error |
46 | , warpSettings :: Warp.Settings -- ^ Configure 'Warp's behaviour | 53 | , warpSettings :: Warp.Settings -- ^ Configure 'Warp's behaviour |
54 | , printers :: Map PrinterId Printer | ||
47 | } | 55 | } |
48 | 56 | ||
49 | instance Default Config where | 57 | instance Default Config where |
50 | def = Config { dyreError = Nothing | 58 | def = Config { dyreError = Nothing |
51 | , warpSettings = Warp.defaultSettings | 59 | , warpSettings = Warp.defaultSettings |
60 | , printers = Map.empty | ||
52 | } | 61 | } |
53 | 62 | ||
54 | 63 | ||
@@ -68,4 +77,5 @@ thermoprintServer io = Dyre.wrapMain $ Dyre.defaultParams | |||
68 | realMain Config{..} = unNat io $ do | 77 | realMain Config{..} = unNat io $ do |
69 | maybe (return ()) ($(logErrorS) "Dyre" . T.pack) dyreError | 78 | maybe (return ()) ($(logErrorS) "Dyre" . T.pack) dyreError |
70 | mapM_ ($(logWarnS) "DB") =<< runSqlPool (runMigrationSilent migrateAll) =<< ask | 79 | mapM_ ($(logWarnS) "DB") =<< runSqlPool (runMigrationSilent migrateAll) =<< ask |
71 | liftIO . Warp.runSettings warpSettings . serve thermoprintAPI . flip enter API.thermoprintServer =<< handlerNat | 80 | forM_ printers $ liftBaseDiscard forkIO . runPrinter |
81 | liftIO . Warp.runSettings warpSettings . serve thermoprintAPI . flip enter API.thermoprintServer =<< handlerNat printers | ||
diff --git a/server/src/Thermoprint/Server/API.hs b/server/src/Thermoprint/Server/API.hs index 6411a70..6a92caf 100644 --- a/server/src/Thermoprint/Server/API.hs +++ b/server/src/Thermoprint/Server/API.hs | |||
@@ -10,6 +10,9 @@ module Thermoprint.Server.API | |||
10 | 10 | ||
11 | import Thermoprint.API hiding (JobId(..), DraftId(..)) | 11 | import Thermoprint.API hiding (JobId(..), DraftId(..)) |
12 | import qualified Thermoprint.API as API (JobId(..), DraftId(..)) | 12 | import qualified Thermoprint.API as API (JobId(..), DraftId(..)) |
13 | |||
14 | import Thermoprint.Server.Printer (Printer(..), Queue(..)) | ||
15 | |||
13 | import Data.Set (Set) | 16 | import Data.Set (Set) |
14 | import qualified Data.Set as Set | 17 | import qualified Data.Set as Set |
15 | import Data.Sequence (Seq) | 18 | import Data.Sequence (Seq) |
@@ -26,10 +29,14 @@ import Control.Monad.Reader | |||
26 | import Control.Monad.Trans.Either | 29 | import Control.Monad.Trans.Either |
27 | import Control.Monad.IO.Class | 30 | import Control.Monad.IO.Class |
28 | 31 | ||
32 | import Control.Concurrent.STM | ||
33 | |||
29 | import Control.Monad ((<=<), liftM2) | 34 | import Control.Monad ((<=<), liftM2) |
30 | import Prelude hiding ((.), id) | 35 | import Prelude hiding ((.), id, mapM) |
31 | import Control.Category | 36 | import Control.Category |
32 | 37 | ||
38 | import Data.Traversable (mapM) | ||
39 | |||
33 | import Database.Persist | 40 | import Database.Persist |
34 | import Database.Persist.Sql | 41 | import Database.Persist.Sql |
35 | 42 | ||
@@ -37,21 +44,23 @@ type ProtoHandler = ReaderT HandlerInput (LoggingT IO) | |||
37 | type Handler = EitherT ServantErr ProtoHandler | 44 | type Handler = EitherT ServantErr ProtoHandler |
38 | 45 | ||
39 | -- ^ Runtime configuration of our handlers | 46 | -- ^ Runtime configuration of our handlers |
40 | data HandlerInput = HandlerInput { sqlPool :: ConnectionPool -- ^ How to interact with 'persistent' storage | 47 | data HandlerInput = HandlerInput { sqlPool :: ConnectionPool -- ^ How to interact with 'persistent' storage |
48 | , printers :: Map PrinterId Printer | ||
41 | } | 49 | } |
42 | 50 | ||
43 | handlerNat :: ( MonadReader ConnectionPool m | 51 | handlerNat :: ( MonadReader ConnectionPool m |
44 | , MonadLoggerIO m | 52 | , MonadLoggerIO m |
45 | ) => m (Handler :~> EitherT ServantErr IO) | 53 | ) => Map PrinterId Printer -> m (Handler :~> EitherT ServantErr IO) |
46 | -- ^ Servant requires its handlers to be 'EitherT ServantErr IO' | 54 | -- ^ Servant requires its handlers to be 'EitherT ServantErr IO' |
47 | -- | 55 | -- |
48 | -- This generates a 'Nat'ural transformation for squashing the monad-transformer-stack we use in our handlers to the monad 'servant-server' wants | 56 | -- This generates a 'Nat'ural transformation for squashing the monad-transformer-stack we use in our handlers to the monad 'servant-server' wants |
49 | handlerNat = do | 57 | handlerNat printerMap = do |
50 | sqlPool <- ask | 58 | sqlPool <- ask |
51 | logFunc <- askLoggerIO | 59 | logFunc <- askLoggerIO |
52 | let | 60 | let |
53 | handlerInput = HandlerInput | 61 | handlerInput = HandlerInput |
54 | { sqlPool = sqlPool | 62 | { sqlPool = sqlPool |
63 | , printers = printerMap | ||
55 | } | 64 | } |
56 | protoNat :: ProtoHandler :~> IO | 65 | protoNat :: ProtoHandler :~> IO |
57 | protoNat = Nat (($ logFunc) . runLoggingT) . runReaderTNat handlerInput | 66 | protoNat = Nat (($ logFunc) . runLoggingT) . runReaderTNat handlerInput |
@@ -71,7 +80,10 @@ thermoprintServer = listPrinters | |||
71 | infixr 9 <||> | 80 | infixr 9 <||> |
72 | 81 | ||
73 | listPrinters :: Handler (Map PrinterId PrinterStatus) | 82 | listPrinters :: Handler (Map PrinterId PrinterStatus) |
74 | listPrinters = return $ Map.fromList [(1, Available), (7, Available), (3, Available)] | 83 | listPrinters = fmap toStatus <$> (mapM (liftIO . readTVarIO . queue) . printers =<< ask) |
84 | where | ||
85 | toStatus (Queue _ Nothing _) = Available | ||
86 | toStatus (Queue _ (Just id) _) = Busy . castId $ fromSqlKey id | ||
75 | 87 | ||
76 | queueJob :: Maybe PrinterId -> Printout -> Handler API.JobId | 88 | queueJob :: Maybe PrinterId -> Printout -> Handler API.JobId |
77 | queueJob = return undefined | 89 | queueJob = return undefined |
diff --git a/server/src/Thermoprint/Server/Printer.hs b/server/src/Thermoprint/Server/Printer.hs index 0db98a0..f34b2fa 100644 --- a/server/src/Thermoprint/Server/Printer.hs +++ b/server/src/Thermoprint/Server/Printer.hs | |||
@@ -8,7 +8,7 @@ | |||
8 | {-# LANGUAGE DeriveGeneric, DeriveAnyClass #-} | 8 | {-# LANGUAGE DeriveGeneric, DeriveAnyClass #-} |
9 | 9 | ||
10 | module Thermoprint.Server.Printer | 10 | module Thermoprint.Server.Printer |
11 | ( Printer(..) | 11 | ( Printer(..), printer |
12 | , Queue(..) | 12 | , Queue(..) |
13 | , runPrinter | 13 | , runPrinter |
14 | ) where | 14 | ) where |
@@ -54,6 +54,9 @@ data Queue = Queue | |||
54 | } | 54 | } |
55 | deriving (Typeable, Generic, NFData) | 55 | deriving (Typeable, Generic, NFData) |
56 | 56 | ||
57 | printer :: (MonadIO m) => (forall m. (MonadIO m) => Printout -> m (Maybe PrintingError)) -> m Printer | ||
58 | printer f = Printer f <$> liftIO (newTVarIO $ Queue Seq.empty Nothing Seq.empty) | ||
59 | |||
57 | atomically' :: MonadIO m => STM a -> m a | 60 | atomically' :: MonadIO m => STM a -> m a |
58 | atomically' = liftIO . atomically | 61 | atomically' = liftIO . atomically |
59 | 62 | ||
diff --git a/server/thermoprint-server.cabal b/server/thermoprint-server.cabal index 926118d..185a0f3 100644 --- a/server/thermoprint-server.cabal +++ b/server/thermoprint-server.cabal | |||
@@ -41,6 +41,7 @@ library | |||
41 | , text >=1.2.1 && <2 | 41 | , text >=1.2.1 && <2 |
42 | , stm >=2.4.4 && <3 | 42 | , stm >=2.4.4 && <3 |
43 | , deepseq >=1.4.1 && <2 | 43 | , deepseq >=1.4.1 && <2 |
44 | , monad-control >=1.0.0 && <2 | ||
44 | hs-source-dirs: src | 45 | hs-source-dirs: src |
45 | default-language: Haskell2010 | 46 | default-language: Haskell2010 |
46 | 47 | ||
diff --git a/server/thermoprint-server.nix b/server/thermoprint-server.nix index 69bff1d..46859e2 100644 --- a/server/thermoprint-server.nix +++ b/server/thermoprint-server.nix | |||
@@ -1,7 +1,7 @@ | |||
1 | { mkDerivation, base, containers, data-default-class, deepseq, dyre | 1 | { mkDerivation, base, containers, data-default-class, deepseq, dyre |
2 | , either, monad-logger, mtl, persistent, persistent-sqlite | 2 | , either, monad-control, monad-logger, mtl, persistent |
3 | , persistent-template, resourcet, servant-server, stdenv, stm, text | 3 | , persistent-sqlite, persistent-template, resourcet, servant-server |
4 | , thermoprint-spec, transformers, wai, warp | 4 | , stdenv, stm, text, thermoprint-spec, transformers, wai, warp |
5 | }: | 5 | }: |
6 | mkDerivation { | 6 | mkDerivation { |
7 | pname = "thermoprint-server"; | 7 | pname = "thermoprint-server"; |
@@ -10,9 +10,10 @@ mkDerivation { | |||
10 | isLibrary = true; | 10 | isLibrary = true; |
11 | isExecutable = true; | 11 | isExecutable = true; |
12 | libraryHaskellDepends = [ | 12 | libraryHaskellDepends = [ |
13 | base containers data-default-class deepseq dyre either monad-logger | 13 | base containers data-default-class deepseq dyre either |
14 | mtl persistent persistent-template resourcet servant-server stm | 14 | monad-control monad-logger mtl persistent persistent-template |
15 | text thermoprint-spec transformers wai warp | 15 | resourcet servant-server stm text thermoprint-spec transformers wai |
16 | warp | ||
16 | ]; | 17 | ]; |
17 | executableHaskellDepends = [ | 18 | executableHaskellDepends = [ |
18 | base monad-logger mtl persistent-sqlite resourcet | 19 | base monad-logger mtl persistent-sqlite resourcet |