diff options
Diffstat (limited to 'server/src')
| -rw-r--r-- | server/src/Thermoprint/Server.hs | 65 | ||||
| -rw-r--r-- | server/src/Thermoprint/Server/Database.hs | 24 | 
2 files changed, 50 insertions, 39 deletions
| diff --git a/server/src/Thermoprint/Server.hs b/server/src/Thermoprint/Server.hs index 0918e83..d1ee6ee 100644 --- a/server/src/Thermoprint/Server.hs +++ b/server/src/Thermoprint/Server.hs | |||
| @@ -1,15 +1,8 @@ | |||
| 1 | {-# LANGUAGE RecordWildCards #-} | 1 | {-# LANGUAGE RecordWildCards #-} | 
| 2 | {-# LANGUAGE EmptyDataDecls #-} | 2 | {-# LANGUAGE TemplateHaskell #-} | 
| 3 | {-# LANGUAGE FlexibleContexts #-} | 3 | {-# LANGUAGE OverloadedStrings #-} | 
| 4 | {-# LANGUAGE GADTs #-} | 4 | {-# LANGUAGE TypeOperators #-} | 
| 5 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | 5 | {-# LANGUAGE FlexibleContexts #-} | 
| 6 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
| 7 | {-# LANGUAGE OverloadedStrings #-} | ||
| 8 | {-# LANGUAGE QuasiQuotes #-} | ||
| 9 | {-# LANGUAGE TemplateHaskell #-} | ||
| 10 | {-# LANGUAGE TypeFamilies #-} | ||
| 11 | {-# LANGUAGE OverloadedStrings #-} | ||
| 12 | {-# LANGUAGE TypeOperators #-} | ||
| 13 | 6 | ||
| 14 | module Thermoprint.Server | 7 | module Thermoprint.Server | 
| 15 | ( thermoprintServer | 8 | ( thermoprintServer | 
| @@ -28,6 +21,8 @@ import Control.Monad ((<=<), mapM_, liftM2) | |||
| 28 | import Prelude hiding ((.), id) | 21 | import Prelude hiding ((.), id) | 
| 29 | import Control.Category | 22 | import Control.Category | 
| 30 | 23 | ||
| 24 | import Data.Maybe (maybe) | ||
| 25 | |||
| 31 | import Control.Monad.Logger | 26 | import Control.Monad.Logger | 
| 32 | import Control.Monad.Reader | 27 | import Control.Monad.Reader | 
| 33 | import Control.Monad.Trans.Resource | 28 | import Control.Monad.Trans.Resource | 
| @@ -45,6 +40,9 @@ import qualified Data.Sequence as Seq | |||
| 45 | import Data.Map (Map) | 40 | import Data.Map (Map) | 
| 46 | import qualified Data.Map as Map | 41 | import qualified Data.Map as Map | 
| 47 | 42 | ||
| 43 | import Data.Text (Text) | ||
| 44 | import qualified Data.Text as T (pack) | ||
| 45 | |||
| 48 | import qualified Network.Wai.Handler.Warp as Warp | 46 | import qualified Network.Wai.Handler.Warp as Warp | 
| 49 | import Network.Wai (Application) | 47 | import Network.Wai (Application) | 
| 50 | 48 | ||
| @@ -52,12 +50,13 @@ import Servant | |||
| 52 | import Servant.Server | 50 | import Servant.Server | 
| 53 | import Servant.Server.Internal.Enter | 51 | import Servant.Server.Internal.Enter | 
| 54 | 52 | ||
| 55 | import Database.Persist | 53 | import Database.Persist.Sql (runMigrationSilent, ConnectionPool, runSqlPool) | 
| 56 | import Database.Persist.Sql | 54 | |
| 57 | import Database.Persist.TH | ||
| 58 | 55 | ||
| 59 | data Config = Config { dyreError :: Maybe String | 56 | import Thermoprint.Server.Database | 
| 60 | , warpSettings :: Warp.Settings | 57 | |
| 58 | data Config = Config { dyreError :: Maybe String -- ^ Set by 'Dyre' -- sent to log as an error | ||
| 59 | , warpSettings :: Warp.Settings -- ^ Configure 'Warp's behaviour | ||
| 61 | } | 60 | } | 
| 62 | 61 | ||
| 63 | instance Default Config where | 62 | instance Default Config where | 
| @@ -69,48 +68,36 @@ data HandlerInput = HandlerInput { sqlPool :: ConnectionPool | |||
| 69 | } | 68 | } | 
| 70 | 69 | ||
| 71 | 70 | ||
| 72 | share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| | ||
| 73 | Job | ||
| 74 | content Printout | ||
| 75 | Draft | ||
| 76 | title DraftTitle Maybe | ||
| 77 | content Printout | ||
| 78 | |] | ||
| 79 | |||
| 80 | |||
| 81 | thermoprintServer :: ( MonadLoggerIO m | 71 | thermoprintServer :: ( MonadLoggerIO m | 
| 82 | , MonadIO m | 72 | , MonadIO m | 
| 83 | , MonadBaseControl IO m | 73 | , MonadBaseControl IO m | 
| 84 | , MonadReader ConnectionPool m | 74 | , MonadReader ConnectionPool m | 
| 85 | ) => (m :~> IO) -> Config -> IO () | 75 | ) => (m :~> IO) -> Config -> IO () | 
| 76 | -- ^ Run the server | ||
| 86 | thermoprintServer io = Dyre.wrapMain $ Dyre.defaultParams | 77 | thermoprintServer io = Dyre.wrapMain $ Dyre.defaultParams | 
| 87 | { Dyre.projectName = "thermoprint-server" | 78 | { Dyre.projectName = "thermoprint-server" | 
| 88 | , Dyre.realMain = realMain <=< handleDyreErrors | 79 | , Dyre.realMain = realMain | 
| 89 | , Dyre.showError = (\cfg msg -> cfg { dyreError = Just msg }) | 80 | , Dyre.showError = (\cfg msg -> cfg { dyreError = Just msg }) | 
| 90 | } | 81 | } | 
| 91 | where | 82 | where | 
| 92 | handleDyreErrors cfg@(Config{..}) | 83 | realMain Config{..} = unNat io $ do | 
| 93 | | Just msg <- dyreError = do | 84 | maybe (return ()) ($(logErrorS) "Dyre" . T.pack) dyreError | 
| 94 | hPutStrLn stderr msg | 85 | |
| 95 | exitFailure | ||
| 96 | undefined | ||
| 97 | | otherwise = return cfg | ||
| 98 | |||
| 99 | realMain (Config{..}) = enter io $ do | ||
| 100 | sqlPool <- ask | 86 | sqlPool <- ask | 
| 101 | runSqlPool (runMigrationSilent migrateAll) sqlPool >>= mapM_ ($(logWarnS) "DB") | ||
| 102 | |||
| 103 | logFunc <- askLoggerIO | 87 | logFunc <- askLoggerIO | 
| 88 | |||
| 89 | runSqlPool (runMigrationSilent migrateAll) sqlPool >>= mapM_ ($(logWarnS) "DB") | ||
| 104 | 90 | ||
| 105 | let | 91 | let | 
| 106 | handlerInput = HandlerInput | 92 | handlerInput = HandlerInput | 
| 107 | { sqlPool = sqlPool | 93 | { sqlPool = sqlPool | 
| 108 | } | 94 | } | 
| 109 | io' :: ReaderT HandlerInput (LoggingT IO) :~> IO | 95 | io' :: ProtoHandler :~> IO | 
| 110 | io' = Nat (($ logFunc) . runLoggingT) . runReaderTNat handlerInput | 96 | io' = Nat (($ logFunc) . runLoggingT) . runReaderTNat handlerInput | 
| 111 | liftIO . Warp.runSettings warpSettings . serve thermoprintAPI $ enter (hoistNat io') thermoprintServer' | 97 | liftIO . Warp.runSettings warpSettings . serve thermoprintAPI $ enter (hoistNat io') thermoprintServer' | 
| 112 | 98 | ||
| 113 | type Handler = EitherT ServantErr (ReaderT HandlerInput (LoggingT IO)) | 99 | type ProtoHandler = ReaderT HandlerInput (LoggingT IO) | 
| 100 | type Handler = EitherT ServantErr ProtoHandler | ||
| 114 | 101 | ||
| 115 | (<||>) :: Monad m => m a -> m b -> m (a :<|> b) | 102 | (<||>) :: Monad m => m a -> m b -> m (a :<|> b) | 
| 116 | (<||>) = liftM2 (:<|>) | 103 | (<||>) = liftM2 (:<|>) | 
| diff --git a/server/src/Thermoprint/Server/Database.hs b/server/src/Thermoprint/Server/Database.hs new file mode 100644 index 0000000..61179e6 --- /dev/null +++ b/server/src/Thermoprint/Server/Database.hs | |||
| @@ -0,0 +1,24 @@ | |||
| 1 | {-# LANGUAGE TemplateHaskell #-} | ||
| 2 | {-# LANGUAGE QuasiQuotes #-} | ||
| 3 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
| 4 | {-# LANGUAGE TypeFamilies #-} | ||
| 5 | {-# LANGUAGE ExistentialQuantification #-} | ||
| 6 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
| 7 | |||
| 8 | module Thermoprint.Server.Database | ||
| 9 | ( Job(..), JobId | ||
| 10 | , Draft(..), DraftId | ||
| 11 | , migrateAll | ||
| 12 | ) where | ||
| 13 | |||
| 14 | import Thermoprint.API (Printout, DraftTitle) | ||
| 15 | |||
| 16 | import Database.Persist.TH | ||
| 17 | |||
| 18 | share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| | ||
| 19 | Job | ||
| 20 | content Printout | ||
| 21 | Draft | ||
| 22 | title DraftTitle Maybe | ||
| 23 | content Printout | ||
| 24 | |] | ||
