1 {-# LANGUAGE OverloadedStrings #-}
5 import Test.Tasty.HUnit
7 import Data.Foldable (Foldable(..))
8 import Data.Function (($), (.))
9 import Data.Functor ((<$>))
11 import Data.Maybe (Maybe(..))
12 import Data.Monoid (Monoid(..))
13 import Data.Ord (Ord(..))
14 import Data.Semigroup (Semigroup(..))
15 import Data.String (String, IsString(..))
17 import Text.Show (Show(..))
18 import qualified Data.List as List
20 import Symantic.Document.API
21 import Symantic.Document.Plain
22 import Symantic.Document.AnsiText
26 hunits = testGroup "HUnit" $
30 hunitPlain :: TestTree
31 hunitPlain = testList "Plain"
33 , "hello\nworld" ==> "hello\nworld"
34 , 10`maxWidth` breakpoints ["hello", "world"] ==> "helloworld"
35 , 9`maxWidth` breakpoints ["hello", "world"] ==> "hello\nworld"
36 , 6`maxWidth` breakpoints ["he", "ll", "o!"] ==> "hello!"
37 , 6`maxWidth` breakpoints ["he", "ll", "o!", "wo", "rl", "d!"] ==> "hello!\nworld!"
38 , 5`maxWidth` breakpoints ["hello", "world"] ==> "hello\nworld"
39 , 5`maxWidth` breakpoints ["he", "llo", "world"] ==> "hello\nworld"
40 , 5`maxWidth` breakpoints ["he", "ll", "o!"] ==> "hell\no!"
41 , 4`maxWidth` breakpoints ["hello", "world"] ==> "hello\nworld"
42 , 4`maxWidth` breakpoints ["he", "ll", "o!"] ==> "hell\no!"
43 , 4`maxWidth` breakpoints ["he", "llo", "world"] ==> "he\nllo\nworld"
44 , 4`maxWidth` breakpoints ["he", "llo", "w", "orld"] ==> "he\nllow\norld"
45 , 4`maxWidth` breakpoints ["he", "ll", "o!", "wo", "rl", "d!"] ==> "hell\no!wo\nrld!"
46 , 3`maxWidth` breakpoints ["hello", "world"] ==> "hello\nworld"
47 , 3`maxWidth` breakpoints ["he", "ll"] ==> "he\nll"
48 , 3`maxWidth` breakpoints ["he", "ll", "o!"] ==> "he\nll\no!"
49 , 1`maxWidth` breakpoints ["he", "ll", "o!"] ==> "he\nll\no!"
50 , 4`maxWidth` mconcat ["__", align $ breakpoints ["he", "ll", "o!", "wo", "rl", "d!"]]
51 ==> "__he\n ll\n o!\n wo\n rl\n d!"
52 , 6`maxWidth` mconcat ["__", align $ breakpoints ["he", "ll", "o!", "wo", "rl", "d!"]]
53 ==> "__hell\n o!wo\n rld!"
54 , 16`maxWidth` mconcat ["__", listHorV ["hello", "world"]] ==> "__[hello, world]"
55 , 4`maxWidth` mconcat ["__", listHorV ["hello", "world"]] ==> "__[ hello\n , world\n ]"
56 , 11`maxWidth` breakspaces ["hello", "world"] ==> "hello world"
57 , 10`maxWidth` breakspaces ["hello", "world"] ==> "hello\nworld"
58 , 6`maxWidth` breakspaces ["hel", "lo", "wo", "rld"] ==> "hel lo\nwo rld"
59 , 6`maxWidth` breakspaces ["hel", "lo", "wo", "rld", "HEL", "LO", "WO", "RLD"] ==> "hel lo\nwo rld\nHEL LO\nWO RLD"
60 , 5`maxWidth` breakspaces ["hello", "world"] ==> "hello\nworld"
61 , 19`maxWidth` fun (fun $ fun $ fun $ fun $ listHorV ["abcdefg", "abcdefg"])
62 ==> "function(function(\n function(\n function(\n function(\n [ abcdefg\n , abcdefg\n ]\n )\n )\n )\n ))"
63 , 19`maxWidth` fun (fun $ fun $ fun $ fun $ listHorV ["abcdefgh", "abcdefgh"])
64 ==> "function(\n function(\n function(\n function(\n function(\n [ abcdefgh\n , abcdefgh\n ]\n )\n )\n )\n )\n )"
65 , 7`maxWidth` ("hello"<>breakspace<>"world") ==> "hello\nworld"
66 , 7`maxWidth` ("hello "<>"world") ==> "hello\nworld"
67 , " "<> "hello\nworld\n!" ==> " hello\nworld\n!"
68 , "__"<>align "hello\nworld\n!" ==> "__hello\n world\n !"
69 , hang 2 "hello\nworld\n!" ==> "hello\n world\n !"
70 , hang 2 "hello\nworld\n!"<>"\nhello\n!" ==> "hello\n world\n !\nhello\n!"
71 , "let " <> align (catV $
72 (\(name, typ) -> fill 6 name <+> "::" <+> typ)
73 <$> [ ("abcdef","Doc")
74 , ("abcde","Int -> Doc -> Doc")
75 , ("abcdefghi","Doc") ])
76 ==> "let abcdef :: Doc\n abcde :: Int -> Doc -> Doc\n abcdefghi :: Doc"
77 , "let " <> align (catV $
78 (\(name, typ) -> breakfill 6 name <> " ::" <+> typ)
79 <$> [ ("abcdef","Doc")
80 , ("abcde","Int -> Doc -> Doc")
81 , ("abcdefghi","Doc") ])
82 ==> "let abcdef :: Doc\n abcde :: Int -> Doc -> Doc\n abcdefghi\n :: Doc"
83 , "let " <> align (catV $
84 (\(name, typ) -> breakfill 6 name <> " ::" <+> typ)
85 <$> [("abcdefghi","Doc ->\nDoc")])
86 ==> "let abcdefghi\n :: Doc ->\n Doc"
87 , "let " <> align (catV $
88 (\(name, typ) -> breakfill 6 name <> align (" ::" <+> typ))
89 <$> [("abcdefghi","Doc ->\nDoc")])
90 ==> "let abcdefghi\n :: Doc ->\n Doc"
91 , 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"
92 , 10 `maxWidth` "a b "<>"12"<>align (" 34 5") ==> "a b 12 34\n 5"
93 , 10 `maxWidth` "a b "<>"12"<>align (" 34" <> align "") ==> "a b 12 34"
94 , 10 `maxWidth` "a b "<>"12"<>align (" 34" <> align " ") ==> "a b 12 34 "
95 , 10 `maxWidth` "a b "<>"12"<>align (" 34" <> align " 5") ==> "a b 12 34\n 5"
96 , 10 `maxWidth` "a b "<>"12"<>align (" 34" <> align " 56") ==> "a b 12\n 34\n 56"
97 , 10 `maxWidth` "a b "<>"12"<>align (" 34" <> align " 567") ==> "a b\n12 34 567"
98 , 10 `maxWidth` "a b "<>"12"<>align (" 34" <> align " 5678") ==> "a b\n12 34 5678"
99 , 10 `maxWidth` "a b "<>"12"<>align (" 34" <> align " 56789") ==> "a b\n12 34\n 56789"
100 , 10 `maxWidth` ("1234567890" <> " ") <> "1" ==> "1234567890\n1"
101 , 10 `maxWidth` nestedAlign 6 ==> "1 2 3 4 5\n 6"
102 , 10 `maxWidth` nestedAlign 7 ==> "1 2 3 4\n 5\n 6\n 7"
103 , 10 `maxWidth` nestedAlign 8 ==> "1 2 3\n 4\n 5\n 6\n 7\n 8"
104 , 10 `maxWidth` nestedAlign 9 ==> "1 2\n 3\n 4\n 5\n 6\n 7\n 8\n 9"
105 , 10 `maxWidth` nestedAlign 10 ==> "1\n 2\n 3\n 4\n 5\n 6\n 7\n 8\n 9\n 10"
107 , 10 `maxWidth` justify "1 2 3 4 5 6" ==> "1 2 3 4 5\n6"
108 -- justify compress spaces
109 , 10 `maxWidth` justify "1 2 3 4 5 6" ==> "1 2 3 4 5\n6"
110 -- justify does not overflow the alignment
111 , 10 `maxWidth` justify (nestedAlign 6) ==> "1 2 3 4 5\n 6"
112 , 10 `maxWidth` justify ("a b\n" <> nestedAlign 2) ==> "a b\n1 2"
113 , 10 `maxWidth` justify (bold ("12 34 56 78 "<> underline "90" <> " 123 456 789"))
114 ==> "\ESC[1m12 34 56\n78 \ESC[4m90\ESC[0;1m 123\n456 789\ESC[0m"
115 -- breakspace backtracking is bounded by the removable indentation
116 -- (hence it can actually justify a few words in reasonable time).
118 "Lorem ipsum dolor sit amet, Nulla nec tortor. Donec id elit quis purus\
119 \ consectetur consequat. Nam congue semper tellus. Sed erat dolor,\
120 \ dapibus sit amet, venenatis ornare, ultrices ut, nisi. Aliquam ante.\
121 \ Suspendisse scelerisque dui nec velit. Duis augue augue, gravida euismod,\
122 \ vulputate ac, facilisis id, sem. Morbi in orci. Nulla purus lacus,\
123 \ pulvinar vel, malesuada ac, mattis nec, quam. Nam molestie scelerisque\
124 \ quam. Nullam feugiat cursus lacus.orem ipsum dolor sit amet, consectetur\
125 \ adipiscing elit. Donec libero risus, commodo vitae, pharetra mollis,\
126 \ posuere eu, pede. Nulla nec tortor. Donec id elit quis purus consectetur\
127 \ consequat. Nam congue semper tellus. Sed erat dolor, dapibus sit\
128 \ amet, venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse\
129 \ scelerisque dui nec velit. Duis augue augue, gravida euismod, vulputate ac,\
130 \ facilisis id, sem. Morbi in orci. Nulla purus lacus, pulvinar vel,\
131 \ malesuada ac, mattis nec, quam. Nam molestie scelerisque quam.\
132 \ Nullam feugiat cursus lacus.orem ipsum dolor sit amet, consectetur\
133 \ adipiscing elit. Donec libero risus, commodo vitae, pharetra mollis,\
134 \ posuere eu, pede. Nulla nec tortor. Donec id elit quis purus consectetur\
135 \ consequat. Nam congue semper tellus. Sed erat dolor, dapibus sit amet,\
136 \ venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse\
137 \ scelerisque dui nec velit. Duis augue augue, gravida euismod, vulputate ac,\
138 \ facilisis id, sem. Morbi in orci. Nulla purus lacus, pulvinar vel,\
139 \ malesuada ac, mattis nec, quam. Nam molestie scelerisque quam. Nullam\
140 \ feugiat cursus lacus.orem ipsum dolor sit amet, consectetur adipiscing\
141 \ elit. Donec libero risus, commodo vitae, pharetra mollis, posuere eu, pede.\
142 \ Nulla nec tortor. Donec id elit quis purus consectetur consequat. Nam\
143 \ congue semper tellus. Sed erat dolor, dapibus sit amet, venenatis ornare,\
144 \ ultrices ut, nisi."
145 ==> "Lorem ipsum dolor sit amet, Nulla nec tortor. Donec id elit quis\
146 \ purus\nconsectetur consequat. Nam congue semper tellus. Sed erat dolor, dapibus\
147 \ sit\namet, venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse\
148 \ scelerisque\ndui nec velit. Duis augue augue, gravida euismod, vulputate ac,\
149 \ facilisis id,\nsem. Morbi in orci. Nulla purus lacus, pulvinar vel, malesuada\
150 \ ac, mattis nec,\nquam. Nam molestie scelerisque quam. Nullam feugiat cursus\
151 \ lacus.orem ipsum\ndolor sit amet, consectetur adipiscing elit. Donec libero\
152 \ risus, commodo vitae,\npharetra mollis, posuere eu, pede. Nulla nec tortor.\
153 \ Donec id elit quis purus\nconsectetur consequat. Nam congue semper tellus. Sed\
154 \ erat dolor, dapibus sit\namet, venenatis ornare, ultrices ut, nisi. Aliquam\
155 \ ante. Suspendisse scelerisque\ndui nec velit. Duis augue augue, gravida\
156 \ euismod, vulputate ac, facilisis id,\nsem. Morbi in orci. Nulla purus lacus,\
157 \ pulvinar vel, malesuada ac, mattis nec,\nquam. Nam molestie scelerisque quam.\
158 \ Nullam feugiat cursus lacus.orem ipsum\ndolor sit amet, consectetur adipiscing\
159 \ elit. Donec libero risus, commodo vitae,\npharetra mollis, posuere eu, pede.\
160 \ Nulla nec tortor. Donec id elit quis purus\nconsectetur consequat. Nam congue\
161 \ semper tellus. Sed erat dolor, dapibus sit\namet, venenatis ornare, ultrices\
162 \ ut, nisi. Aliquam ante. Suspendisse scelerisque\ndui nec velit. Duis augue\
163 \ augue, gravida euismod, vulputate ac, facilisis id,\nsem. Morbi in orci. Nulla\
164 \ purus lacus, pulvinar vel, malesuada ac, mattis nec,\nquam. Nam molestie\
165 \ scelerisque quam. Nullam feugiat cursus lacus.orem ipsum\ndolor sit amet,\
166 \ consectetur adipiscing elit. Donec libero risus, commodo vitae,\npharetra\
167 \ mollis, posuere eu, pede. Nulla nec tortor. Donec id elit quis\
168 \ purus\nconsectetur consequat. Nam congue semper tellus. Sed erat dolor, dapibus\
169 \ sit\namet, venenatis ornare, ultrices ut, nisi."
172 (==>) :: IsString d => d ~ String => AnsiText (Plain d) -> d -> Assertion; infix 0 ==>
173 p ==> exp = got @?= exp
174 where got = runPlain $ runAnsiText p
176 testList :: String -> [Assertion] -> TestTree
177 testList n as = testGroup n $ List.zipWith testCase (show <$> [1::Int ..]) as
179 breakpoints :: Wrappable d => Monoid d => [d] -> d
180 breakpoints = intercalate breakpoint
182 breakspaces :: Wrappable d => Monoid d => [d] -> d
183 breakspaces = intercalate breakspace
186 maxWidth :: Wrappable d => Width -> d -> d
187 maxWidth = setWidth . Just
190 DocFrom (Line String) d =>
191 Spaceable d => Indentable d => Wrappable d =>
196 docFrom (Line (show i)) <>
197 (if n <= i then mempty
198 else align (breakspace <> go (i+1)))
200 listHorV :: IsString d => Indentable d => Wrappable d => [d] -> d
202 listHorV [d] = "["<>d<>"]"
205 ("[" <> intercalate ("," <> space) ds <> "]")
206 (align $ "[" <> space
207 <> foldr1 (\a acc -> a <> newline <> "," <> space <> acc) ds
210 fun :: IsString d => Indentable d => Wrappable d => d -> d
211 fun d = "function(" <> incrIndent 2 (breakalt d (newline<>d<>newline)) <> ")"