diff options
Diffstat (limited to 'server')
-rw-r--r-- | server/src/Thermoprint/Server/API.hs | 37 |
1 files changed, 29 insertions, 8 deletions
diff --git a/server/src/Thermoprint/Server/API.hs b/server/src/Thermoprint/Server/API.hs index a1efb8f..bff8eed 100644 --- a/server/src/Thermoprint/Server/API.hs +++ b/server/src/Thermoprint/Server/API.hs | |||
@@ -2,6 +2,7 @@ | |||
2 | {-# LANGUAGE FlexibleContexts #-} | 2 | {-# LANGUAGE FlexibleContexts #-} |
3 | {-# LANGUAGE TemplateHaskell #-} | 3 | {-# LANGUAGE TemplateHaskell #-} |
4 | {-# LANGUAGE OverloadedStrings #-} | 4 | {-# LANGUAGE OverloadedStrings #-} |
5 | {-# LANGUAGE TupleSections #-} | ||
5 | 6 | ||
6 | module Thermoprint.Server.API | 7 | module Thermoprint.Server.API |
7 | ( ProtoHandler, Handler | 8 | ( ProtoHandler, Handler |
@@ -38,7 +39,11 @@ import Control.Monad ((<=<), liftM2) | |||
38 | import Prelude hiding ((.), id, mapM) | 39 | import Prelude hiding ((.), id, mapM) |
39 | import Control.Category | 40 | import Control.Category |
40 | 41 | ||
42 | import Data.Foldable (toList) | ||
41 | import Data.Traversable (mapM) | 43 | import Data.Traversable (mapM) |
44 | import Data.Bifunctor | ||
45 | import Data.Monoid | ||
46 | import Data.Maybe | ||
42 | 47 | ||
43 | import Database.Persist | 48 | import Database.Persist |
44 | import Database.Persist.Sql | 49 | import Database.Persist.Sql |
@@ -82,16 +87,26 @@ thermoprintServer = listPrinters | |||
82 | (<||>) = liftM2 (:<|>) | 87 | (<||>) = liftM2 (:<|>) |
83 | infixr 9 <||> | 88 | infixr 9 <||> |
84 | 89 | ||
85 | lookupPrinter :: Maybe PrinterId -> Handler Printer | 90 | lookupPrinter :: Maybe PrinterId -> Handler (PrinterId, Printer) |
86 | lookupPrinter pId = asks printers >>= maybePrinter' pId | 91 | lookupPrinter pId = asks printers >>= maybePrinter' pId |
87 | where | 92 | where |
88 | maybePrinter' Nothing printerMap | 93 | maybePrinter' Nothing printerMap |
89 | | Map.null printerMap = left $ err501 { errBody = "No printers available" } | 94 | | Map.null printerMap = left $ err501 { errBody = "No printers available" } |
90 | | otherwise = return . snd $ Map.findMin printerMap | 95 | | otherwise = return $ Map.findMin printerMap |
91 | maybePrinter (Just pId) printerMap | 96 | maybePrinter (Just pId) printerMap |
92 | | Just printer <- Map.lookup pId printerMap = return printer | 97 | | Just printer <- Map.lookup pId printerMap = return (pId, printer) |
93 | | otherwise = left $ err404 { errBody = "No such printer" } | 98 | | otherwise = left $ err404 { errBody = "No such printer" } |
94 | 99 | ||
100 | queue' :: MonadIO m => Printer -> m Queue | ||
101 | queue' = liftIO . readTVarIO . queue | ||
102 | |||
103 | extractJobs :: (PrinterId, Queue) -> Seq (API.JobId, JobStatus) | ||
104 | extractJobs (pId, Queue pending current history) = fmap (, Queued pId) pending' <> maybe Seq.empty Seq.singleton (fmap (, Printing pId) current') <> fmap (second $ maybe Done Failed) history' | ||
105 | where | ||
106 | pending' = fmap (castId' . unJobKey) pending | ||
107 | current' = fmap (castId' . unJobKey) current | ||
108 | history' = fmap (first $ castId' . unJobKey) history | ||
109 | |||
95 | listPrinters :: Handler (Map PrinterId PrinterStatus) | 110 | listPrinters :: Handler (Map PrinterId PrinterStatus) |
96 | listPrinters = fmap toStatus <$> (mapM (liftIO . readTVarIO . queue) . printers =<< ask) | 111 | listPrinters = fmap toStatus <$> (mapM (liftIO . readTVarIO . queue) . printers =<< ask) |
97 | where | 112 | where |
@@ -99,19 +114,25 @@ listPrinters = fmap toStatus <$> (mapM (liftIO . readTVarIO . queue) . printers | |||
99 | toStatus (Queue _ (Just id) _) = Busy . castId $ fromSqlKey id | 114 | toStatus (Queue _ (Just id) _) = Busy . castId $ fromSqlKey id |
100 | 115 | ||
101 | queueJob :: Maybe PrinterId -> Printout -> Handler API.JobId | 116 | queueJob :: Maybe PrinterId -> Printout -> Handler API.JobId |
102 | queueJob pId printout = lift . fmap (castId' . unJobKey) . withReaderT sqlPool . addToQueue printout =<< lookupPrinter pId | 117 | queueJob pId printout = lift . fmap (castId' . unJobKey) . withReaderT sqlPool . addToQueue printout . snd =<< lookupPrinter pId |
103 | 118 | ||
104 | printerStatus :: PrinterId -> Handler PrinterStatus | 119 | printerStatus :: PrinterId -> Handler PrinterStatus |
105 | printerStatus = return undefined | 120 | printerStatus = fmap queueToStatus . queue' . snd <=< lookupPrinter . Just |
121 | where | ||
122 | queueToStatus (Queue _ Nothing _) = Available | ||
123 | queueToStatus (Queue _ (Just id) _) = Busy . castId' $ unJobKey id | ||
106 | 124 | ||
107 | listJobs :: Maybe PrinterId -> Maybe API.JobId -> Maybe API.JobId -> Handler (Seq (API.JobId, JobStatus)) | 125 | listJobs :: Maybe PrinterId -> Maybe API.JobId -> Maybe API.JobId -> Handler (Seq (API.JobId, JobStatus)) |
108 | listJobs = return undefined | 126 | listJobs Nothing minId maxId = fmap mconcat . mapM (\pId -> listJobs (Just pId) minId maxId) =<< asks (Map.keys . printers) |
127 | listJobs pId minId maxId = fmap (filterJobs . extractJobs) . (\(a, b) -> (,) a <$> queue' b) =<< lookupPrinter pId | ||
128 | where | ||
129 | filterJobs = Seq.filter (\(id, _) -> maybe True (< id) minId && maybe True (> id) maxId) | ||
109 | 130 | ||
110 | getJob :: API.JobId -> Handler Printout | 131 | getJob :: API.JobId -> Handler Printout |
111 | getJob = return undefined | 132 | getJob jobId = fmap jobContent . maybe (left err404) return =<< runSqlPool (get . JobKey . SqlBackendKey $ castId jobId) =<< asks sqlPool |
112 | 133 | ||
113 | jobStatus :: API.JobId -> Handler JobStatus | 134 | jobStatus :: API.JobId -> Handler JobStatus |
114 | jobStatus = return undefined | 135 | jobStatus jobId = maybe (left err404) return . lookup jobId . toList =<< listJobs Nothing Nothing Nothing |
115 | 136 | ||
116 | deleteJob :: API.JobId -> Handler () | 137 | deleteJob :: API.JobId -> Handler () |
117 | deleteJob = return undefined | 138 | deleteJob = return undefined |