aboutsummaryrefslogtreecommitdiff
path: root/server/src/Thermoprint/Server.hs
blob: d1ee6ee711209a6a008a54a7882aa98a48e74607 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
{-# LANGUAGE RecordWildCards   #-}
{-# LANGUAGE TemplateHaskell   #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators     #-}
{-# LANGUAGE FlexibleContexts  #-}

module Thermoprint.Server
       ( thermoprintServer
       , Config(..)
       , module Data.Default.Class
       , module Servant.Server.Internal.Enter
       ) where

import Data.Default.Class
import qualified Config.Dyre as Dyre

import System.IO (hPutStrLn, stderr)
import System.Exit (exitFailure)

import Control.Monad ((<=<), mapM_, liftM2)
import Prelude hiding ((.), id)
import Control.Category

import Data.Maybe (maybe)

import Control.Monad.Logger
import Control.Monad.Reader
import Control.Monad.Trans.Resource
import Control.Monad.Trans.Either
import Control.Monad.IO.Class

import Data.Functor.Compose

import Thermoprint.API hiding (JobId(..), DraftId(..))
import qualified Thermoprint.API as API (JobId(..), DraftId(..))
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Sequence (Seq)
import qualified Data.Sequence as Seq
import Data.Map (Map)
import qualified Data.Map as Map

import Data.Text (Text)
import qualified Data.Text as T (pack)

import qualified Network.Wai.Handler.Warp as Warp
import Network.Wai (Application)

import Servant
import Servant.Server
import Servant.Server.Internal.Enter

import Database.Persist.Sql (runMigrationSilent, ConnectionPool, runSqlPool)


import Thermoprint.Server.Database

data Config = Config { dyreError    :: Maybe String -- ^ Set by 'Dyre' -- sent to log as an error
                     , warpSettings :: Warp.Settings -- ^ Configure 'Warp's behaviour
                     }

instance Default Config where
  def = Config { dyreError    = Nothing
               , warpSettings = Warp.defaultSettings
               }

data HandlerInput = HandlerInput { sqlPool :: ConnectionPool
                                 }


thermoprintServer :: ( MonadLoggerIO m
                     , MonadIO m
                     , MonadBaseControl IO m
                     , MonadReader ConnectionPool m
                     ) => (m :~> IO) -> Config -> IO ()
-- ^ Run the server
thermoprintServer io = Dyre.wrapMain $ Dyre.defaultParams
  { Dyre.projectName = "thermoprint-server"
  , Dyre.realMain    = realMain
  , Dyre.showError   = (\cfg msg -> cfg { dyreError = Just msg })
  }
    where
      realMain Config{..} = unNat io $ do
        maybe (return ()) ($(logErrorS) "Dyre" . T.pack) dyreError
        
        sqlPool <- ask
        logFunc <- askLoggerIO

        runSqlPool (runMigrationSilent migrateAll) sqlPool >>= mapM_ ($(logWarnS) "DB")
        
        let
          handlerInput = HandlerInput
            { sqlPool = sqlPool
            }
          io' :: ProtoHandler :~> IO
          io' = Nat (($ logFunc) . runLoggingT) . runReaderTNat handlerInput
        liftIO . Warp.runSettings warpSettings . serve thermoprintAPI $ enter (hoistNat io') thermoprintServer'

type ProtoHandler = ReaderT HandlerInput (LoggingT IO)
type Handler      = EitherT ServantErr ProtoHandler

(<||>) :: Monad m => m a -> m b -> m (a :<|> b)
(<||>) = liftM2 (:<|>)
infixr 9 <||>

thermoprintServer' :: ServerT ThermoprintAPI Handler
thermoprintServer' = listPrinters
                     :<|> (listJobs :<|> queueJob)
                     :<|> getJob <||> jobStatus <||> deleteJob
                     :<|> (listDrafts :<|> addDraft)
                     :<|> updateDraft <||> getDraft <||> deleteDraft <||> printDraft


listPrinters :: Handler (Map PrinterId PrinterStatus)
listPrinters = return $ Map.fromList [(1, Available), (7, Available), (3, Available)]

queueJob :: Maybe PrinterId -> Printout -> Handler API.JobId
queueJob = return undefined

printerStatus :: PrinterId -> Handler PrinterStatus
printerStatus = return undefined

listJobs :: Maybe PrinterId -> Maybe API.JobId -> Maybe API.JobId -> Handler (Seq (API.JobId, JobStatus))
listJobs = return undefined

getJob :: API.JobId -> Handler Printout
getJob = return undefined

jobStatus :: API.JobId -> Handler JobStatus
jobStatus = return undefined

deleteJob :: API.JobId -> Handler ()
deleteJob = return undefined

listDrafts :: Handler (Map API.DraftId (Maybe DraftTitle))
listDrafts = return undefined

addDraft :: Maybe DraftTitle -> Printout -> Handler API.DraftId
addDraft = return undefined

updateDraft :: API.DraftId -> Maybe DraftTitle -> Printout -> Handler ()
updateDraft = return undefined

getDraft :: API.DraftId -> Handler (Maybe DraftTitle, Printout)
getDraft = return undefined

deleteDraft :: API.DraftId -> Handler ()
deleteDraft = return undefined

printDraft :: API.DraftId -> Maybe PrinterId -> Handler API.JobId
printDraft = return undefined