aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2016-01-24 16:10:48 +0000
committerGregor Kleen <gkleen@yggdrasil.li>2016-01-24 16:10:48 +0000
commitc3a6d0657eb2987aa13b53419269274d848d9e0c (patch)
treefcf161b74fffad2294efc0b558a0dfd1bc27d49b
parent7d3df6adce65e8840ef651a8a02a34a1a02083aa (diff)
downloadthermoprint-c3a6d0657eb2987aa13b53419269274d848d9e0c.tar
thermoprint-c3a6d0657eb2987aa13b53419269274d848d9e0c.tar.gz
thermoprint-c3a6d0657eb2987aa13b53419269274d848d9e0c.tar.bz2
thermoprint-c3a6d0657eb2987aa13b53419269274d848d9e0c.tar.xz
thermoprint-c3a6d0657eb2987aa13b53419269274d848d9e0c.zip
Working printer config & debug printer
-rw-r--r--server/default-conf/Main.hs14
-rw-r--r--server/src/Thermoprint/Server.hs35
-rw-r--r--server/src/Thermoprint/Server/API.hs27
-rw-r--r--server/src/Thermoprint/Server/Database.hs11
-rw-r--r--server/src/Thermoprint/Server/Printer.hs51
-rw-r--r--server/src/Thermoprint/Server/Printer/Debug.hs39
-rw-r--r--server/thermoprint-server.cabal1
7 files changed, 145 insertions, 33 deletions
diff --git a/server/default-conf/Main.hs b/server/default-conf/Main.hs
index 0aa7d91..0fba774 100644
--- a/server/default-conf/Main.hs
+++ b/server/default-conf/Main.hs
@@ -1,9 +1,12 @@
1{-# LANGUAGE OverloadedStrings #-} 1{-# LANGUAGE OverloadedStrings #-}
2{-# LANGUAGE ImpredicativeTypes #-}
2 3
3module Main (main) where 4module Main (main) where
4 5
5import Thermoprint.Server 6import Thermoprint.Server
6 7
8import Thermoprint.Server.Printer.Debug
9
7import Control.Monad.Trans.Resource 10import Control.Monad.Trans.Resource
8import Control.Monad.Logger 11import Control.Monad.Logger
9import Control.Monad.Reader 12import Control.Monad.Reader
@@ -11,7 +14,10 @@ import Control.Monad.Reader
11import Database.Persist.Sqlite 14import Database.Persist.Sqlite
12 15
13main :: IO () 16main :: IO ()
14main = thermoprintServer (Nat runSqlite) def 17main = thermoprintServer (Nat runSqlite) $ def `withPrinters` printers
15 where 18 where
16 runSqlite :: ReaderT ConnectionPool (LoggingT (ResourceT IO)) a -> IO a 19 runSqlite :: ReaderT ConnectionPool (LoggingT IO) a -> IO a
17 runSqlite = runResourceT . runStderrLoggingT . withSqlitePool ":memory:" 1 . runReaderT 20 runSqlite = runStderrLoggingT . withSqlitePool ":memory:" 1 . runReaderT
21
22 printers = [ PS Debug
23 ]
diff --git a/server/src/Thermoprint/Server.hs b/server/src/Thermoprint/Server.hs
index 39bf0a1..ed20983 100644
--- a/server/src/Thermoprint/Server.hs
+++ b/server/src/Thermoprint/Server.hs
@@ -1,12 +1,14 @@
1{-# LANGUAGE RecordWildCards #-} 1{-# LANGUAGE RecordWildCards #-}
2{-# LANGUAGE TemplateHaskell #-} 2{-# LANGUAGE TemplateHaskell #-}
3{-# LANGUAGE OverloadedStrings #-} 3{-# LANGUAGE OverloadedStrings #-}
4{-# LANGUAGE TypeOperators #-} 4{-# LANGUAGE TypeOperators #-}
5{-# LANGUAGE FlexibleContexts #-} 5{-# LANGUAGE FlexibleContexts #-}
6{-# LANGUAGE ImpredicativeTypes #-}
6 7
7module Thermoprint.Server 8module Thermoprint.Server
8 ( thermoprintServer 9 ( thermoprintServer
9 , Config(..) 10 , Config(..)
11 , withPrinters
10 , module Data.Default.Class 12 , module Data.Default.Class
11 , module Servant.Server.Internal.Enter 13 , module Servant.Server.Internal.Enter
12 , module Thermoprint.Server.Printer 14 , module Thermoprint.Server.Printer
@@ -19,13 +21,15 @@ import Data.Map (Map)
19import qualified Data.Map as Map 21import qualified Data.Map as Map
20 22
21import Data.Maybe (maybe) 23import Data.Maybe (maybe)
22import Data.Foldable (mapM_, forM_) 24import Data.Foldable (mapM_, forM_, foldlM)
23 25
24import Control.Monad.Trans.Resource 26import Control.Monad.Trans.Resource
25import Control.Monad.Trans.Control 27import Control.Monad.Trans.Control
26import Control.Monad.Logger 28import Control.Monad.Logger
27import Control.Monad.Reader 29import Control.Monad.Reader
28import Control.Monad.IO.Class 30import Control.Monad.IO.Class
31import Control.Category
32import Prelude hiding (id, (.))
29 33
30import Control.Concurrent 34import Control.Concurrent
31 35
@@ -62,20 +66,27 @@ instance Default Config where
62 66
63 67
64thermoprintServer :: ( MonadLoggerIO m 68thermoprintServer :: ( MonadLoggerIO m
65 , MonadIO m
66 , MonadBaseControl IO m
67 , MonadReader ConnectionPool m 69 , MonadReader ConnectionPool m
70 , MonadResourceBase m
68 ) => (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. 71 ) => (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.
69 -> Config -> IO () 72 -> ResourceT m Config -> IO ()
70-- ^ Run the server 73-- ^ Run the server
71thermoprintServer io = Dyre.wrapMain $ Dyre.defaultParams 74thermoprintServer io = Dyre.wrapMain $ Dyre.defaultParams
72 { Dyre.projectName = "thermoprint-server" 75 { Dyre.projectName = "thermoprint-server"
73 , Dyre.realMain = realMain 76 , Dyre.realMain = realMain
74 , Dyre.showError = (\cfg msg -> cfg { dyreError = Just msg }) 77 , Dyre.showError = flip (\msg -> fmap (\cfg -> cfg { dyreError = Just msg }))
75 } 78 }
76 where 79 where
77 realMain Config{..} = unNat io $ do 80 realMain cfg = unNat (io . Nat runResourceT) $ do
81 Config{..} <- cfg
78 maybe (return ()) ($(logErrorS) "Dyre" . T.pack) dyreError 82 maybe (return ()) ($(logErrorS) "Dyre" . T.pack) dyreError
79 mapM_ ($(logWarnS) "DB") =<< runSqlPool (runMigrationSilent migrateAll) =<< ask 83 mapM_ ($(logWarnS) "DB") =<< runSqlPool (runMigrationSilent migrateAll) =<< ask
80 forM_ printers $ liftBaseDiscard forkIO . runPrinter 84 forM_ printers $ resourceForkIO . runPrinter
81 liftIO . Warp.runSettings warpSettings . serve thermoprintAPI . flip enter API.thermoprintServer =<< handlerNat printers 85 liftIO . Warp.runSettings warpSettings . serve thermoprintAPI . flip enter API.thermoprintServer =<< handlerNat printers
86
87withPrinters :: MonadResource m => Config -> [PrinterSpec m] -> m Config
88withPrinters cfg pss = (\map -> cfg { printers = map }) <$> foldlM (\map spec -> Map.insert (nextKey map) <$> printer spec <*> pure map) Map.empty pss
89 where
90 nextKey map
91 | Map.null map = 0
92 | otherwise = succ . fst $ Map.findMin map
diff --git a/server/src/Thermoprint/Server/API.hs b/server/src/Thermoprint/Server/API.hs
index 6a92caf..a1efb8f 100644
--- a/server/src/Thermoprint/Server/API.hs
+++ b/server/src/Thermoprint/Server/API.hs
@@ -1,6 +1,7 @@
1{-# LANGUAGE TypeOperators #-} 1{-# LANGUAGE TypeOperators #-}
2{-# LANGUAGE FlexibleContexts #-} 2{-# LANGUAGE FlexibleContexts #-}
3{-# LANGUAGE TemplateHaskell #-} 3{-# LANGUAGE TemplateHaskell #-}
4{-# LANGUAGE OverloadedStrings #-}
4 5
5module Thermoprint.Server.API 6module Thermoprint.Server.API
6 ( ProtoHandler, Handler 7 ( ProtoHandler, Handler
@@ -11,7 +12,8 @@ module Thermoprint.Server.API
11import Thermoprint.API hiding (JobId(..), DraftId(..)) 12import Thermoprint.API hiding (JobId(..), DraftId(..))
12import qualified Thermoprint.API as API (JobId(..), DraftId(..)) 13import qualified Thermoprint.API as API (JobId(..), DraftId(..))
13 14
14import Thermoprint.Server.Printer (Printer(..), Queue(..)) 15import Thermoprint.Server.Printer
16import Thermoprint.Server.Database
15 17
16import Data.Set (Set) 18import Data.Set (Set)
17import qualified Data.Set as Set 19import qualified Data.Set as Set
@@ -26,6 +28,7 @@ import Servant.Server.Internal.Enter
26 28
27import Control.Monad.Logger 29import Control.Monad.Logger
28import Control.Monad.Reader 30import Control.Monad.Reader
31import Control.Monad.Trans.Resource
29import Control.Monad.Trans.Either 32import Control.Monad.Trans.Either
30import Control.Monad.IO.Class 33import Control.Monad.IO.Class
31 34
@@ -40,7 +43,7 @@ import Data.Traversable (mapM)
40import Database.Persist 43import Database.Persist
41import Database.Persist.Sql 44import Database.Persist.Sql
42 45
43type ProtoHandler = ReaderT HandlerInput (LoggingT IO) 46type ProtoHandler = ReaderT HandlerInput (LoggingT (ResourceT IO))
44type Handler = EitherT ServantErr ProtoHandler 47type Handler = EitherT ServantErr ProtoHandler
45 48
46-- ^ Runtime configuration of our handlers 49-- ^ Runtime configuration of our handlers
@@ -63,7 +66,7 @@ handlerNat printerMap = do
63 , printers = printerMap 66 , printers = printerMap
64 } 67 }
65 protoNat :: ProtoHandler :~> IO 68 protoNat :: ProtoHandler :~> IO
66 protoNat = Nat (($ logFunc) . runLoggingT) . runReaderTNat handlerInput 69 protoNat = Nat runResourceT . Nat (($ logFunc) . runLoggingT) . runReaderTNat handlerInput
67 return $ hoistNat protoNat 70 return $ hoistNat protoNat
68 71
69thermoprintServer :: ServerT ThermoprintAPI Handler 72thermoprintServer :: ServerT ThermoprintAPI Handler
@@ -79,6 +82,16 @@ thermoprintServer = listPrinters
79 (<||>) = liftM2 (:<|>) 82 (<||>) = liftM2 (:<|>)
80 infixr 9 <||> 83 infixr 9 <||>
81 84
85lookupPrinter :: Maybe PrinterId -> Handler Printer
86lookupPrinter pId = asks printers >>= maybePrinter' pId
87 where
88 maybePrinter' Nothing printerMap
89 | Map.null printerMap = left $ err501 { errBody = "No printers available" }
90 | otherwise = return . snd $ Map.findMin printerMap
91 maybePrinter (Just pId) printerMap
92 | Just printer <- Map.lookup pId printerMap = return printer
93 | otherwise = left $ err404 { errBody = "No such printer" }
94
82listPrinters :: Handler (Map PrinterId PrinterStatus) 95listPrinters :: Handler (Map PrinterId PrinterStatus)
83listPrinters = fmap toStatus <$> (mapM (liftIO . readTVarIO . queue) . printers =<< ask) 96listPrinters = fmap toStatus <$> (mapM (liftIO . readTVarIO . queue) . printers =<< ask)
84 where 97 where
@@ -86,7 +99,7 @@ listPrinters = fmap toStatus <$> (mapM (liftIO . readTVarIO . queue) . printers
86 toStatus (Queue _ (Just id) _) = Busy . castId $ fromSqlKey id 99 toStatus (Queue _ (Just id) _) = Busy . castId $ fromSqlKey id
87 100
88queueJob :: Maybe PrinterId -> Printout -> Handler API.JobId 101queueJob :: Maybe PrinterId -> Printout -> Handler API.JobId
89queueJob = return undefined 102queueJob pId printout = lift . fmap (castId' . unJobKey) . withReaderT sqlPool . addToQueue printout =<< lookupPrinter pId
90 103
91printerStatus :: PrinterId -> Handler PrinterStatus 104printerStatus :: PrinterId -> Handler PrinterStatus
92printerStatus = return undefined 105printerStatus = return undefined
diff --git a/server/src/Thermoprint/Server/Database.hs b/server/src/Thermoprint/Server/Database.hs
index 29732e1..1e01680 100644
--- a/server/src/Thermoprint/Server/Database.hs
+++ b/server/src/Thermoprint/Server/Database.hs
@@ -9,16 +9,18 @@
9module Thermoprint.Server.Database 9module Thermoprint.Server.Database
10 ( Job(..), JobId 10 ( Job(..), JobId
11 , Draft(..), DraftId 11 , Draft(..), DraftId
12 , Key(..)
12 , migrateAll 13 , migrateAll
14 , castId'
13 ) where 15 ) where
14 16
15import Control.DeepSeq 17import Control.DeepSeq
16 18
17import Thermoprint.API (Printout, DraftTitle, JobStatus) 19import Thermoprint.API (Printout, DraftTitle, JobStatus, castId)
18 20
19import Database.Persist.TH 21import Database.Persist.TH
20import Database.Persist.Sql (unSqlBackendKey) 22import Database.Persist.Sql (unSqlBackendKey, SqlBackend)
21import Database.Persist.Class (Key) 23import Database.Persist.Class (Key, BackendKey)
22 24
23import Thermoprint.Server.Database.Instances 25import Thermoprint.Server.Database.Instances
24 26
@@ -32,3 +34,6 @@ Draft
32 34
33instance NFData (Key Job) where 35instance NFData (Key Job) where
34 rnf = rnf . unSqlBackendKey . unJobKey 36 rnf = rnf . unSqlBackendKey . unJobKey
37
38castId' :: Enum b => BackendKey SqlBackend -> b
39castId' = castId . unSqlBackendKey
diff --git a/server/src/Thermoprint/Server/Printer.hs b/server/src/Thermoprint/Server/Printer.hs
index f34b2fa..46b8a53 100644
--- a/server/src/Thermoprint/Server/Printer.hs
+++ b/server/src/Thermoprint/Server/Printer.hs
@@ -1,16 +1,21 @@
1{-# LANGUAGE RankNTypes #-} 1{-# LANGUAGE RankNTypes #-}
2{-# LANGUAGE TypeSynonymInstances #-}
2{-# LANGUAGE MultiParamTypeClasses #-} 3{-# LANGUAGE MultiParamTypeClasses #-}
4{-# LANGUAGE FlexibleInstances #-}
3{-# LANGUAGE FlexibleContexts #-} 5{-# LANGUAGE FlexibleContexts #-}
4{-# LANGUAGE RecordWildCards #-} 6{-# LANGUAGE RecordWildCards #-}
5{-# LANGUAGE OverloadedStrings #-} 7{-# LANGUAGE OverloadedStrings #-}
6{-# LANGUAGE TemplateHaskell #-} 8{-# LANGUAGE TemplateHaskell #-}
7{-# LANGUAGE StandaloneDeriving #-} 9{-# LANGUAGE StandaloneDeriving #-}
10{-# LANGUAGE GADTs #-}
11{-# LANGUAGE ExistentialQuantification #-}
8{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-} 12{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}
9 13
10module Thermoprint.Server.Printer 14module Thermoprint.Server.Printer
11 ( Printer(..), printer 15 ( PrinterMethod(..), PrinterSpec(..), IsPrinter(..), Printer(..), printer
12 , Queue(..) 16 , Queue(..)
13 , runPrinter 17 , runPrinter
18 , addToQueue
14 ) where 19 ) where
15 20
16import Thermoprint.API (PrintingError(..), Printout) 21import Thermoprint.API (PrintingError(..), Printout)
@@ -31,6 +36,7 @@ import qualified Data.Text as T (pack)
31import Data.Typeable (Typeable) 36import Data.Typeable (Typeable)
32import GHC.Generics (Generic) 37import GHC.Generics (Generic)
33import Control.DeepSeq 38import Control.DeepSeq
39import Data.Default.Class
34 40
35import Control.Monad.Trans.Resource 41import Control.Monad.Trans.Resource
36import Control.Monad.IO.Class 42import Control.Monad.IO.Class
@@ -41,8 +47,20 @@ import Control.Monad (forever)
41 47
42import Control.Concurrent.STM 48import Control.Concurrent.STM
43 49
50newtype PrinterMethod = PM { unPM :: forall m. (MonadResource m, MonadLogger m) => Printout -> m (Maybe PrintingError) }
51data PrinterSpec m = forall p. IsPrinter p m => PS p
52
53class IsPrinter p m where
54 printMethod :: p -> m PrinterMethod
55
56instance Applicative m => IsPrinter PrinterMethod m where
57 printMethod = pure
58
59instance IsPrinter (PrinterSpec m) m where
60 printMethod (PS p) = printMethod p
61
44data Printer = Printer 62data Printer = Printer
45 { print :: forall m. (MonadIO m) => Printout -> m (Maybe PrintingError) 63 { print :: PrinterMethod
46 , queue :: TVar Queue 64 , queue :: TVar Queue
47 } 65 }
48 66
@@ -54,16 +72,23 @@ data Queue = Queue
54 } 72 }
55 deriving (Typeable, Generic, NFData) 73 deriving (Typeable, Generic, NFData)
56 74
57printer :: (MonadIO m) => (forall m. (MonadIO m) => Printout -> m (Maybe PrintingError)) -> m Printer 75instance Default Queue where
58printer f = Printer f <$> liftIO (newTVarIO $ Queue Seq.empty Nothing Seq.empty) 76 def = Queue
77 { pending = Seq.empty
78 , current = Nothing
79 , history = Seq.empty
80 }
81
82printer :: (MonadResource m, IsPrinter p m) => p -> m Printer
83printer spec = Printer <$> printMethod spec <*> liftIO (newTVarIO def)
59 84
60atomically' :: MonadIO m => STM a -> m a 85atomically' :: MonadIO m => STM a -> m a
61atomically' = liftIO . atomically 86atomically' = liftIO . atomically
62 87
63runPrinter :: ( MonadReader ConnectionPool m 88runPrinter :: ( MonadReader ConnectionPool m
64 , MonadIO m
65 , MonadLogger m 89 , MonadLogger m
66 , MonadBaseControl IO m 90 , MonadBaseControl IO m
91 , MonadResource m
67 ) => Printer -> m () 92 ) => Printer -> m ()
68-- ^ Loop 'forever' pushing entries from the 'Queue' associated to a 'Printer' into its 'print'-method 93-- ^ Loop 'forever' pushing entries from the 'Queue' associated to a 'Printer' into its 'print'-method
69runPrinter Printer{..} = forever $ do 94runPrinter Printer{..} = forever $ do
@@ -78,6 +103,18 @@ runPrinter Printer{..} = forever $ do
78 case job of 103 case job of
79 Nothing -> $(logWarn) "Nonexistent job id in printer queue" 104 Nothing -> $(logWarn) "Nonexistent job id in printer queue"
80 Just job -> do 105 Just job -> do
81 printReturn <- print (jobContent job) 106 $(logInfo) . T.pack $ "Printing " ++ show (unSqlBackendKey . unJobKey $ jobId)
82 maybe (return ()) ($(logWarn) . T.pack . (("Error while printing " ++ show jobId ++ ": ") ++) . show) $ printReturn 107 printReturn <- (unPM print) (jobContent job)
108 maybe (return ()) ($(logWarn) . T.pack . (("Error while printing " ++ show (unSqlBackendKey . unJobKey $ jobId) ++ ": ") ++) . show) $ printReturn
83 atomically' $ modifyTVar' queue (\Queue{..} -> force . Queue pending Nothing $ (jobId, printReturn) <| history) 109 atomically' $ modifyTVar' queue (\Queue{..} -> force . Queue pending Nothing $ (jobId, printReturn) <| history)
110
111addToQueue :: ( MonadReader ConnectionPool m
112 , MonadLogger m
113 , MonadResource m
114 , MonadBaseControl IO m
115 ) => Printout -> Printer -> m JobId
116addToQueue printout Printer{..} = do
117 jobId <- runSqlPool (insert $ Job printout) =<< ask
118 $(logInfo) . T.pack $ "Queueing " ++ show (unSqlBackendKey . unJobKey $ jobId)
119 atomically' $ modifyTVar' queue (\Queue{..} -> force $ Queue (jobId <| pending) current history)
120 return jobId
diff --git a/server/src/Thermoprint/Server/Printer/Debug.hs b/server/src/Thermoprint/Server/Printer/Debug.hs
new file mode 100644
index 0000000..b8c1430
--- /dev/null
+++ b/server/src/Thermoprint/Server/Printer/Debug.hs
@@ -0,0 +1,39 @@
1{-# LANGUAGE OverloadedStrings #-}
2{-# LANGUAGE RankNTypes #-}
3{-# LANGUAGE TemplateHaskell #-}
4{-# LANGUAGE MultiParamTypeClasses #-}
5{-# LANGUAGE FlexibleInstances #-}
6
7module Thermoprint.Server.Printer.Debug
8 ( Debug(..)
9 ) where
10
11import Control.Monad.IO.Class
12import Control.Monad.Trans.Resource
13import Control.Monad.Logger
14
15import Data.Text.Lazy (Text)
16import qualified Data.Text.Lazy as TL
17
18import qualified Data.Text as T
19
20import Thermoprint.Printout
21import Thermoprint.Server.Printer
22
23import Data.List (intersperse)
24import Data.Foldable (toList)
25import Data.Monoid
26
27data Debug = Debug
28
29instance Applicative m => IsPrinter Debug m where
30 printMethod _ = printMethod debugPrinter
31
32debugPrinter :: PrinterMethod
33debugPrinter = PM $ (>> return Nothing) . $(logDebugS) "Printer.Debug" . T.pack . show . cotext'
34
35cotext' :: Printout -> Text
36cotext' = mconcat . intersperse "\n\n" . map (mconcat . map cotext'' . toList) . toList
37 where
38 cotext'' (Cooked b) = cotext b
39 cotext'' (Raw _) = "[Raw]"
diff --git a/server/thermoprint-server.cabal b/server/thermoprint-server.cabal
index 185a0f3..dd495c0 100644
--- a/server/thermoprint-server.cabal
+++ b/server/thermoprint-server.cabal
@@ -21,6 +21,7 @@ library
21 , Thermoprint.Server.Database 21 , Thermoprint.Server.Database
22 , Thermoprint.Server.API 22 , Thermoprint.Server.API
23 , Thermoprint.Server.Printer 23 , Thermoprint.Server.Printer
24 , Thermoprint.Server.Printer.Debug
24 other-modules: Thermoprint.Server.Database.Instances 25 other-modules: Thermoprint.Server.Database.Instances
25 -- other-extensions: 26 -- other-extensions:
26 build-depends: base >=4.8 && <5 27 build-depends: base >=4.8 && <5