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

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

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

import Data.Map (Map)
import qualified Data.Map as Map

import Data.Maybe (maybe)
import Data.Foldable (mapM_, forM_, foldlM)
import Data.Monoid

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

import Control.Monad.Writer

import Control.Concurrent
       
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.Server (serve)
import Servant.Server.Internal.Enter (enter, (:~>)(..))

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


import Thermoprint.API (thermoprintAPI, PrinterId)

import Thermoprint.Server.Database
import Thermoprint.Server.Printer
import qualified Thermoprint.Server.API as API (thermoprintServer)
import Thermoprint.Server.API hiding (thermoprintServer)

-- | Compile-time configuration for 'thermoprintServer'
data Config = Config { dyreError    :: Maybe String -- ^ Set by 'Dyre' -- sent to log as an error
                     , warpSettings :: Warp.Settings -- ^ Configure 'Warp's behaviour
                     , printers     :: Map PrinterId Printer
                     }

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


thermoprintServer :: ( MonadLoggerIO m
                     , MonadReader ConnectionPool m
                     , MonadResource m
                     , MonadBaseControl IO m
                     ) => (m :~> IO) -- ^ 'dyre' controls the base of the monad-transformer-stack ('IO') but we let the user specify the rest of it. Therefore we require a specification of how to enter the stack.
                     -> 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
        mapM_ ($(logWarnS) "DB") =<< runSqlPool (runMigrationSilent migrateAll) =<< ask
        forM_ printers $ liftBaseDiscard forkIO . runPrinter
        liftIO . Warp.runSettings warpSettings . serve thermoprintAPI . flip enter API.thermoprintServer =<< handlerNat printers

withPrinters :: MonadResource m => Config -> [PrinterSpec] -> m Config
-- ^ Helper for comfortably specifying a set of 'Printer's
withPrinters cfg = fmap (\ps -> cfg { printers = printers cfg <> ps }) . foldlM (\ps p -> Map.insert (nextKey ps) <$> printer p <*> pure ps) Map.empty
  where
    nextKey :: Map PrinterId a -> PrinterId
    nextKey (Map.keys -> keys)
      | null keys = 0
      | otherwise = succ $ maximum keys