{-# LANGUAGE TypeOperators #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TemplateHaskell #-} 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 (Printer(..), Queue(..)) 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.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 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 (($ 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 <||> 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 = 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