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