aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--server/src/Thermoprint/Server/Printer/Generic.hs100
-rw-r--r--server/thermoprint-server.cabal4
-rw-r--r--server/thermoprint-server.nix18
3 files changed, 114 insertions, 8 deletions
diff --git a/server/src/Thermoprint/Server/Printer/Generic.hs b/server/src/Thermoprint/Server/Printer/Generic.hs
new file mode 100644
index 0000000..bf6ce3b
--- /dev/null
+++ b/server/src/Thermoprint/Server/Printer/Generic.hs
@@ -0,0 +1,100 @@
1{-# LANGUAGE FlexibleContexts #-}
2{-# LANGUAGE ViewPatterns #-}
3{-# LANGUAGE OverloadedStrings #-}
4
5module Thermoprint.Server.Printer.Generic
6 ( genericPrint
7 ) where
8
9import Thermoprint.Printout
10import Thermoprint.API (PrintingError(IOError))
11import Thermoprint.Server.Printer
12
13import System.FileLock
14import System.IO
15
16import Data.Sequence (Seq, (|>), (<|), ViewL(..), viewl)
17import qualified Data.Sequence as Seq
18
19import qualified Data.ByteString.Lazy as Lazy (ByteString)
20import qualified Data.ByteString.Lazy as LBS
21import qualified Data.ByteString.Lazy.Char8 as CLBS
22
23import qualified Data.Text.Lazy as Lazy (Text)
24import qualified Data.Text.Lazy as TL
25
26import Data.Encoding
27import Data.Encoding.CP437
28import Data.Word
29
30import Control.Monad
31import Control.Monad.Reader
32import Control.Monad.Trans.State
33import Control.Monad.IO.Class
34
35import Control.Monad.Trans.Resource
36import Data.Acquire
37
38import Control.Exception.Base (IOException)
39import Control.Monad.Catch
40
41import Data.Foldable
42
43import Data.List (intersperse, genericReplicate, intercalate)
44
45import Data.Int (Int64)
46
47import Prelude hiding (mapM_, sequence_)
48
49lockedFile :: FilePath -> Acquire (FileLock, Handle)
50lockedFile f = mkAcquire ((,) <$> lockFile f Exclusive <*> openFile f AppendMode) (\(lock, h) -> () <$ hClose h <* unlockFile lock)
51
52withLockedFile :: (MonadIO m, MonadMask m) => FilePath -> (Handle -> m a) -> m a
53withLockedFile path f = withEx (lockedFile path) (f . snd)
54
55genericPrint :: FilePath -> PrinterMethod
56genericPrint path = PM $ flip catches handlers . withLockedFile path . print
57 where
58 print printout handle = liftIO $ runReaderT (bracket_ initialize (render printout) finalize) handle >> return Nothing
59 handlers = [ Handler $ return . Just . IOError . (show :: IOException -> String)
60 , Handler $ return . Just . EncError
61 ]
62
63type Render = ReaderT Handle IO ()
64
65encode' :: ByteSink m => String -> m ()
66encode' = encode CP437
67
68width :: Int64
69width = 32
70
71esc :: Word8
72esc = 27
73
74escSequence :: [Word8] -> Render
75escSequence = mapM_ pushWord8 . (esc:)
76
77initialize :: Render
78initialize = replicateM_ 2 $ escSequence [64]
79
80finalize :: Render -- TODO: adjust this to produce proper padding
81finalize = encode' "\n\n\n"
82
83intersperse' :: b -> (a -> b) -> Seq a -> Seq b
84intersperse' _ _ (viewl -> EmptyL) = Seq.empty
85intersperse' _ f (viewl -> x :< (viewl -> EmptyL)) = Seq.singleton $ f x
86intersperse' b f (viewl -> x :< xs) = f x <| b <| intersperse' b f xs
87
88render :: Printout -> Render
89render = sequence_ . intersperse' (encode' "\n\n") renderPar
90
91renderPar :: Paragraph -> Render
92renderPar = mapM_ renderChunk
93 where
94 renderChunk (Raw bs) = mapM_ pushWord8 $ LBS.unpack bs
95 renderChunk (Cooked block) = renderBlock block
96
97renderBlock :: Block -> Render
98renderBlock (VSpace n) = encode' $ genericReplicate n '\n'
99renderBlock (NewlSep xs) = sequence_ intercalate (encode' "\n") . map renderBlock . toList $ xs
100renderBlock (Line x) = undefined
diff --git a/server/thermoprint-server.cabal b/server/thermoprint-server.cabal
index 5783f06..5e9c61f 100644
--- a/server/thermoprint-server.cabal
+++ b/server/thermoprint-server.cabal
@@ -23,6 +23,7 @@ library
23 , Thermoprint.Server.Queue 23 , Thermoprint.Server.Queue
24 , Thermoprint.Server.Printer 24 , Thermoprint.Server.Printer
25 , Thermoprint.Server.Printer.Debug 25 , Thermoprint.Server.Printer.Debug
26 , Thermoprint.Server.Printer.Generic
26 other-modules: Thermoprint.Server.Database.Instances 27 other-modules: Thermoprint.Server.Database.Instances
27 -- other-extensions: 28 -- other-extensions:
28 build-depends: base >=4.8 && <5 29 build-depends: base >=4.8 && <5
@@ -49,6 +50,9 @@ library
49 , warp >=3.1.9 && <4 50 , warp >=3.1.9 && <4
50 , mmorph >=1.0.4 && <2 51 , mmorph >=1.0.4 && <2
51 , extended-reals >=0.2.1 && <1 52 , extended-reals >=0.2.1 && <1
53 , filelock >=0.1.0 && <1
54 , bytestring >=0.10.6 && <1
55 , encoding >=0.8 && <1
52 hs-source-dirs: src 56 hs-source-dirs: src
53 default-language: Haskell2010 57 default-language: Haskell2010
54 58
diff --git a/server/thermoprint-server.nix b/server/thermoprint-server.nix
index a33e6db..d4ebb60 100644
--- a/server/thermoprint-server.nix
+++ b/server/thermoprint-server.nix
@@ -1,6 +1,7 @@
1{ mkDerivation, base, conduit, containers, data-default-class 1{ mkDerivation, base, bytestring, conduit, containers
2, deepseq, dyre, either, exceptions, extended-reals, hspec, mmorph 2, data-default-class, deepseq, dyre, either, encoding, exceptions
3, monad-control, monad-logger, mtl, persistent, persistent-sqlite 3, extended-reals, filelock, hspec, mmorph, monad-control
4, monad-logger, mtl, persistent, persistent-sqlite
4, persistent-template, QuickCheck, quickcheck-instances, resourcet 5, persistent-template, QuickCheck, quickcheck-instances, resourcet
5, servant-server, stdenv, stm, text, thermoprint-spec, time 6, servant-server, stdenv, stm, text, thermoprint-spec, time
6, transformers, wai, warp 7, transformers, wai, warp
@@ -12,16 +13,17 @@ mkDerivation {
12 isLibrary = true; 13 isLibrary = true;
13 isExecutable = true; 14 isExecutable = true;
14 libraryHaskellDepends = [ 15 libraryHaskellDepends = [
15 base conduit containers data-default-class deepseq dyre either 16 base bytestring conduit containers data-default-class deepseq dyre
16 exceptions extended-reals mmorph monad-control monad-logger mtl 17 either encoding exceptions extended-reals filelock mmorph
17 persistent persistent-template resourcet servant-server stm text 18 monad-control monad-logger mtl persistent persistent-template
18 thermoprint-spec time transformers wai warp 19 resourcet servant-server stm text thermoprint-spec time
20 transformers wai warp
19 ]; 21 ];
20 executableHaskellDepends = [ 22 executableHaskellDepends = [
21 base monad-logger mtl persistent-sqlite resourcet 23 base monad-logger mtl persistent-sqlite resourcet
22 ]; 24 ];
23 testHaskellDepends = [ 25 testHaskellDepends = [
24 base hspec QuickCheck quickcheck-instances 26 base hspec QuickCheck quickcheck-instances thermoprint-spec
25 ]; 27 ];
26 homepage = "http://dirty-haskell.org/tags/thermoprint.html"; 28 homepage = "http://dirty-haskell.org/tags/thermoprint.html";
27 description = "Server for thermoprint-spec"; 29 description = "Server for thermoprint-spec";