diff options
| author | Gregor Kleen <gkleen@yggdrasil.li> | 2016-01-23 14:47:59 +0000 | 
|---|---|---|
| committer | Gregor Kleen <gkleen@yggdrasil.li> | 2016-01-23 14:47:59 +0000 | 
| commit | 8553c33f72c41e553cbef4e7175cef8cec3cdbe2 (patch) | |
| tree | a5f82445047b6a4eefb803c0f3ee7dec5d1247f7 /server/src/Thermoprint/Server | |
| parent | 0a5b8082e5ddcd22b846cc7c145af2468c542fa4 (diff) | |
| download | thermoprint-8553c33f72c41e553cbef4e7175cef8cec3cdbe2.tar thermoprint-8553c33f72c41e553cbef4e7175cef8cec3cdbe2.tar.gz thermoprint-8553c33f72c41e553cbef4e7175cef8cec3cdbe2.tar.bz2 thermoprint-8553c33f72c41e553cbef4e7175cef8cec3cdbe2.tar.xz thermoprint-8553c33f72c41e553cbef4e7175cef8cec3cdbe2.zip  | |
Printer handling threads & printers handler
Diffstat (limited to 'server/src/Thermoprint/Server')
| -rw-r--r-- | server/src/Thermoprint/Server/API.hs | 24 | ||||
| -rw-r--r-- | server/src/Thermoprint/Server/Printer.hs | 5 | 
2 files changed, 22 insertions, 7 deletions
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 | ||
