diff options
Diffstat (limited to 'server')
-rw-r--r-- | server/src/Thermoprint/Server.hs | 105 | ||||
-rw-r--r-- | server/src/Thermoprint/Server/API.hs | 104 | ||||
-rw-r--r-- | server/thermoprint-server.cabal | 1 |
3 files changed, 117 insertions, 93 deletions
diff --git a/server/src/Thermoprint/Server.hs b/server/src/Thermoprint/Server.hs index d1ee6ee..419679c 100644 --- a/server/src/Thermoprint/Server.hs +++ b/server/src/Thermoprint/Server.hs | |||
@@ -14,47 +14,34 @@ module Thermoprint.Server | |||
14 | import Data.Default.Class | 14 | import Data.Default.Class |
15 | import qualified Config.Dyre as Dyre | 15 | import qualified Config.Dyre as Dyre |
16 | 16 | ||
17 | import System.IO (hPutStrLn, stderr) | 17 | import Control.Monad (mapM_) |
18 | import System.Exit (exitFailure) | ||
19 | |||
20 | import Control.Monad ((<=<), mapM_, liftM2) | ||
21 | import Prelude hiding ((.), id) | ||
22 | import Control.Category | ||
23 | 18 | ||
24 | import Data.Maybe (maybe) | 19 | import Data.Maybe (maybe) |
25 | 20 | ||
21 | import Control.Monad.Trans.Resource | ||
26 | import Control.Monad.Logger | 22 | import Control.Monad.Logger |
27 | import Control.Monad.Reader | 23 | import Control.Monad.Reader |
28 | import Control.Monad.Trans.Resource | ||
29 | import Control.Monad.Trans.Either | ||
30 | import Control.Monad.IO.Class | 24 | import Control.Monad.IO.Class |
31 | 25 | ||
32 | import Data.Functor.Compose | ||
33 | |||
34 | import Thermoprint.API hiding (JobId(..), DraftId(..)) | ||
35 | import qualified Thermoprint.API as API (JobId(..), DraftId(..)) | ||
36 | import Data.Set (Set) | ||
37 | import qualified Data.Set as Set | ||
38 | import Data.Sequence (Seq) | ||
39 | import qualified Data.Sequence as Seq | ||
40 | import Data.Map (Map) | ||
41 | import qualified Data.Map as Map | ||
42 | |||
43 | import Data.Text (Text) | 26 | import Data.Text (Text) |
44 | import qualified Data.Text as T (pack) | 27 | import qualified Data.Text as T (pack) |
45 | 28 | ||
46 | import qualified Network.Wai.Handler.Warp as Warp | 29 | import qualified Network.Wai.Handler.Warp as Warp |
47 | import Network.Wai (Application) | 30 | import Network.Wai (Application) |
48 | 31 | ||
49 | import Servant | 32 | import Servant.Server (serve) |
50 | import Servant.Server | 33 | import Servant.Server.Internal.Enter (enter, (:~>)(..)) |
51 | import Servant.Server.Internal.Enter | ||
52 | 34 | ||
53 | import Database.Persist.Sql (runMigrationSilent, ConnectionPool, runSqlPool) | 35 | import Database.Persist.Sql (runMigrationSilent, ConnectionPool, runSqlPool) |
54 | 36 | ||
55 | 37 | ||
38 | import Thermoprint.API (thermoprintAPI) | ||
39 | |||
56 | import Thermoprint.Server.Database | 40 | import Thermoprint.Server.Database |
41 | import qualified Thermoprint.Server.API as API (thermoprintServer) | ||
42 | import Thermoprint.Server.API hiding (thermoprintServer) | ||
57 | 43 | ||
44 | |||
58 | data Config = Config { dyreError :: Maybe String -- ^ Set by 'Dyre' -- sent to log as an error | 45 | data Config = Config { dyreError :: Maybe String -- ^ Set by 'Dyre' -- sent to log as an error |
59 | , warpSettings :: Warp.Settings -- ^ Configure 'Warp's behaviour | 46 | , warpSettings :: Warp.Settings -- ^ Configure 'Warp's behaviour |
60 | } | 47 | } |
@@ -64,9 +51,6 @@ instance Default Config where | |||
64 | , warpSettings = Warp.defaultSettings | 51 | , warpSettings = Warp.defaultSettings |
65 | } | 52 | } |
66 | 53 | ||
67 | data HandlerInput = HandlerInput { sqlPool :: ConnectionPool | ||
68 | } | ||
69 | |||
70 | 54 | ||
71 | thermoprintServer :: ( MonadLoggerIO m | 55 | thermoprintServer :: ( MonadLoggerIO m |
72 | , MonadIO m | 56 | , MonadIO m |
@@ -82,70 +66,5 @@ thermoprintServer io = Dyre.wrapMain $ Dyre.defaultParams | |||
82 | where | 66 | where |
83 | realMain Config{..} = unNat io $ do | 67 | realMain Config{..} = unNat io $ do |
84 | maybe (return ()) ($(logErrorS) "Dyre" . T.pack) dyreError | 68 | maybe (return ()) ($(logErrorS) "Dyre" . T.pack) dyreError |
85 | 69 | mapM_ ($(logWarnS) "DB") =<< runSqlPool (runMigrationSilent migrateAll) =<< ask | |
86 | sqlPool <- ask | 70 | liftIO . Warp.runSettings warpSettings . serve thermoprintAPI . flip enter API.thermoprintServer =<< handlerNat |
87 | logFunc <- askLoggerIO | ||
88 | |||
89 | runSqlPool (runMigrationSilent migrateAll) sqlPool >>= mapM_ ($(logWarnS) "DB") | ||
90 | |||
91 | let | ||
92 | handlerInput = HandlerInput | ||
93 | { sqlPool = sqlPool | ||
94 | } | ||
95 | io' :: ProtoHandler :~> IO | ||
96 | io' = Nat (($ logFunc) . runLoggingT) . runReaderTNat handlerInput | ||
97 | liftIO . Warp.runSettings warpSettings . serve thermoprintAPI $ enter (hoistNat io') thermoprintServer' | ||
98 | |||
99 | type ProtoHandler = ReaderT HandlerInput (LoggingT IO) | ||
100 | type Handler = EitherT ServantErr ProtoHandler | ||
101 | |||
102 | (<||>) :: Monad m => m a -> m b -> m (a :<|> b) | ||
103 | (<||>) = liftM2 (:<|>) | ||
104 | infixr 9 <||> | ||
105 | |||
106 | thermoprintServer' :: ServerT ThermoprintAPI Handler | ||
107 | thermoprintServer' = listPrinters | ||
108 | :<|> (listJobs :<|> queueJob) | ||
109 | :<|> getJob <||> jobStatus <||> deleteJob | ||
110 | :<|> (listDrafts :<|> addDraft) | ||
111 | :<|> updateDraft <||> getDraft <||> deleteDraft <||> printDraft | ||
112 | |||
113 | |||
114 | listPrinters :: Handler (Map PrinterId PrinterStatus) | ||
115 | listPrinters = return $ Map.fromList [(1, Available), (7, Available), (3, Available)] | ||
116 | |||
117 | queueJob :: Maybe PrinterId -> Printout -> Handler API.JobId | ||
118 | queueJob = return undefined | ||
119 | |||
120 | printerStatus :: PrinterId -> Handler PrinterStatus | ||
121 | printerStatus = return undefined | ||
122 | |||
123 | listJobs :: Maybe PrinterId -> Maybe API.JobId -> Maybe API.JobId -> Handler (Seq (API.JobId, JobStatus)) | ||
124 | listJobs = return undefined | ||
125 | |||
126 | getJob :: API.JobId -> Handler Printout | ||
127 | getJob = return undefined | ||
128 | |||
129 | jobStatus :: API.JobId -> Handler JobStatus | ||
130 | jobStatus = return undefined | ||
131 | |||
132 | deleteJob :: API.JobId -> Handler () | ||
133 | deleteJob = return undefined | ||
134 | |||
135 | listDrafts :: Handler (Map API.DraftId (Maybe DraftTitle)) | ||
136 | listDrafts = return undefined | ||
137 | |||
138 | addDraft :: Maybe DraftTitle -> Printout -> Handler API.DraftId | ||
139 | addDraft = return undefined | ||
140 | |||
141 | updateDraft :: API.DraftId -> Maybe DraftTitle -> Printout -> Handler () | ||
142 | updateDraft = return undefined | ||
143 | |||
144 | getDraft :: API.DraftId -> Handler (Maybe DraftTitle, Printout) | ||
145 | getDraft = return undefined | ||
146 | |||
147 | deleteDraft :: API.DraftId -> Handler () | ||
148 | deleteDraft = return undefined | ||
149 | |||
150 | printDraft :: API.DraftId -> Maybe PrinterId -> Handler API.JobId | ||
151 | printDraft = return undefined | ||
diff --git a/server/src/Thermoprint/Server/API.hs b/server/src/Thermoprint/Server/API.hs new file mode 100644 index 0000000..9559ad1 --- /dev/null +++ b/server/src/Thermoprint/Server/API.hs | |||
@@ -0,0 +1,104 @@ | |||
1 | {-# LANGUAGE TypeOperators #-} | ||
2 | {-# LANGUAGE FlexibleContexts #-} | ||
3 | {-# LANGUAGE TemplateHaskell #-} | ||
4 | |||
5 | module Thermoprint.Server.API | ||
6 | ( ProtoHandler, Handler | ||
7 | , thermoprintServer | ||
8 | , handlerNat | ||
9 | ) where | ||
10 | |||
11 | import Thermoprint.API hiding (JobId(..), DraftId(..)) | ||
12 | import qualified Thermoprint.API as API (JobId(..), DraftId(..)) | ||
13 | import Data.Set (Set) | ||
14 | import qualified Data.Set as Set | ||
15 | import Data.Sequence (Seq) | ||
16 | import qualified Data.Sequence as Seq | ||
17 | import Data.Map (Map) | ||
18 | import qualified Data.Map as Map | ||
19 | |||
20 | import Servant | ||
21 | import Servant.Server | ||
22 | import Servant.Server.Internal.Enter | ||
23 | |||
24 | import Control.Monad.Logger | ||
25 | import Control.Monad.Reader | ||
26 | import Control.Monad.Trans.Either | ||
27 | import Control.Monad.IO.Class | ||
28 | |||
29 | import Control.Monad ((<=<), liftM2) | ||
30 | import Prelude hiding ((.), id) | ||
31 | import Control.Category | ||
32 | |||
33 | import Database.Persist | ||
34 | import Database.Persist.Sql | ||
35 | |||
36 | type ProtoHandler = ReaderT HandlerInput (LoggingT IO) | ||
37 | type Handler = EitherT ServantErr ProtoHandler | ||
38 | |||
39 | data HandlerInput = HandlerInput { sqlPool :: ConnectionPool | ||
40 | } | ||
41 | |||
42 | handlerNat :: ( MonadReader ConnectionPool m | ||
43 | , MonadLoggerIO m | ||
44 | ) => m (Handler :~> EitherT ServantErr IO) | ||
45 | handlerNat = do | ||
46 | sqlPool <- ask | ||
47 | logFunc <- askLoggerIO | ||
48 | let | ||
49 | handlerInput = HandlerInput | ||
50 | { sqlPool = sqlPool | ||
51 | } | ||
52 | protoNat :: ProtoHandler :~> IO | ||
53 | protoNat = Nat (($ logFunc) . runLoggingT) . runReaderTNat handlerInput | ||
54 | return $ hoistNat protoNat | ||
55 | |||
56 | thermoprintServer :: ServerT ThermoprintAPI Handler | ||
57 | thermoprintServer = listPrinters | ||
58 | :<|> (listJobs :<|> queueJob) | ||
59 | :<|> getJob <||> jobStatus <||> deleteJob | ||
60 | :<|> (listDrafts :<|> addDraft) | ||
61 | :<|> updateDraft <||> getDraft <||> deleteDraft <||> printDraft | ||
62 | where | ||
63 | (<||>) :: Monad m => m a -> m b -> m (a :<|> b) | ||
64 | (<||>) = liftM2 (:<|>) | ||
65 | infixr 9 <||> | ||
66 | |||
67 | listPrinters :: Handler (Map PrinterId PrinterStatus) | ||
68 | listPrinters = return $ Map.fromList [(1, Available), (7, Available), (3, Available)] | ||
69 | |||
70 | queueJob :: Maybe PrinterId -> Printout -> Handler API.JobId | ||
71 | queueJob = return undefined | ||
72 | |||
73 | printerStatus :: PrinterId -> Handler PrinterStatus | ||
74 | printerStatus = return undefined | ||
75 | |||
76 | listJobs :: Maybe PrinterId -> Maybe API.JobId -> Maybe API.JobId -> Handler (Seq (API.JobId, JobStatus)) | ||
77 | listJobs = return undefined | ||
78 | |||
79 | getJob :: API.JobId -> Handler Printout | ||
80 | getJob = return undefined | ||
81 | |||
82 | jobStatus :: API.JobId -> Handler JobStatus | ||
83 | jobStatus = return undefined | ||
84 | |||
85 | deleteJob :: API.JobId -> Handler () | ||
86 | deleteJob = return undefined | ||
87 | |||
88 | listDrafts :: Handler (Map API.DraftId (Maybe DraftTitle)) | ||
89 | listDrafts = return undefined | ||
90 | |||
91 | addDraft :: Maybe DraftTitle -> Printout -> Handler API.DraftId | ||
92 | addDraft = return undefined | ||
93 | |||
94 | updateDraft :: API.DraftId -> Maybe DraftTitle -> Printout -> Handler () | ||
95 | updateDraft = return undefined | ||
96 | |||
97 | getDraft :: API.DraftId -> Handler (Maybe DraftTitle, Printout) | ||
98 | getDraft = return undefined | ||
99 | |||
100 | deleteDraft :: API.DraftId -> Handler () | ||
101 | deleteDraft = return undefined | ||
102 | |||
103 | printDraft :: API.DraftId -> Maybe PrinterId -> Handler API.JobId | ||
104 | printDraft = return undefined | ||
diff --git a/server/thermoprint-server.cabal b/server/thermoprint-server.cabal index 45e57a6..45f24d3 100644 --- a/server/thermoprint-server.cabal +++ b/server/thermoprint-server.cabal | |||
@@ -19,6 +19,7 @@ cabal-version: >=1.10 | |||
19 | library | 19 | library |
20 | exposed-modules: Thermoprint.Server | 20 | exposed-modules: Thermoprint.Server |
21 | , Thermoprint.Server.Database | 21 | , Thermoprint.Server.Database |
22 | , Thermoprint.Server.API | ||
22 | -- other-modules: | 23 | -- other-modules: |
23 | -- other-extensions: | 24 | -- other-extensions: |
24 | build-depends: base >=4.8 && <5 | 25 | build-depends: base >=4.8 && <5 |