diff options
-rw-r--r-- | server/default-conf/Main.hs | 14 | ||||
-rw-r--r-- | server/src/Thermoprint/Server.hs | 35 | ||||
-rw-r--r-- | server/src/Thermoprint/Server/API.hs | 27 | ||||
-rw-r--r-- | server/src/Thermoprint/Server/Database.hs | 11 | ||||
-rw-r--r-- | server/src/Thermoprint/Server/Printer.hs | 51 | ||||
-rw-r--r-- | server/src/Thermoprint/Server/Printer/Debug.hs | 39 | ||||
-rw-r--r-- | server/thermoprint-server.cabal | 1 |
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 | ||
3 | module Main (main) where | 4 | module Main (main) where |
4 | 5 | ||
5 | import Thermoprint.Server | 6 | import Thermoprint.Server |
6 | 7 | ||
8 | import Thermoprint.Server.Printer.Debug | ||
9 | |||
7 | import Control.Monad.Trans.Resource | 10 | import Control.Monad.Trans.Resource |
8 | import Control.Monad.Logger | 11 | import Control.Monad.Logger |
9 | import Control.Monad.Reader | 12 | import Control.Monad.Reader |
@@ -11,7 +14,10 @@ import Control.Monad.Reader | |||
11 | import Database.Persist.Sqlite | 14 | import Database.Persist.Sqlite |
12 | 15 | ||
13 | main :: IO () | 16 | main :: IO () |
14 | main = thermoprintServer (Nat runSqlite) def | 17 | main = 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 | ||
7 | module Thermoprint.Server | 8 | module 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) | |||
19 | import qualified Data.Map as Map | 21 | import qualified Data.Map as Map |
20 | 22 | ||
21 | import Data.Maybe (maybe) | 23 | import Data.Maybe (maybe) |
22 | import Data.Foldable (mapM_, forM_) | 24 | import Data.Foldable (mapM_, forM_, foldlM) |
23 | 25 | ||
24 | import Control.Monad.Trans.Resource | 26 | import Control.Monad.Trans.Resource |
25 | import Control.Monad.Trans.Control | 27 | import Control.Monad.Trans.Control |
26 | import Control.Monad.Logger | 28 | import Control.Monad.Logger |
27 | import Control.Monad.Reader | 29 | import Control.Monad.Reader |
28 | import Control.Monad.IO.Class | 30 | import Control.Monad.IO.Class |
31 | import Control.Category | ||
32 | import Prelude hiding (id, (.)) | ||
29 | 33 | ||
30 | import Control.Concurrent | 34 | import Control.Concurrent |
31 | 35 | ||
@@ -62,20 +66,27 @@ instance Default Config where | |||
62 | 66 | ||
63 | 67 | ||
64 | thermoprintServer :: ( MonadLoggerIO m | 68 | thermoprintServer :: ( 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 |
71 | thermoprintServer io = Dyre.wrapMain $ Dyre.defaultParams | 74 | thermoprintServer 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 | |||
87 | withPrinters :: MonadResource m => Config -> [PrinterSpec m] -> m Config | ||
88 | withPrinters 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 | ||
5 | module Thermoprint.Server.API | 6 | module Thermoprint.Server.API |
6 | ( ProtoHandler, Handler | 7 | ( ProtoHandler, Handler |
@@ -11,7 +12,8 @@ module Thermoprint.Server.API | |||
11 | import Thermoprint.API hiding (JobId(..), DraftId(..)) | 12 | import Thermoprint.API hiding (JobId(..), DraftId(..)) |
12 | import qualified Thermoprint.API as API (JobId(..), DraftId(..)) | 13 | import qualified Thermoprint.API as API (JobId(..), DraftId(..)) |
13 | 14 | ||
14 | import Thermoprint.Server.Printer (Printer(..), Queue(..)) | 15 | import Thermoprint.Server.Printer |
16 | import Thermoprint.Server.Database | ||
15 | 17 | ||
16 | import Data.Set (Set) | 18 | import Data.Set (Set) |
17 | import qualified Data.Set as Set | 19 | import qualified Data.Set as Set |
@@ -26,6 +28,7 @@ import Servant.Server.Internal.Enter | |||
26 | 28 | ||
27 | import Control.Monad.Logger | 29 | import Control.Monad.Logger |
28 | import Control.Monad.Reader | 30 | import Control.Monad.Reader |
31 | import Control.Monad.Trans.Resource | ||
29 | import Control.Monad.Trans.Either | 32 | import Control.Monad.Trans.Either |
30 | import Control.Monad.IO.Class | 33 | import Control.Monad.IO.Class |
31 | 34 | ||
@@ -40,7 +43,7 @@ import Data.Traversable (mapM) | |||
40 | import Database.Persist | 43 | import Database.Persist |
41 | import Database.Persist.Sql | 44 | import Database.Persist.Sql |
42 | 45 | ||
43 | type ProtoHandler = ReaderT HandlerInput (LoggingT IO) | 46 | type ProtoHandler = ReaderT HandlerInput (LoggingT (ResourceT IO)) |
44 | type Handler = EitherT ServantErr ProtoHandler | 47 | type 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 | ||
69 | thermoprintServer :: ServerT ThermoprintAPI Handler | 72 | thermoprintServer :: ServerT ThermoprintAPI Handler |
@@ -79,6 +82,16 @@ thermoprintServer = listPrinters | |||
79 | (<||>) = liftM2 (:<|>) | 82 | (<||>) = liftM2 (:<|>) |
80 | infixr 9 <||> | 83 | infixr 9 <||> |
81 | 84 | ||
85 | lookupPrinter :: Maybe PrinterId -> Handler Printer | ||
86 | lookupPrinter 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 | |||
82 | listPrinters :: Handler (Map PrinterId PrinterStatus) | 95 | listPrinters :: Handler (Map PrinterId PrinterStatus) |
83 | listPrinters = fmap toStatus <$> (mapM (liftIO . readTVarIO . queue) . printers =<< ask) | 96 | listPrinters = 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 | ||
88 | queueJob :: Maybe PrinterId -> Printout -> Handler API.JobId | 101 | queueJob :: Maybe PrinterId -> Printout -> Handler API.JobId |
89 | queueJob = return undefined | 102 | queueJob pId printout = lift . fmap (castId' . unJobKey) . withReaderT sqlPool . addToQueue printout =<< lookupPrinter pId |
90 | 103 | ||
91 | printerStatus :: PrinterId -> Handler PrinterStatus | 104 | printerStatus :: PrinterId -> Handler PrinterStatus |
92 | printerStatus = return undefined | 105 | printerStatus = 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 @@ | |||
9 | module Thermoprint.Server.Database | 9 | module 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 | ||
15 | import Control.DeepSeq | 17 | import Control.DeepSeq |
16 | 18 | ||
17 | import Thermoprint.API (Printout, DraftTitle, JobStatus) | 19 | import Thermoprint.API (Printout, DraftTitle, JobStatus, castId) |
18 | 20 | ||
19 | import Database.Persist.TH | 21 | import Database.Persist.TH |
20 | import Database.Persist.Sql (unSqlBackendKey) | 22 | import Database.Persist.Sql (unSqlBackendKey, SqlBackend) |
21 | import Database.Persist.Class (Key) | 23 | import Database.Persist.Class (Key, BackendKey) |
22 | 24 | ||
23 | import Thermoprint.Server.Database.Instances | 25 | import Thermoprint.Server.Database.Instances |
24 | 26 | ||
@@ -32,3 +34,6 @@ Draft | |||
32 | 34 | ||
33 | instance NFData (Key Job) where | 35 | instance NFData (Key Job) where |
34 | rnf = rnf . unSqlBackendKey . unJobKey | 36 | rnf = rnf . unSqlBackendKey . unJobKey |
37 | |||
38 | castId' :: Enum b => BackendKey SqlBackend -> b | ||
39 | castId' = 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 | ||
10 | module Thermoprint.Server.Printer | 14 | module 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 | ||
16 | import Thermoprint.API (PrintingError(..), Printout) | 21 | import Thermoprint.API (PrintingError(..), Printout) |
@@ -31,6 +36,7 @@ import qualified Data.Text as T (pack) | |||
31 | import Data.Typeable (Typeable) | 36 | import Data.Typeable (Typeable) |
32 | import GHC.Generics (Generic) | 37 | import GHC.Generics (Generic) |
33 | import Control.DeepSeq | 38 | import Control.DeepSeq |
39 | import Data.Default.Class | ||
34 | 40 | ||
35 | import Control.Monad.Trans.Resource | 41 | import Control.Monad.Trans.Resource |
36 | import Control.Monad.IO.Class | 42 | import Control.Monad.IO.Class |
@@ -41,8 +47,20 @@ import Control.Monad (forever) | |||
41 | 47 | ||
42 | import Control.Concurrent.STM | 48 | import Control.Concurrent.STM |
43 | 49 | ||
50 | newtype PrinterMethod = PM { unPM :: forall m. (MonadResource m, MonadLogger m) => Printout -> m (Maybe PrintingError) } | ||
51 | data PrinterSpec m = forall p. IsPrinter p m => PS p | ||
52 | |||
53 | class IsPrinter p m where | ||
54 | printMethod :: p -> m PrinterMethod | ||
55 | |||
56 | instance Applicative m => IsPrinter PrinterMethod m where | ||
57 | printMethod = pure | ||
58 | |||
59 | instance IsPrinter (PrinterSpec m) m where | ||
60 | printMethod (PS p) = printMethod p | ||
61 | |||
44 | data Printer = Printer | 62 | data 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 | ||
57 | printer :: (MonadIO m) => (forall m. (MonadIO m) => Printout -> m (Maybe PrintingError)) -> m Printer | 75 | instance Default Queue where |
58 | printer 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 | |||
82 | printer :: (MonadResource m, IsPrinter p m) => p -> m Printer | ||
83 | printer spec = Printer <$> printMethod spec <*> liftIO (newTVarIO def) | ||
59 | 84 | ||
60 | atomically' :: MonadIO m => STM a -> m a | 85 | atomically' :: MonadIO m => STM a -> m a |
61 | atomically' = liftIO . atomically | 86 | atomically' = liftIO . atomically |
62 | 87 | ||
63 | runPrinter :: ( MonadReader ConnectionPool m | 88 | runPrinter :: ( 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 |
69 | runPrinter Printer{..} = forever $ do | 94 | runPrinter 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 | |||
111 | addToQueue :: ( MonadReader ConnectionPool m | ||
112 | , MonadLogger m | ||
113 | , MonadResource m | ||
114 | , MonadBaseControl IO m | ||
115 | ) => Printout -> Printer -> m JobId | ||
116 | addToQueue 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 | |||
7 | module Thermoprint.Server.Printer.Debug | ||
8 | ( Debug(..) | ||
9 | ) where | ||
10 | |||
11 | import Control.Monad.IO.Class | ||
12 | import Control.Monad.Trans.Resource | ||
13 | import Control.Monad.Logger | ||
14 | |||
15 | import Data.Text.Lazy (Text) | ||
16 | import qualified Data.Text.Lazy as TL | ||
17 | |||
18 | import qualified Data.Text as T | ||
19 | |||
20 | import Thermoprint.Printout | ||
21 | import Thermoprint.Server.Printer | ||
22 | |||
23 | import Data.List (intersperse) | ||
24 | import Data.Foldable (toList) | ||
25 | import Data.Monoid | ||
26 | |||
27 | data Debug = Debug | ||
28 | |||
29 | instance Applicative m => IsPrinter Debug m where | ||
30 | printMethod _ = printMethod debugPrinter | ||
31 | |||
32 | debugPrinter :: PrinterMethod | ||
33 | debugPrinter = PM $ (>> return Nothing) . $(logDebugS) "Printer.Debug" . T.pack . show . cotext' | ||
34 | |||
35 | cotext' :: Printout -> Text | ||
36 | cotext' = 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 |