aboutsummaryrefslogtreecommitdiff
path: root/server/test/Thermoprint
diff options
context:
space:
mode:
authorGregor Kleen <pngwjpgh@users.noreply.github.com>2017-01-23 16:09:05 +0100
committerGregor Kleen <pngwjpgh@users.noreply.github.com>2017-01-23 16:09:05 +0100
commit64b6ead0d1e157701f8569743eda496bc71b8351 (patch)
treef7ae09e9ec950e91cacb1923aa54b96d59c9a8f3 /server/test/Thermoprint
parente95dac748371afcad3ffddf5c98e5fcb0a8302b7 (diff)
downloadthermoprint-64b6ead0d1e157701f8569743eda496bc71b8351.tar
thermoprint-64b6ead0d1e157701f8569743eda496bc71b8351.tar.gz
thermoprint-64b6ead0d1e157701f8569743eda496bc71b8351.tar.bz2
thermoprint-64b6ead0d1e157701f8569743eda496bc71b8351.tar.xz
thermoprint-64b6ead0d1e157701f8569743eda496bc71b8351.zip
Add support for ESC/POS text decoration
Diffstat (limited to 'server/test/Thermoprint')
-rw-r--r--server/test/Thermoprint/Server/Printer/GenericSpec.hs69
1 files changed, 69 insertions, 0 deletions
diff --git a/server/test/Thermoprint/Server/Printer/GenericSpec.hs b/server/test/Thermoprint/Server/Printer/GenericSpec.hs
new file mode 100644
index 0000000..80096b0
--- /dev/null
+++ b/server/test/Thermoprint/Server/Printer/GenericSpec.hs
@@ -0,0 +1,69 @@
1{-# LANGUAGE OverloadedStrings, OverloadedLists #-}
2{-# LANGUAGE StandaloneDeriving #-}
3{-# LANGUAGE ViewPatterns #-}
4
5module Thermoprint.Server.Printer.GenericSpec (spec) where
6
7import Test.Hspec
8import Test.Hspec.QuickCheck (prop)
9import Test.QuickCheck (Property, Discard(..), property)
10import Test.QuickCheck.Instances
11
12import Thermoprint.Server.Printer.Generic
13import Thermoprint.Printout
14
15import Data.Text (Text)
16import qualified Data.Text.Lazy as TL (pack)
17
18import qualified Data.ByteString.Lazy as L (ByteString)
19import qualified Data.ByteString.Lazy as L.BS
20
21import Data.String (IsString(..))
22
23import Control.Monad (zipWithM_, join)
24import Data.Monoid ((<>))
25import Data.Function (on)
26
27import Data.Word
28
29import Data.Sequence (Seq)
30import qualified Data.Sequence as Seq
31
32import Debug.Trace
33
34instance IsString Line where
35 fromString = (\(Right l) -> l) . text . TL.pack
36
37spec :: Spec
38spec = do
39 describe "example printouts" $
40 zipWithM_ example [1..] examples
41 where
42 example n (s, ts) = let str = show s
43 in specify str $ traceDump (mkPrintout . Printout . fmap (Paragraph . Seq.singleton) . fmap Cooked $ s) == ts
44
45final, initial :: L.ByteString
46initial = esc [64] <> esc [64]
47final = "\n\n\n \n"
48
49esc :: [Word8] -> L.ByteString
50esc = L.BS.pack . (27:)
51
52p :: L.ByteString -> L.ByteString
53p = (<> final) . (initial <>)
54
55traceDump :: L.ByteString -> L.ByteString
56traceDump bs = traceShow (map (\b -> (b, (toEnum $ fromEnum b) :: Char)) $ L.BS.unpack bs) bs
57
58examples :: [(Seq Block, L.ByteString)]
59examples = [ ( [Line (JuxtaPos ["Hello", HSpace 1, "World!"])]
60 , p "Hello World!")
61 , ( [Line (JuxtaPos ["Hello", HSpace 4, "World!"])]
62 , p "Hello World!")
63 , ( [Line ("Par1"), Line ("Par2"), Line (JuxtaPos ["Par3", HSpace 1, "Word2"])]
64 , p "Par1\n\nPar2\n\nPar3 Word2")
65 , ( [Line (JuxtaPos ["Par1", HSpace 4]), NewlSep [VSpace 2, Line ("Par2")], Line (JuxtaPos ["Par3", HSpace 1, "Word2"])]
66 , p "Par1 \n\n\n\n\nPar2\n\nPar3 Word2")
67 , ( [Line (JuxtaPos [Markup [Bold] (JuxtaPos ["B",HSpace 1,Markup [Underline] "BM"]),HSpace 1,Markup [Bold,Underline] "BM"])]
68 , p $ esc [33, 8] <> "B " <> esc [33, 128 + 8] <> "BM" <> esc [33, 8] <> esc [33, 0] <> " " <> esc [33, 128 + 8] <> "BM" <> esc [33, 0])
69 ]