]> Git — Sourcephile - haskell/symantic-document.git/blob - tests/HUnit.hs
tests: move some units to goldens
[haskell/symantic-document.git] / tests / HUnit.hs
1 {-# LANGUAGE OverloadedStrings #-}
2 module HUnit where
3
4 import Test.Tasty
5 import Test.Tasty.HUnit
6
7 import Data.Foldable (Foldable(..))
8 import Data.Function (($), (.))
9 import Data.Functor ((<$>))
10 import Data.Int (Int)
11 import Data.Maybe (Maybe(..))
12 import Data.Ord (Ord(..))
13 import Data.String (String, IsString(..))
14 import Prelude ((+))
15 import Text.Show (Show(..))
16 import qualified Data.List as List
17
18 import Symantic.Formatter.Class
19 import Symantic.Formatter.Plain (Plain, runPlain)
20
21 -- * Tests
22 hunit :: TestTree
23 hunit = testGroup "HUnit"
24 [ testList "Plain"
25 [ testPlain newline () "\n"
26 , testPlain ("hello".>"world") () "helloworld"
27 , testPlain ("hello".>newline.>"world") () "hello\nworld"
28 , testPlain ("hello\nworld") () "hello\nworld"
29 , testPlain (setWidth (Just 9) $ "hello" .> breakpoint .> "world")
30 ()
31 "hello\nworld"
32 , testPlain (setWidth (Just 10) $ intercalate_ breakpoint string)
33 ["hello", "world"]
34 "helloworld"
35 , testPlain (setWidth (Just 6) $ intercalate_ breakpoint string)
36 ["he", "ll", "o!"]
37 "hello!"
38 , testPlain (setWidth (Just 6) $ intercalate_ breakpoint string)
39 ["he", "ll", "o!", "wo", "rl", "d!"]
40 "hello!\nworld!"
41 , testPlain (setWidth (Just 5) $ intercalate_ breakpoint string)
42 ["hello", "world"]
43 "hello\nworld"
44 , testPlain (setWidth (Just 5) $ intercalate_ breakpoint string)
45 ["he", "llo", "world"]
46 "hello\nworld"
47 , testPlain (setWidth (Just 5) $ intercalate_ breakpoint string)
48 ["he", "ll", "o!"]
49 "hell\no!"
50 , testPlain (setWidth (Just 4) $ intercalate_ breakpoint string)
51 ["hello", "world"]
52 "hello\nworld"
53 , testPlain (setWidth (Just 4) $ intercalate_ breakpoint string)
54 ["he", "ll", "o!"]
55 "hell\no!"
56 , testPlain (setWidth (Just 4) $ intercalate_ breakpoint string)
57 ["he", "llo", "world"]
58 "he\nllo\nworld"
59 , testPlain (setWidth (Just 4) $ intercalate_ breakpoint string)
60 ["he", "llo", "w", "orld"]
61 "he\nllow\norld"
62 , testPlain (setWidth (Just 4) $ intercalate_ breakpoint string)
63 ["he", "ll", "o!", "wo", "rl", "d!"]
64 "hell\no!wo\nrld!"
65 , testPlain (setWidth (Just 3) $ intercalate_ breakpoint string)
66 ["hello", "world"]
67 "hello\nworld"
68 , testPlain (setWidth (Just 3) $ intercalate_ breakpoint string)
69 ["he", "ll"]
70 "he\nll"
71 , testPlain (setWidth (Just 3) $ intercalate_ breakpoint string)
72 ["he", "ll", "o!"]
73 "he\nll\no!"
74 , testPlain (setWidth (Just 1) $ intercalate_ breakpoint string)
75 ["he", "ll", "o!"]
76 "he\nll\no!"
77 , testPlain (setWidth (Just 4) $ "__" .> align (intercalate_ breakpoint string))
78 ["he", "ll", "o!", "wo", "rl", "d!"]
79 "__he\n ll\n o!\n wo\n rl\n d!"
80 , testPlain (setWidth (Just 6) $ "__" .> align (intercalate_ breakpoint string))
81 ["he", "ll", "o!", "wo", "rl", "d!"]
82 "__hell\n o!wo\n rld!"
83 , testPlain (setWidth (Just 16) $ "__" .> bracketList string)
84 ["hello", "world"]
85 "__[hello, world]"
86 , testPlain (setWidth (Just 11) $ intercalate_ breakspace string)
87 ["hello", "world"]
88 "hello world"
89 , testPlain (setWidth (Just 10) $ intercalate_ breakspace string)
90 ["hello", "world"]
91 "hello\nworld"
92 , testPlain (setWidth (Just 6) $ intercalate_ breakspace string)
93 ["hel", "lo", "wo", "rld"]
94 "hel lo\nwo rld"
95 , testPlain (setWidth (Just 6) $ intercalate_ breakspace string)
96 ["hel", "lo", "wo", "rld", "HEL", "LO", "WO", "RLD"] "hel lo\nwo rld\nHEL LO\nWO RLD"
97 , testPlain (setWidth (Just 5) $ intercalate_ breakspace string)
98 ["hello", "world"]
99 "hello\nworld"
100 , testPlain (setWidth (Just 7) $ ("hello".>breakspace.>"world"))
101 ()
102 "hello\nworld"
103 , testPlain (setWidth (Just 7) $ ("hello ".>"world"))
104 ()
105 "hello\nworld"
106 , testPlain (" ".> "hello\nworld\n!")
107 ()
108 " hello\nworld\n!"
109 , testPlain ("__".>align "hello\nworld\n!")
110 ()
111 "__hello\n world\n !"
112 , testPlain (hang 2 "hello\nworld\n!") ()
113 "hello\n world\n !"
114 , testPlain (hang 2 "hello\nworld\n!".>"\nhello\n!")
115 ()
116 "hello\n world\n !\nhello\n!"
117 , testPlain (setWidth (Just 10) $ unwords_ int)
118 [1..15]
119 "1 2 3 4 5\n6 7 8 9 10\n11 12 13\n14 15"
120 , testPlain (setWidth (Just 10) $ ("1234567890" .> " ") .> "1")
121 ()
122 "1234567890\n1"
123 -- justify respects concatenating words
124 , testPlain (setWidth (Just 10) $ justify (setWidth (Just 11) ("1 2 3".>"4 5 6 7")))
125 ()
126 "1 2 34 5 6\n7"
127 -- justify flushes the buffer before
128 , testPlain (setWidth (Just 10) $ "__" .> align (justify "1 2 3 4 5"))
129 ()
130 "__1 2 3 4\n 5"
131 , testPlain (setWidth (Just 10) $ justify (bold ("12 34 56 78 ".> underline "90" .> " 123 456 789")))
132 ()
133 "\ESC[1m12 34 56\n78 \ESC[4m90\ESC[0;1m 123\n456 789\ESC[0m"
134 -- handle escaping correctly over custom indenting
135 , testPlain (setWidth (Just 10) $ setIndent (blue "X") 1 (red ("12".>green "4\n5" .> "6")))
136 ()
137 "\ESC[31m12\ESC[32m4\n\ESC[34mX\ESC[0;31;32m5\ESC[0;31m6\ESC[0m"
138 , testPlain (setWidth (Just 10) $ setIndent (blue "X") 1 (justify (red ("1 2 3 4".>green " 5 6 " .> "7 ") .> "8")))
139 ()
140 "\ESC[31m1 2 3 4\ESC[32m 5\n\ESC[34mX\ESC[0;31;32m6 \ESC[0;31m7 \ESC[0m8"
141 -- unorderedList/orderedList are empty when no item
142 , testPlain (unorderedList int) [] ""
143 , testPlain (unorderedList int) [] ""
144 -- endline break spaces
145 , testPlain (setWidth (Just 10) $ ("a".>endline.>" b")) () "a\nb"
146 -- endline does no justify
147 , testPlain (setWidth (Just 10) $ justify ("a b".>endline.>" c")) () "a b\nc"
148 -- endline works overflowed
149 , testPlain (setWidth (Just 10) $ justify ("abcdefghijk".>endline.>" a")) () "abcdefghijk\na"
150 -- endline prints nothing
151 , testPlain (setWidth (Just 10) $ justify ("12345678".>endline.>"90ab".>align (" cdefghijk cdefghijk")))
152 ()
153 "1234567890ab\n\
154 \ cdefghijk\n\
155 \ cdefghijk"
156 -- newline stops overflow
157 , testPlain (setWidth (Just 10) $ breakalt "fits" "over".>"\n".>"12345678901")
158 ()
159 "fits\n\
160 \12345678901"
161 -- breakalt triggers only if its first argument overflows,
162 -- not if what's next overflows.
163 , testPlain (setWidth (Just 10) $ spaces 2.>align(breakalt "fits" "over".>newline.>"12345678901"))
164 ()
165 " fits\n\
166 \ 12345678901"
167 ]
168 ]
169 where
170 testList :: String -> [Assertion] -> TestTree
171 testList n as = testGroup n $ List.zipWith testCase (show <$> [1::Int ..]) as
172 testPlain :: o ~ String => Plain o a -> a -> o -> Assertion
173 testPlain fmt a exp = runPlain fmt a @?= exp