{-# 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 Control.Monad (mapM_) import Data.Maybe (maybe) import Control.Monad.Trans.Resource import Control.Monad.Logger import Control.Monad.Reader import Control.Monad.IO.Class 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) import Thermoprint.Server.Database 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 } instance Default Config where def = Config { dyreError = Nothing , warpSettings = Warp.defaultSettings } thermoprintServer :: ( MonadLoggerIO m , MonadIO m , MonadBaseControl IO m , MonadReader ConnectionPool 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 liftIO . Warp.runSettings warpSettings . serve thermoprintAPI . flip enter API.thermoprintServer =<< handlerNat