]> Git — Sourcephile - haskell/symantic-document.git/blob - tests/HUnit.hs
iface: change to a typed representation
[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.Document.Class
19 import Symantic.Document.Plain (Plain, runPlain)
20
21 -- * Tests
22 hunits :: TestTree
23 hunits = testGroup "HUnit" $
24 [ hunitPlain
25 ]
26
27 hunitPlain :: TestTree
28 hunitPlain = testList "Plain"
29 [ newline ==> "\n"
30 , "hello".>"world" ==> "helloworld"
31 , "hello".>newline.>"world" ==> "hello\nworld"
32 , "hello\nworld" ==> "hello\nworld"
33 , 10`maxWidth` breakpoints ["hello", "world"] ==> "helloworld"
34 , 9`maxWidth` "hello" .> breakpoint .> "world" ==> "hello\nworld"
35 , 6`maxWidth` breakpoints ["he", "ll", "o!"] ==> "hello!"
36 , 6`maxWidth` breakpoints ["he", "ll", "o!", "wo", "rl", "d!"] ==> "hello!\nworld!"
37 , 5`maxWidth` breakpoints ["hello", "world"] ==> "hello\nworld"
38 , 5`maxWidth` breakpoints ["he", "llo", "world"] ==> "hello\nworld"
39 , 5`maxWidth` breakpoints ["he", "ll", "o!"] ==> "hell\no!"
40 , 4`maxWidth` breakpoints ["hello", "world"] ==> "hello\nworld"
41 , 4`maxWidth` breakpoints ["he", "ll", "o!"] ==> "hell\no!"
42 , 4`maxWidth` breakpoints ["he", "llo", "world"] ==> "he\nllo\nworld"
43 , 4`maxWidth` breakpoints ["he", "llo", "w", "orld"] ==> "he\nllow\norld"
44 , 4`maxWidth` breakpoints ["he", "ll", "o!", "wo", "rl", "d!"] ==> "hell\no!wo\nrld!"
45 , 3`maxWidth` breakpoints ["hello", "world"] ==> "hello\nworld"
46 , 3`maxWidth` breakpoints ["he", "ll"] ==> "he\nll"
47 , 3`maxWidth` breakpoints ["he", "ll", "o!"] ==> "he\nll\no!"
48 , 1`maxWidth` breakpoints ["he", "ll", "o!"] ==> "he\nll\no!"
49 , 4`maxWidth` concat ["__", align $ breakpoints ["he", "ll", "o!", "wo", "rl", "d!"]]
50 ==> "__he\n ll\n o!\n wo\n rl\n d!"
51 , testPlain
52 (4`maxWidth` "__" .> align (intercalate_ breakpoint string))
53 ["he", "ll", "o!", "wo", "rl", "d!"]
54 "__he\n ll\n o!\n wo\n rl\n d!"
55 , 6`maxWidth` concat ["__", align $ breakpoints ["he", "ll", "o!", "wo", "rl", "d!"]]
56 ==> "__hell\n o!wo\n rld!"
57 , testPlain
58 (6`maxWidth` "__" .> align (intercalate_ breakpoint string))
59 ["he", "ll", "o!", "wo", "rl", "d!"]
60 "__hell\n o!wo\n rld!"
61 , 16`maxWidth` concat ["__", listHorV ["hello", "world"]] ==> "__[hello, world]"
62 , testPlain
63 (16`maxWidth` "__" .> bracketList string)
64 ["hello", "world"]
65 "__[hello, world]"
66 , 4`maxWidth` concat ["__", listHorV ["hello", "world"]] ==> "__[ hello\n , world\n ]"
67 , 11`maxWidth` breakspaces ["hello", "world"] ==> "hello world"
68 , 10`maxWidth` breakspaces ["hello", "world"] ==> "hello\nworld"
69 , 6`maxWidth` breakspaces ["hel", "lo", "wo", "rld"] ==> "hel lo\nwo rld"
70 , 6`maxWidth` breakspaces ["hel", "lo", "wo", "rld", "HEL", "LO", "WO", "RLD"] ==> "hel lo\nwo rld\nHEL LO\nWO RLD"
71 , 5`maxWidth` breakspaces ["hello", "world"] ==> "hello\nworld"
72 , 19`maxWidth` fun (fun $ fun $ fun $ fun $ listHorV ["abcdefg", "abcdefg"])
73 ==> "function(function(\n function(\n function(\n function(\n [ abcdefg\n , abcdefg\n ]\n )\n )\n )\n ))"
74 , 19`maxWidth` fun (fun $ fun $ fun $ fun $ listHorV ["abcdefgh", "abcdefgh"])
75 ==> "function(\n function(\n function(\n function(\n function(\n [ abcdefgh\n , abcdefgh\n ]\n )\n )\n )\n )\n )"
76 , 7`maxWidth` ("hello".>breakspace.>"world") ==> "hello\nworld"
77 , 7`maxWidth` ("hello ".>"world") ==> "hello\nworld"
78 , " ".> "hello\nworld\n!" ==> " hello\nworld\n!"
79 , "__".>align "hello\nworld\n!" ==> "__hello\n world\n !"
80 , hang 2 "hello\nworld\n!" ==> "hello\n world\n !"
81 , hang 2 "hello\nworld\n!".>"\nhello\n!" ==> "hello\n world\n !\nhello\n!"
82 , "let " .> align (catV $
83 (\(name, typ) -> fill 6 name <+ "::" +> typ)
84 <$> [ ("abcdef","Doc")
85 , ("abcde","Int -> Doc -> Doc")
86 , ("abcdefghi","Doc") ])
87 ==> "let abcdef :: Doc\n abcde :: Int -> Doc -> Doc\n abcdefghi :: Doc"
88 , "let " .> align (catV $
89 (\(name, typ) -> fillOrBreak 6 name <. " ::" +> typ)
90 <$> [ ("abcdef","Doc")
91 , ("abcde","Int -> Doc -> Doc")
92 , ("abcdefghi","Doc") ])
93 ==> "let abcdef :: Doc\n abcde :: Int -> Doc -> Doc\n abcdefghi\n :: Doc"
94 , "let " .> align (catV $
95 (\(name, typ) -> fillOrBreak 6 name <. " ::" +> typ)
96 <$> [("abcdefghi","Doc ->\nDoc")])
97 ==> "let abcdefghi\n :: Doc ->\n Doc"
98 , "let " .> align (catV $
99 (\(name, typ) -> fillOrBreak 6 name <. align (" ::" +> typ))
100 <$> [("abcdefghi","Doc ->\nDoc")])
101 ==> "let abcdefghi\n :: Doc ->\n Doc"
102 , 10 `maxWidth` "1 2 3 4 5 6 7 8 9 10 11 12 13 14 15" ==> "1 2 3 4 5\n6 7 8 9 10\n11 12 13\n14 15"
103 , 10 `maxWidth` "a b ".>"12".>align (" 34 5") ==> "a b 12 34\n 5"
104 , 10 `maxWidth` "a b ".>"12".>align (" 34" .> align "") ==> "a b 12 34"
105 , 10 `maxWidth` "a b ".>"12".>align (" 34" .> align " ") ==> "a b 12 34 "
106 , 10 `maxWidth` "a b ".>"12".>align (" 34" .> align " 5") ==> "a b 12 34\n 5"
107 , 10 `maxWidth` "a b ".>"12".>align (" 34" .> align " 56") ==> "a b 12\n 34\n 56"
108 , 10 `maxWidth` "a b ".>"12".>align (" 34" .> align " 567") ==> "a b\n12 34 567"
109 , 10 `maxWidth` "a b ".>"12".>align (" 34" .> align " 5678") ==> "a b\n12 34 5678"
110 , 10 `maxWidth` "a b ".>"12".>align (" 34" .> align " 56789") ==> "a b\n12 34\n 56789"
111 , 10 `maxWidth` ("1234567890" .> " ") .> "1" ==> "1234567890\n1"
112 , 10 `maxWidth` nestedAlign 6 ==> "1 2 3 4 5\n 6"
113 , 10 `maxWidth` nestedAlign 7 ==> "1 2 3 4\n 5\n 6\n 7"
114 , 10 `maxWidth` nestedAlign 8 ==> "1 2 3\n 4\n 5\n 6\n 7\n 8"
115 , 10 `maxWidth` nestedAlign 9 ==> "1 2\n 3\n 4\n 5\n 6\n 7\n 8\n 9"
116 , 10 `maxWidth` nestedAlign 10 ==> "1\n 2\n 3\n 4\n 5\n 6\n 7\n 8\n 9\n 10"
117 -- justify justifies
118 , 10 `maxWidth` justify "1 2 3 4 5 6" ==> "1 2 3 4 5\n6"
119 -- justify compresses spaces
120 , 10 `maxWidth` justify "1 2 3 4 5 6" ==> "1 2 3 4 5\n6"
121 , 10 `maxWidth` justify " 1 2 3 4 5 6 7 8 9" ==> " 1 2 3 4 5\n6 7 8 9"
122 -- justify respects concatenating words
123 , 10 `maxWidth` justify (setWidth (Just 11) ("1 2 3".>"4 5 6 7")) ==> "1 2 34 5 6\n7"
124 -- justify flushes the buffer before
125 , 10 `maxWidth` "__" .> align (justify "1 2 3 4 5") ==> "__1 2 3 4\n 5"
126 -- justify does not overflow the alignment
127 , 10 `maxWidth` justify (nestedAlign 6) ==> "1 2 3 4 5\n 6"
128 , 10 `maxWidth` justify ("a b c de " .> nestedAlign 2) ==> "a b c de\n1 2"
129 , 10 `maxWidth` justify (bold ("12 34 56 78 ".> underline "90" .> " 123 456 789"))
130 ==> "\ESC[1m12 34 56\n78 \ESC[4m90\ESC[0;1m 123\n456 789\ESC[0m"
131 -- justify does not justify on explicit newlines
132 , 10 `maxWidth` justify "1 2 3 4 5 6 7\n8 9 1 2 3 4 5" ==> "1 2 3 4 5\n6 7\n8 9 1 2 3\n4 5"
133 -- align flushes the buffer
134 , 10 `maxWidth` justify (ul ["1 2 3 4 5 6 7 8 9"])
135 ==> "- 1 2 3 4\n\
136 \ 5 6 7 8\n\
137 \ 9"
138 -- ul/ol is empty when no item
139 , ul [] ==> ""
140 , ol [] ==> ""
141 -- ul flushes the buffer
142 , 10 `maxWidth` justify (let i = "1 2 3 4 5 6 7 8 9" in ul [i, i])
143 ==> "- 1 2 3 4\n\
144 \ 5 6 7 8\n\
145 \ 9\n\
146 \- 1 2 3 4\n\
147 \ 5 6 7 8\n\
148 \ 9"
149 , testPlain (10 `maxWidth` justify (unorderedList (unwords_ int))) (let i = [1..9] in [i, i])
150 "- 1 2 3 4\n\
151 \ 5 6 7 8\n\
152 \ 9\n\
153 \- 1 2 3 4\n\
154 \ 5 6 7 8\n\
155 \ 9"
156 , testPlain (11 `maxWidth` justify (orderedList (unwords_ int))) (let i = [1..9] in [i, i])
157 "1. 1 2 3 4\n\
158 \ 5 6 7 8\n\
159 \ 9\n\
160 \2. 1 2 3 4\n\
161 \ 5 6 7 8\n\
162 \ 9"
163 , 10 `maxWidth` justify (let i = "1 2 3 4 5 6 7 8 9" in
164 ul [ul [i, i], ul [i, i]])
165 ==> "- - 1 2 3\n\
166 \ 4 5 6\n\
167 \ 7 8 9\n\
168 \ - 1 2 3\n\
169 \ 4 5 6\n\
170 \ 7 8 9\n\
171 \- - 1 2 3\n\
172 \ 4 5 6\n\
173 \ 7 8 9\n\
174 \ - 1 2 3\n\
175 \ 4 5 6\n\
176 \ 7 8 9"
177 , 10 `maxWidth` justify (let i = "1 2 3 4 5 6 7 8 9" in
178 ol [ol [i, i], ol [i, i]])
179 ==> "1. 1. 1 2\n\
180 \ 3 4\n\
181 \ 5 6\n\
182 \ 7 8\n\
183 \ 9\n\
184 \ 2. 1 2\n\
185 \ 3 4\n\
186 \ 5 6\n\
187 \ 7 8\n\
188 \ 9\n\
189 \2. 1. 1 2\n\
190 \ 3 4\n\
191 \ 5 6\n\
192 \ 7 8\n\
193 \ 9\n\
194 \ 2. 1 2\n\
195 \ 3 4\n\
196 \ 5 6\n\
197 \ 7 8\n\
198 \ 9"
199 -- endline breakspaces
200 , 10 `maxWidth` ("a".>endline.>" b") ==> "a\nb"
201 -- endline does no justify
202 , 10 `maxWidth` justify ("a b".>endline.>" c") ==> "a b\nc"
203 -- endline works overflowed
204 , 10 `maxWidth` justify ("abcdefghijk".>endline.>" a") ==> "abcdefghijk\na"
205 -- endline prints no nothing
206 , 10 `maxWidth` justify ("12345678".>endline.>"90ab".>align (" cdefghijk cdefghijk"))
207 ==> "1234567890ab\n\
208 \ cdefghijk\n\
209 \ cdefghijk"
210 -- newline stops overflow
211 , 10 `maxWidth` breakalt "fits" "over".>"\n".>"12345678901"
212 ==> "fits\n\
213 \12345678901"
214 -- breakalt triggers only if its first argument overflows,
215 -- not if what's next overflows.
216 , 10 `maxWidth` spaces 2.>align(breakalt "fits" "over".>newline.>"12345678901")
217 ==> " fits\n\
218 \ 12345678901"
219 -- handle escaping correctly over custom indenting
220 , 10 `maxWidth` setIndent (blue "X") 1 (red ("12".>green "4\n5" .> "6"))
221 ==> "\ESC[31m12\ESC[32m4\n\ESC[34mX\ESC[0;31;32m5\ESC[0;31m6\ESC[0m"
222 , 10 `maxWidth` setIndent (blue "X") 1 (justify (red ("1 2 3 4".>green " 5 6 " .> "7 ") .> "8"))
223 ==> "\ESC[31m1 2 3 4\ESC[32m 5\n\ESC[34mX\ESC[0;31;32m6 \ESC[0;31m7 \ESC[0m8"
224 -- breakspace backtracking is bounded by the removable indentation
225 -- (hence it can actually wrap a few words in reasonable time).
226 , 80 `maxWidth`
227 "Lorem ipsum dolor sit amet, Nulla nec tortor. Donec id elit quis purus\
228 \ consectetur consequat. Nam congue semper tellus. Sed erat dolor,\
229 \ dapibus sit amet, venenatis ornare, ultrices ut, nisi. Aliquam ante.\
230 \ Suspendisse scelerisque dui nec velit. Duis augue augue, gravida euismod,\
231 \ vulputate ac, facilisis id, sem. Morbi in orci. Nulla purus lacus,\
232 \ pulvinar vel, malesuada ac, mattis nec, quam. Nam molestie scelerisque\
233 \ quam. Nullam feugiat cursus lacus.orem ipsum dolor sit amet, consectetur\
234 \ adipiscing elit. Donec libero risus, commodo vitae, pharetra mollis,\
235 \ posuere eu, pede. Nulla nec tortor. Donec id elit quis purus consectetur\
236 \ consequat. Nam congue semper tellus. Sed erat dolor, dapibus sit\
237 \ amet, venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse\
238 \ scelerisque dui nec velit. Duis augue augue, gravida euismod, vulputate ac,\
239 \ facilisis id, sem. Morbi in orci. Nulla purus lacus, pulvinar vel,\
240 \ malesuada ac, mattis nec, quam. Nam molestie scelerisque quam.\
241 \ Nullam feugiat cursus lacus.orem ipsum dolor sit amet, consectetur\
242 \ adipiscing elit. Donec libero risus, commodo vitae, pharetra mollis,\
243 \ posuere eu, pede. Nulla nec tortor. Donec id elit quis purus consectetur\
244 \ consequat. Nam congue semper tellus. Sed erat dolor, dapibus sit amet,\
245 \ venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse\
246 \ scelerisque dui nec velit. Duis augue augue, gravida euismod, vulputate ac,\
247 \ facilisis id, sem. Morbi in orci. Nulla purus lacus, pulvinar vel,\
248 \ malesuada ac, mattis nec, quam. Nam molestie scelerisque quam. Nullam\
249 \ feugiat cursus lacus.orem ipsum dolor sit amet, consectetur adipiscing\
250 \ elit. Donec libero risus, commodo vitae, pharetra mollis, posuere eu, pede.\
251 \ Nulla nec tortor. Donec id elit quis purus consectetur consequat. Nam\
252 \ congue semper tellus. Sed erat dolor, dapibus sit amet, venenatis ornare,\
253 \ ultrices ut, nisi."
254 ==> "Lorem ipsum dolor sit amet, Nulla nec tortor. Donec id elit quis\
255 \ purus\nconsectetur consequat. Nam congue semper tellus. Sed erat dolor, dapibus\
256 \ sit\namet, venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse\
257 \ scelerisque\ndui nec velit. Duis augue augue, gravida euismod, vulputate ac,\
258 \ facilisis id,\nsem. Morbi in orci. Nulla purus lacus, pulvinar vel, malesuada\
259 \ ac, mattis nec,\nquam. Nam molestie scelerisque quam. Nullam feugiat cursus\
260 \ lacus.orem ipsum\ndolor sit amet, consectetur adipiscing elit. Donec libero\
261 \ risus, commodo vitae,\npharetra mollis, posuere eu, pede. Nulla nec tortor.\
262 \ Donec id elit quis purus\nconsectetur consequat. Nam congue semper tellus. Sed\
263 \ erat dolor, dapibus sit\namet, venenatis ornare, ultrices ut, nisi. Aliquam\
264 \ ante. Suspendisse scelerisque\ndui nec velit. Duis augue augue, gravida\
265 \ euismod, vulputate ac, facilisis id,\nsem. Morbi in orci. Nulla purus lacus,\
266 \ pulvinar vel, malesuada ac, mattis nec,\nquam. Nam molestie scelerisque quam.\
267 \ Nullam feugiat cursus lacus.orem ipsum\ndolor sit amet, consectetur adipiscing\
268 \ elit. Donec libero risus, commodo vitae,\npharetra mollis, posuere eu, pede.\
269 \ Nulla nec tortor. Donec id elit quis purus\nconsectetur consequat. Nam congue\
270 \ semper tellus. Sed erat dolor, dapibus sit\namet, venenatis ornare, ultrices\
271 \ ut, nisi. Aliquam ante. Suspendisse scelerisque\ndui nec velit. Duis augue\
272 \ augue, gravida euismod, vulputate ac, facilisis id,\nsem. Morbi in orci. Nulla\
273 \ purus lacus, pulvinar vel, malesuada ac, mattis nec,\nquam. Nam molestie\
274 \ scelerisque quam. Nullam feugiat cursus lacus.orem ipsum\ndolor sit amet,\
275 \ consectetur adipiscing elit. Donec libero risus, commodo vitae,\npharetra\
276 \ mollis, posuere eu, pede. Nulla nec tortor. Donec id elit quis\
277 \ purus\nconsectetur consequat. Nam congue semper tellus. Sed erat dolor, dapibus\
278 \ sit\namet, venenatis ornare, ultrices ut, nisi."
279 , 80 `maxWidth` justify
280 "Lorem ipsum dolor sit amet, Nulla nec tortor. Donec id elit quis purus\
281 \ consectetur consequat. Nam congue semper tellus. Sed erat dolor,\
282 \ dapibus sit amet, venenatis ornare, ultrices ut, nisi. Aliquam ante.\
283 \ Suspendisse scelerisque dui nec velit. Duis augue augue, gravida euismod,\
284 \ vulputate ac, facilisis id, sem. Morbi in orci. Nulla purus lacus,\
285 \ pulvinar vel, malesuada ac, mattis nec, quam. Nam molestie scelerisque\
286 \ quam. Nullam feugiat cursus lacus.orem ipsum dolor sit amet, consectetur\
287 \ adipiscing elit. Donec libero risus, commodo vitae, pharetra mollis,\
288 \ posuere eu, pede. Nulla nec tortor. Donec id elit quis purus consectetur\
289 \ consequat. Nam congue semper tellus. Sed erat dolor, dapibus sit\
290 \ amet, venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse\
291 \ scelerisque dui nec velit. Duis augue augue, gravida euismod, vulputate ac,\
292 \ facilisis id, sem. Morbi in orci. Nulla purus lacus, pulvinar vel,\
293 \ malesuada ac, mattis nec, quam. Nam molestie scelerisque quam.\
294 \ Nullam feugiat cursus lacus.orem ipsum dolor sit amet, consectetur\
295 \ adipiscing elit. Donec libero risus, commodo vitae, pharetra mollis,\
296 \ posuere eu, pede. Nulla nec tortor. Donec id elit quis purus consectetur\
297 \ consequat. Nam congue semper tellus. Sed erat dolor, dapibus sit amet,\
298 \ venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse\
299 \ scelerisque dui nec velit. Duis augue augue, gravida euismod, vulputate ac,\
300 \ facilisis id, sem. Morbi in orci. Nulla purus lacus, pulvinar vel,\
301 \ malesuada ac, mattis nec, quam. Nam molestie scelerisque quam. Nullam\
302 \ feugiat cursus lacus.orem ipsum dolor sit amet, consectetur adipiscing\
303 \ elit. Donec libero risus, commodo vitae, pharetra mollis, posuere eu, pede.\
304 \ Nulla nec tortor. Donec id elit quis purus consectetur consequat. Nam\
305 \ congue semper tellus. Sed erat dolor, dapibus sit amet, venenatis ornare,\
306 \ ultrices ut, nisi."
307 ==> "Lorem ipsum dolor sit amet, Nulla nec tortor. Donec id elit quis purus\n\
308 \consectetur consequat. Nam congue semper tellus. Sed erat dolor, dapibus sit\n\
309 \amet, venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse scelerisque\n\
310 \dui nec velit. Duis augue augue, gravida euismod, vulputate ac, facilisis id,\n\
311 \sem. Morbi in orci. Nulla purus lacus, pulvinar vel, malesuada ac, mattis nec,\n\
312 \quam. Nam molestie scelerisque quam. Nullam feugiat cursus lacus.orem ipsum\n\
313 \dolor sit amet, consectetur adipiscing elit. Donec libero risus, commodo vitae,\n\
314 \pharetra mollis, posuere eu, pede. Nulla nec tortor. Donec id elit quis purus\n\
315 \consectetur consequat. Nam congue semper tellus. Sed erat dolor, dapibus sit\n\
316 \amet, venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse scelerisque\n\
317 \dui nec velit. Duis augue augue, gravida euismod, vulputate ac, facilisis id,\n\
318 \sem. Morbi in orci. Nulla purus lacus, pulvinar vel, malesuada ac, mattis nec,\n\
319 \quam. Nam molestie scelerisque quam. Nullam feugiat cursus lacus.orem ipsum\n\
320 \dolor sit amet, consectetur adipiscing elit. Donec libero risus, commodo vitae,\n\
321 \pharetra mollis, posuere eu, pede. Nulla nec tortor. Donec id elit quis purus\n\
322 \consectetur consequat. Nam congue semper tellus. Sed erat dolor, dapibus sit\n\
323 \amet, venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse scelerisque\n\
324 \dui nec velit. Duis augue augue, gravida euismod, vulputate ac, facilisis id,\n\
325 \sem. Morbi in orci. Nulla purus lacus, pulvinar vel, malesuada ac, mattis nec,\n\
326 \quam. Nam molestie scelerisque quam. Nullam feugiat cursus lacus.orem ipsum\n\
327 \dolor sit amet, consectetur adipiscing elit. Donec libero risus, commodo vitae,\n\
328 \pharetra mollis, posuere eu, pede. Nulla nec tortor. Donec id elit quis purus\n\
329 \consectetur consequat. Nam congue semper tellus. Sed erat dolor, dapibus sit\n\
330 \amet, venenatis ornare, ultrices ut, nisi."
331 ]
332 where
333 (==>) :: IsString o => o ~ String => Plain o () -> o -> Assertion; infix 0 ==>
334 fmt ==> exp = got @?= exp
335 where got = runPlain fmt ()
336 testPlain :: IsString o => o ~ String => Plain o a -> a -> o -> Assertion
337 testPlain fmt a exp = got @?= exp
338 where got = runPlain fmt a
339
340 testList :: String -> [Assertion] -> TestTree
341 testList n as = testGroup n $ List.zipWith testCase (show <$> [1::Int ..]) as
342
343 breakpoints ::
344 Emptyable repr =>
345 ProductFunctor repr =>
346 Wrappable repr =>
347 [repr ()] -> repr ()
348 breakpoints = intercalate breakpoint
349
350 breakspaces ::
351 Emptyable repr =>
352 ProductFunctor repr =>
353 Wrappable repr =>
354 [repr ()] -> repr ()
355 breakspaces = intercalate breakspace
356
357 infix 1 `maxWidth`
358 maxWidth :: Wrappable repr => Width -> repr a -> repr a
359 maxWidth = setWidth . Just
360
361 nestedAlign ::
362 IsString (repr ()) =>
363 Indentable repr =>
364 Emptyable repr =>
365 ProductFunctor repr =>
366 Wrappable repr =>
367 Int -> repr ()
368 nestedAlign n = go 1
369 where
370 go i =
371 fromString (show i) .>
372 (if n <= i then empty
373 else align (breakspace .> go (i+1)))
374
375 listHorV ::
376 IsString (repr ()) =>
377 Emptyable repr =>
378 Wrappable repr =>
379 ProductFunctor repr =>
380 Indentable repr =>
381 Newlineable repr =>
382 [repr ()] -> repr ()
383 listHorV [] = "[]"
384 listHorV [t] = "[".>t<."]"
385 listHorV ts =
386 breakalt
387 ("[" .> intercalate ("," .> space) ts <. "]")
388 (align $ "[" .> space
389 .> foldr1 (\a acc -> a <. newline <. "," <. space <. acc) ts
390 <. newline <. "]")
391
392 fun ::
393 Wrappable repr =>
394 ProductFunctor repr =>
395 Indentable repr =>
396 Newlineable repr =>
397 IsString (repr ()) =>
398 repr a -> repr a
399 fun t = "function("
400 .> incrIndent (spaces 2) 2 (breakalt t (newline.>t<.newline))
401 <. ")"