diff options
author | Gregor Kleen <gkleen@yggdrasil.li> | 2016-01-25 13:25:18 +0000 |
---|---|---|
committer | Gregor Kleen <gkleen@yggdrasil.li> | 2016-01-25 13:25:18 +0000 |
commit | 9d9bad89241bfa14255361dd8452ad40291a9684 (patch) | |
tree | 5e0f940724f060fb732c36e81217b10c5eb69229 | |
parent | 09f4d0431ef3015653b6b78f1d413454519380bd (diff) | |
download | thermoprint-9d9bad89241bfa14255361dd8452ad40291a9684.tar thermoprint-9d9bad89241bfa14255361dd8452ad40291a9684.tar.gz thermoprint-9d9bad89241bfa14255361dd8452ad40291a9684.tar.bz2 thermoprint-9d9bad89241bfa14255361dd8452ad40291a9684.tar.xz thermoprint-9d9bad89241bfa14255361dd8452ad40291a9684.zip |
Cleaned up printer declaration
-rw-r--r-- | server/default-conf/Main.hs | 2 | ||||
-rw-r--r-- | server/src/Thermoprint/Server.hs | 2 | ||||
-rw-r--r-- | server/src/Thermoprint/Server/Printer.hs | 20 | ||||
-rw-r--r-- | server/src/Thermoprint/Server/Printer/Debug.hs | 14 |
4 files changed, 9 insertions, 29 deletions
diff --git a/server/default-conf/Main.hs b/server/default-conf/Main.hs index 982f50e..39e500d 100644 --- a/server/default-conf/Main.hs +++ b/server/default-conf/Main.hs | |||
@@ -19,5 +19,5 @@ main = thermoprintServer (Nat runSqlite) $ def `withPrinters` printers | |||
19 | runSqlite :: ReaderT ConnectionPool (LoggingT IO) a -> IO a | 19 | runSqlite :: ReaderT ConnectionPool (LoggingT IO) a -> IO a |
20 | runSqlite = runStderrLoggingT . withSqlitePool "thermoprint.sqlite" 1 . runReaderT | 20 | runSqlite = runStderrLoggingT . withSqlitePool "thermoprint.sqlite" 1 . runReaderT |
21 | 21 | ||
22 | printers = [ PS Debug | 22 | printers = [ pure debugPrint |
23 | ] | 23 | ] |
diff --git a/server/src/Thermoprint/Server.hs b/server/src/Thermoprint/Server.hs index ed20983..3d0e97e 100644 --- a/server/src/Thermoprint/Server.hs +++ b/server/src/Thermoprint/Server.hs | |||
@@ -84,7 +84,7 @@ thermoprintServer io = Dyre.wrapMain $ Dyre.defaultParams | |||
84 | forM_ printers $ resourceForkIO . runPrinter | 84 | forM_ printers $ resourceForkIO . runPrinter |
85 | 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 | 86 | ||
87 | withPrinters :: MonadResource m => Config -> [PrinterSpec m] -> m Config | 87 | withPrinters :: MonadResource m => Config -> [m PrinterMethod] -> m Config |
88 | withPrinters cfg pss = (\map -> cfg { printers = map }) <$> foldlM (\map spec -> Map.insert (nextKey map) <$> printer spec <*> pure map) Map.empty pss | 88 | withPrinters cfg pss = (\map -> cfg { printers = map }) <$> foldlM (\map spec -> Map.insert (nextKey map) <$> printer spec <*> pure map) Map.empty pss |
89 | where | 89 | where |
90 | nextKey map | 90 | nextKey map |
diff --git a/server/src/Thermoprint/Server/Printer.hs b/server/src/Thermoprint/Server/Printer.hs index 46b8a53..5b1b7b0 100644 --- a/server/src/Thermoprint/Server/Printer.hs +++ b/server/src/Thermoprint/Server/Printer.hs | |||
@@ -1,7 +1,4 @@ | |||
1 | {-# LANGUAGE RankNTypes #-} | 1 | {-# LANGUAGE RankNTypes #-} |
2 | {-# LANGUAGE TypeSynonymInstances #-} | ||
3 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
4 | {-# LANGUAGE FlexibleInstances #-} | ||
5 | {-# LANGUAGE FlexibleContexts #-} | 2 | {-# LANGUAGE FlexibleContexts #-} |
6 | {-# LANGUAGE RecordWildCards #-} | 3 | {-# LANGUAGE RecordWildCards #-} |
7 | {-# LANGUAGE OverloadedStrings #-} | 4 | {-# LANGUAGE OverloadedStrings #-} |
@@ -12,7 +9,8 @@ | |||
12 | {-# LANGUAGE DeriveGeneric, DeriveAnyClass #-} | 9 | {-# LANGUAGE DeriveGeneric, DeriveAnyClass #-} |
13 | 10 | ||
14 | module Thermoprint.Server.Printer | 11 | module Thermoprint.Server.Printer |
15 | ( PrinterMethod(..), PrinterSpec(..), IsPrinter(..), Printer(..), printer | 12 | ( PrinterMethod(..), Printer(..) |
13 | , printer | ||
16 | , Queue(..) | 14 | , Queue(..) |
17 | , runPrinter | 15 | , runPrinter |
18 | , addToQueue | 16 | , addToQueue |
@@ -48,16 +46,6 @@ import Control.Monad (forever) | |||
48 | import Control.Concurrent.STM | 46 | import Control.Concurrent.STM |
49 | 47 | ||
50 | newtype PrinterMethod = PM { unPM :: forall m. (MonadResource m, MonadLogger m) => Printout -> m (Maybe PrintingError) } | 48 | 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 | 49 | ||
62 | data Printer = Printer | 50 | data Printer = Printer |
63 | { print :: PrinterMethod | 51 | { print :: PrinterMethod |
@@ -79,8 +67,8 @@ instance Default Queue where | |||
79 | , history = Seq.empty | 67 | , history = Seq.empty |
80 | } | 68 | } |
81 | 69 | ||
82 | printer :: (MonadResource m, IsPrinter p m) => p -> m Printer | 70 | printer :: MonadResource m => m PrinterMethod -> m Printer |
83 | printer spec = Printer <$> printMethod spec <*> liftIO (newTVarIO def) | 71 | printer p = Printer <$> p <*> liftIO (newTVarIO def) |
84 | 72 | ||
85 | atomically' :: MonadIO m => STM a -> m a | 73 | atomically' :: MonadIO m => STM a -> m a |
86 | atomically' = liftIO . atomically | 74 | atomically' = liftIO . atomically |
diff --git a/server/src/Thermoprint/Server/Printer/Debug.hs b/server/src/Thermoprint/Server/Printer/Debug.hs index b8c1430..721ec84 100644 --- a/server/src/Thermoprint/Server/Printer/Debug.hs +++ b/server/src/Thermoprint/Server/Printer/Debug.hs | |||
@@ -1,11 +1,8 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | 1 | {-# LANGUAGE OverloadedStrings #-} |
2 | {-# LANGUAGE RankNTypes #-} | ||
3 | {-# LANGUAGE TemplateHaskell #-} | 2 | {-# LANGUAGE TemplateHaskell #-} |
4 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
5 | {-# LANGUAGE FlexibleInstances #-} | ||
6 | 3 | ||
7 | module Thermoprint.Server.Printer.Debug | 4 | module Thermoprint.Server.Printer.Debug |
8 | ( Debug(..) | 5 | ( debugPrint |
9 | ) where | 6 | ) where |
10 | 7 | ||
11 | import Control.Monad.IO.Class | 8 | import Control.Monad.IO.Class |
@@ -24,13 +21,8 @@ import Data.List (intersperse) | |||
24 | import Data.Foldable (toList) | 21 | import Data.Foldable (toList) |
25 | import Data.Monoid | 22 | import Data.Monoid |
26 | 23 | ||
27 | data Debug = Debug | 24 | debugPrint :: PrinterMethod |
28 | 25 | debugPrint = PM $ (>> return Nothing) . $(logDebugS) "Printer.Debug" . T.pack . show . cotext' | |
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 | 26 | ||
35 | cotext' :: Printout -> Text | 27 | cotext' :: Printout -> Text |
36 | cotext' = mconcat . intersperse "\n\n" . map (mconcat . map cotext'' . toList) . toList | 28 | cotext' = mconcat . intersperse "\n\n" . map (mconcat . map cotext'' . toList) . toList |