aboutsummaryrefslogtreecommitdiff
path: root/server/src/Thermoprint/Server/API.hs
blob: a1efb8f53f658bfa203792661b29058109b61d84 (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
{-# LANGUAGE TypeOperators     #-}
{-# LANGUAGE FlexibleContexts  #-}
{-# LANGUAGE TemplateHaskell   #-}
{-# LANGUAGE OverloadedStrings #-}

module Thermoprint.Server.API
       ( ProtoHandler, Handler
       , thermoprintServer
       , handlerNat
       ) where

import Thermoprint.API hiding (JobId(..), DraftId(..))
import qualified Thermoprint.API as API (JobId(..), DraftId(..))

import Thermoprint.Server.Printer
import Thermoprint.Server.Database

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 Servant
import Servant.Server
import Servant.Server.Internal.Enter

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

import Control.Concurrent.STM

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

import Data.Traversable (mapM)

import Database.Persist
import Database.Persist.Sql

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

-- ^ Runtime configuration of our handlers
data HandlerInput = HandlerInput { sqlPool  :: ConnectionPool -- ^ How to interact with 'persistent' storage
                                 , printers :: Map PrinterId Printer
                                 }

handlerNat :: ( MonadReader ConnectionPool m
              , MonadLoggerIO m
              ) => Map PrinterId Printer -> m (Handler :~> EitherT ServantErr IO)
-- ^ Servant requires its handlers to be 'EitherT ServantErr IO'
--
-- This generates a 'Nat'ural transformation for squashing the monad-transformer-stack we use in our handlers to the monad 'servant-server' wants
handlerNat printerMap = do
  sqlPool <- ask
  logFunc <- askLoggerIO
  let
    handlerInput = HandlerInput
      { sqlPool  = sqlPool
      , printers = printerMap
      }
    protoNat :: ProtoHandler :~> IO
    protoNat = Nat runResourceT . Nat (($ logFunc) . runLoggingT) . runReaderTNat handlerInput
  return $ hoistNat protoNat

thermoprintServer :: ServerT ThermoprintAPI Handler
-- ^ A 'servant-server' for 'ThermoprintAPI'
thermoprintServer = listPrinters
                     :<|> (listJobs :<|> queueJob)
                     :<|> getJob <||> jobStatus <||> deleteJob
                     :<|> (listDrafts :<|> addDraft)
                     :<|> updateDraft <||> getDraft <||> deleteDraft <||> printDraft
  where
    --     :: (a -> b) -> (a -> c) -> (a -> b :<|> c)
    (<||>) :: Monad m => m a -> m b -> m (a :<|> b)
    (<||>) = liftM2 (:<|>)
    infixr 9 <||>

lookupPrinter :: Maybe PrinterId -> Handler Printer
lookupPrinter pId = asks printers >>= maybePrinter' pId
  where
    maybePrinter' Nothing printerMap
      | Map.null printerMap = left $ err501 { errBody = "No printers available" }
      | otherwise = return . snd $ Map.findMin printerMap
    maybePrinter (Just pId) printerMap
      | Just printer <- Map.lookup pId printerMap = return printer
      | otherwise = left $ err404 { errBody = "No such printer" }

listPrinters :: Handler (Map PrinterId PrinterStatus)
listPrinters = fmap toStatus <$> (mapM (liftIO . readTVarIO . queue) . printers =<< ask)
  where
    toStatus (Queue _ Nothing   _) = Available
    toStatus (Queue _ (Just id) _) = Busy . castId $ fromSqlKey id

queueJob :: Maybe PrinterId -> Printout -> Handler API.JobId
queueJob pId printout = lift . fmap (castId' . unJobKey) . withReaderT sqlPool . addToQueue printout =<< lookupPrinter pId

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