aboutsummaryrefslogtreecommitdiff
path: root/servant/src/Main.hs
diff options
context:
space:
mode:
Diffstat (limited to 'servant/src/Main.hs')
-rw-r--r--servant/src/Main.hs105
1 files changed, 96 insertions, 9 deletions
diff --git a/servant/src/Main.hs b/servant/src/Main.hs
index 9d88559..0aa9eeb 100644
--- a/servant/src/Main.hs
+++ b/servant/src/Main.hs
@@ -1,27 +1,59 @@
1{-# LANGUAGE RecordWildCards, OverloadedStrings #-} 1{-# LANGUAGE RecordWildCards, OverloadedStrings #-}
2{-# LANGUAGE EmptyDataDecls #-}
3{-# LANGUAGE FlexibleContexts #-}
4{-# LANGUAGE GADTs #-}
5{-# LANGUAGE GeneralizedNewtypeDeriving #-}
6{-# LANGUAGE MultiParamTypeClasses #-}
7{-# LANGUAGE QuasiQuotes #-}
8{-# LANGUAGE TemplateHaskell #-}
9{-# LANGUAGE TypeFamilies #-}
2 10
3import Thermoprint 11import Thermoprint
4import Thermoprint.Api 12import Thermoprint.Api
13import PrintOut
5 14
15import qualified Data.Text.Lazy as TL
16import qualified Data.ByteString.Lazy.Char8 as LBS
17import qualified Data.ByteString.Lazy.Char8 as Lazy (ByteString)
18import qualified Data.Text as T (pack)
19import Data.ByteString (ByteString)
20import qualified Data.ByteString as BS
21
6import Data.Aeson 22import Data.Aeson
7import Network.Wai 23import Network.Wai
8import Network.Wai.Handler.Warp 24import Network.Wai.Handler.Warp
9import Servant 25import Servant
10import qualified Data.Text.Lazy as Text
11import qualified Data.ByteString.Lazy.Char8 as ByteString
12import Data.ByteString.Lazy.Char8 (ByteString)
13import GHC.Generics 26import GHC.Generics
14 27
15import Control.Monad 28import Control.Monad
29import Control.Monad.Trans.Class
16import Control.Monad.IO.Class 30import Control.Monad.IO.Class
17import Control.Monad.Trans.Either 31import Control.Monad.Trans.Either
18 32
33import Control.Monad.Logger
34
19import Options.Applicative 35import Options.Applicative
20 36
21import System.IO 37import System.IO hiding (print)
38
39import Database.Persist
40import Database.Persist.Sqlite
41import Database.Persist.TH
42
43import Data.Int (Int64)
44
45import Prelude hiding (print)
46
47share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
48Draft
49 title String
50 content PrintOut
51 deriving Show
52|]
53
22 54
23server :: Options -> Integer -> Block String -> EitherT ServantErr IO () 55print :: Options -> Integer -> Block String -> EitherT ServantErr IO ()
24server Options{..} printerNo printOut = do 56print Options{..} printerNo printOut = do
25 printerPath <- case genericIndex printers printerNo of 57 printerPath <- case genericIndex printers printerNo of
26 Just path -> return path 58 Just path -> return path
27 Nothing -> left $ err404 { errBody = "printerId out of bounds" } 59 Nothing -> left $ err404 { errBody = "printerId out of bounds" }
@@ -29,7 +61,7 @@ server Options{..} printerNo printOut = do
29 where 61 where
30 doPrint handle = do 62 doPrint handle = do
31 hSetBuffering handle NoBuffering 63 hSetBuffering handle NoBuffering
32 ByteString.hPut handle $ render' printOut 64 LBS.hPut handle $ render' printOut
33 genericIndex :: Integral i => [a] -> i -> Maybe a 65 genericIndex :: Integral i => [a] -> i -> Maybe a
34 genericIndex (x:_) 0 = Just x 66 genericIndex (x:_) 0 = Just x
35 genericIndex (_:xs) n 67 genericIndex (_:xs) n
@@ -37,11 +69,47 @@ server Options{..} printerNo printOut = do
37 | otherwise = Nothing 69 | otherwise = Nothing
38 genericIndex _ _ = Nothing 70 genericIndex _ _ = Nothing
39 71
72withPool = flip runSqlPool
73
74queryDrafts :: Options -> ConnectionPool -> EitherT ServantErr IO [(Int64, String)]
75queryDrafts Options{..} cPool = withPool cPool $ do
76 drafts <- selectList [] []
77 return $ map deSQLify drafts
78 where
79 deSQLify :: Entity Draft -> (Int64, String)
80 deSQLify (Entity k (Draft title _)) = (fromSqlKey k, title)
81
82getDraft :: Options -> ConnectionPool -> Int64 -> EitherT ServantErr IO (String, Block String)
83getDraft Options{..} cPool draftId = withPool cPool $ do
84 draft <- get $ toSqlKey draftId
85 case draft of
86 Nothing -> lift $ left $ err404 { errBody = "no such draftId" }
87 Just (Draft title content) -> return (title, content)
88
89writeDraft :: Options -> ConnectionPool -> Int64 -> (String, Block String) -> EitherT ServantErr IO ()
90writeDraft Options{..} cPool draftId (draftName, draft) = withPool cPool $ repsert (toSqlKey draftId) (Draft draftName draft)
91
92addDraft :: Options -> ConnectionPool -> (String, Block String) -> EitherT ServantErr IO Int64
93addDraft Options{..} cPool (draftName, draft) = withPool cPool $ (fromSqlKey <$> insert (Draft draftName draft))
94
95delDraft :: Options -> ConnectionPool -> Int64 -> EitherT ServantErr IO ()
96delDraft Options{..} cPool draftId = withPool cPool $ delete (toSqlKey draftId :: Key Draft)
97
40data Options = Options 98data Options = Options
41 { port :: Int 99 { port :: Int
100 , connStr :: String
101 , connNmbr :: Int
42 , printers :: [FilePath] 102 , printers :: [FilePath]
43 } 103 }
44 104
105server :: Options -> ConnectionPool -> Server ThermoprintApi
106server opts cPool = print opts
107 :<|> queryDrafts opts cPool
108 :<|> addDraft opts cPool
109 :<|> getDraft opts cPool
110 :<|> writeDraft opts cPool
111 :<|> delDraft opts cPool
112
45options :: Parser Options 113options :: Parser Options
46options = Options 114options = Options
47 <$> option auto ( 115 <$> option auto (
@@ -52,6 +120,21 @@ options = Options
52 <> value 8080 120 <> value 8080
53 <> showDefault 121 <> showDefault
54 ) 122 )
123 <*> strOption (
124 long "database"
125 <> short 'd'
126 <> metavar "STRING"
127 <> help "The sqlite connection string to use (can inlude some options)"
128 <> value "./storage.sqlite"
129 <> showDefault
130 )
131 <*> option auto (
132 long "database-connections"
133 <> metavar "INT"
134 <> help "The number of parallel sqlite connections to maintain"
135 <> value 2
136 <> showDefault
137 )
55 <*> some (strArgument ( 138 <*> some (strArgument (
56 metavar "PATH [...]" 139 metavar "PATH [...]"
57 <> help "Path to one of the printers to use" 140 <> help "Path to one of the printers to use"
@@ -62,10 +145,14 @@ thermoprintApi = Proxy
62 145
63main :: IO () 146main :: IO ()
64main = do 147main = do
65 execParser opts >>= main' 148 execParser opts >>= runNoLoggingT . main'
66 where 149 where
67 opts = info (helper <*> options) ( 150 opts = info (helper <*> options) (
68 fullDesc 151 fullDesc
69 <> header "thermoprint-servant - A REST server for interacting with a cheap thermoprinter" 152 <> header "thermoprint-servant - A REST server for interacting with a cheap thermoprinter"
70 ) 153 )
71 main' args@(Options{..}) = run port $ serve thermoprintApi (server args) 154 main' args@(Options{..}) = withSqlitePool (T.pack connStr) connNmbr $ main''
155 where
156 main'' cPool = do
157 runSqlPool (runMigration migrateAll) cPool
158 liftIO $ run port $ serve thermoprintApi (server args cPool)