aboutsummaryrefslogtreecommitdiff
path: root/server/src/Thermoprint/Server
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2016-01-23 19:42:22 +0000
committerGregor Kleen <gkleen@yggdrasil.li>2016-01-23 19:42:22 +0000
commit6434397a3d103547b563ada27fd64c38cb05e1f0 (patch)
tree29e67e7a0804ca46467565c35dc3c15447bf814e /server/src/Thermoprint/Server
parent8553c33f72c41e553cbef4e7175cef8cec3cdbe2 (diff)
downloadthermoprint-6434397a3d103547b563ada27fd64c38cb05e1f0.tar
thermoprint-6434397a3d103547b563ada27fd64c38cb05e1f0.tar.gz
thermoprint-6434397a3d103547b563ada27fd64c38cb05e1f0.tar.bz2
thermoprint-6434397a3d103547b563ada27fd64c38cb05e1f0.tar.xz
thermoprint-6434397a3d103547b563ada27fd64c38cb05e1f0.zip
Broken existentially quantified printer config
Diffstat (limited to 'server/src/Thermoprint/Server')
-rw-r--r--server/src/Thermoprint/Server/Printer.hs39
-rw-r--r--server/src/Thermoprint/Server/Printer/Debug.hs32
2 files changed, 65 insertions, 6 deletions
diff --git a/server/src/Thermoprint/Server/Printer.hs b/server/src/Thermoprint/Server/Printer.hs
index f34b2fa..cd12297 100644
--- a/server/src/Thermoprint/Server/Printer.hs
+++ b/server/src/Thermoprint/Server/Printer.hs
@@ -1,14 +1,18 @@
1{-# LANGUAGE RankNTypes #-} 1{-# LANGUAGE RankNTypes #-}
2{-# LANGUAGE ImpredicativeTypes #-}
2{-# LANGUAGE MultiParamTypeClasses #-} 3{-# LANGUAGE MultiParamTypeClasses #-}
3{-# LANGUAGE FlexibleContexts #-} 4{-# LANGUAGE FlexibleContexts #-}
4{-# LANGUAGE RecordWildCards #-} 5{-# LANGUAGE RecordWildCards #-}
5{-# LANGUAGE OverloadedStrings #-} 6{-# LANGUAGE OverloadedStrings #-}
6{-# LANGUAGE TemplateHaskell #-} 7{-# LANGUAGE TemplateHaskell #-}
7{-# LANGUAGE StandaloneDeriving #-} 8{-# LANGUAGE StandaloneDeriving #-}
9{-# LANGUAGE ExistentialQuantification #-}
10{-# LANGUAGE RecordWildCards #-}
8{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-} 11{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}
9 12
10module Thermoprint.Server.Printer 13module Thermoprint.Server.Printer
11 ( Printer(..), printer 14 ( Printer(..), printer
15 , IsPrinter(..), PrinterSpec(..)
12 , Queue(..) 16 , Queue(..)
13 , runPrinter 17 , runPrinter
14 ) where 18 ) where
@@ -41,8 +45,23 @@ import Control.Monad (forever)
41 45
42import Control.Concurrent.STM 46import Control.Concurrent.STM
43 47
44data Printer = Printer 48import Data.Default.Class
45 { print :: forall m. (MonadIO m) => Printout -> m (Maybe PrintingError) 49
50import Prelude hiding (print)
51
52class IsPrinter a where
53 toMethod :: forall m. (MonadResource m) => a -> (forall m1. (MonadResource m1) => m (Printout -> m1 (Maybe PrintingError)))
54
55instance (MonadResource m) => IsPrinter (Printer m) where
56 toMethod Printer{..} = return print
57
58instance (MonadResource m) => IsPrinter (PrinterSpec m) where
59 toMethod (PS p) = toMethod p
60
61data PrinterSpec m = forall p. IsPrinter p => PS p
62
63data Printer m = Printer
64 { print :: Printout -> m (Maybe PrintingError)
46 , queue :: TVar Queue 65 , queue :: TVar Queue
47 } 66 }
48 67
@@ -54,17 +73,25 @@ data Queue = Queue
54 } 73 }
55 deriving (Typeable, Generic, NFData) 74 deriving (Typeable, Generic, NFData)
56 75
57printer :: (MonadIO m) => (forall m. (MonadIO m) => Printout -> m (Maybe PrintingError)) -> m Printer 76instance Default Queue where
58printer f = Printer f <$> liftIO (newTVarIO $ Queue Seq.empty Nothing Seq.empty) 77 def = Queue
78 { pending = Seq.empty
79 , current = Nothing
80 , history = Seq.empty
81 }
82
83printer :: (MonadResource m, MonadResource m1, IsPrinter p) => p -> m (Printer m1)
84-- ^ Version of 'Printer' handling the initialisation of the 'TVar'
85printer p = Printer <$> toMethod p <*> liftIO (newTVarIO def)
59 86
60atomically' :: MonadIO m => STM a -> m a 87atomically' :: MonadIO m => STM a -> m a
61atomically' = liftIO . atomically 88atomically' = liftIO . atomically
62 89
63runPrinter :: ( MonadReader ConnectionPool m 90runPrinter :: ( MonadReader ConnectionPool m
64 , MonadIO m
65 , MonadLogger m 91 , MonadLogger m
92 , MonadResource m
66 , MonadBaseControl IO m 93 , MonadBaseControl IO m
67 ) => Printer -> m () 94 ) => Printer m -> m ()
68-- ^ Loop 'forever' pushing entries from the 'Queue' associated to a 'Printer' into its 'print'-method 95-- ^ Loop 'forever' pushing entries from the 'Queue' associated to a 'Printer' into its 'print'-method
69runPrinter Printer{..} = forever $ do 96runPrinter Printer{..} = forever $ do
70 jobId <- atomically' $ do 97 jobId <- atomically' $ do
diff --git a/server/src/Thermoprint/Server/Printer/Debug.hs b/server/src/Thermoprint/Server/Printer/Debug.hs
new file mode 100644
index 0000000..81e43a3
--- /dev/null
+++ b/server/src/Thermoprint/Server/Printer/Debug.hs
@@ -0,0 +1,32 @@
1{-# LANGUAGE EmptyDataDecls #-}
2{-# LANGUAGE OverloadedStrings #-}
3{-# LANGUAGE RankNTypes #-}
4
5module Thermoprint.Server.Printer.Debug
6 ( Debug
7 ) where
8
9import Control.Monad.IO.Class
10import Control.Monad.Trans.Resource
11
12import Data.Text.Lazy (Text)
13import qualified Data.Text.Lazy as TL
14import qualified Data.Text.Lazy.IO as TL
15
16import Thermoprint.Printout
17import Thermoprint.Server.Printer
18
19import Data.List (intersperse)
20import Data.Foldable (toList)
21import Data.Monoid
22
23data Debug
24
25-- instance IsPrinter Debug where
26-- toMethod _ = (>> return Nothing) . liftIO . TL.putStrLn . cotext'
27
28-- cotext' :: Printout -> Text
29-- cotext' = mconcat . intersperse "\n\n" . map (mconcat . map cotext'' . toList) . toList
30-- where
31-- cotext'' (Cooked b) = cotext b
32-- cotext'' (Raw _) = "[Raw]"