]> Git — Sourcephile - haskell/symantic.git/blob - symantic-document/test/HUnit.hs
Use Nat, instead of convoluted type families.
[haskell/symantic.git] / symantic-document / test / HUnit.hs
1 {-# LANGUAGE OverloadedLists #-}
2 {-# LANGUAGE TypeApplications #-}
3 module HUnit where
4
5 import Test.Tasty
6 import Test.Tasty.HUnit
7
8 import Data.Foldable (Foldable(..))
9 import Data.Function (($))
10 import Data.Functor ((<$>))
11 import Data.Int (Int)
12 import Data.Ord (Ord(..))
13 import Data.Semigroup (Semigroup(..))
14 import Data.String (String)
15 import Text.Show (Show(..))
16 import qualified Data.List as List
17 import qualified Data.Text.Lazy as TL
18
19 import qualified Language.Symantic.Document.Term as Doc
20 import Language.Symantic.Document.Term ((<+>))
21
22 -- * Tests
23 hunits :: TestTree
24 hunits = testGroup "HUnit" $
25 [ hunitsTerm
26 ]
27
28 infix 0 ==>
29 (==>) :: Doc.Term -> TL.Text -> Assertion
30 p ==> expected = got @?= expected
31 where got = Doc.textTerm p
32
33 testList :: String -> [Assertion] -> TestTree
34 testList n as = testGroup n $ List.zipWith testCase (show <$> [1::Int ..]) as
35
36 testMessage :: TL.Text -> String
37 testMessage msg =
38 foldMap esc $ TL.unpack $
39 if 42 < TL.length msg then excerpt else msg
40 where
41 excerpt = TL.take 42 msg <> "…"
42 esc = \case
43 '\n' -> "\\n"
44 c -> [c]
45
46 hunitsTerm :: TestTree
47 hunitsTerm = testGroup "Term"
48 [ testList "Textable"
49 [ Doc.newline ==> "\n"
50 , Doc.stringH "hello" ==> "hello"
51 , "hello" ==> "hello"
52 , Doc.catV @_ @[] ["hello", "world"] ==> "hello\nworld"
53 ]
54 , testList "Alignable"
55 [ "hello\nworld" ==> "hello\nworld"
56 , " "<> "hello\nworld\n!" ==> " hello\nworld\n!"
57 , "__"<>Doc.align "hello\nworld\n!" ==> "__hello\n world\n !"
58 , Doc.hang 2 "hello\nworld\n!" ==> "hello\n world\n !"
59 , Doc.hang 2 "hello\nworld\n!"<>"\nhello\n!" ==> "hello\n world\n !\nhello\n!"
60 , "let " <> Doc.align (Doc.catV $
61 (\(name, typ) -> Doc.fill 6 (Doc.stringH name) <+> "::" <+> Doc.stringH typ)
62 `List.map` [ ("abcdef","Doc")
63 , ("abcde","Int -> Doc -> Doc")
64 , ("abcdefghi","Doc") ])
65 ==> "let abcdef :: Doc\n abcde :: Int -> Doc -> Doc\n abcdefghi :: Doc"
66 , "let " <> Doc.align (Doc.catV $
67 (\(name, typ) -> Doc.breakableFill 6 (Doc.stringH name) $ " ::" <+> Doc.stringH typ)
68 `List.map` [ ("abcdef","Doc")
69 , ("abcde","Int -> Doc -> Doc")
70 , ("abcdefghi","Doc") ])
71 ==> "let abcdef :: Doc\n abcde :: Int -> Doc -> Doc\n abcdefghi\n :: Doc"
72 , "let " <> Doc.align (Doc.catV $
73 (\(name, typ) -> Doc.breakableFill 6 (Doc.stringH name) $ " ::" <+> typ)
74 `List.map` [("abcdefghi","Doc ->\nDoc")])
75 ==> "let abcdefghi\n :: Doc ->\n Doc"
76 ]
77 , testList "Wrapable"
78 [ 10`wc` be ["hello", "world"] ==> "helloworld"
79 , 9`wc` be ["hello", "world"] ==> "hello\nworld"
80 , 6`wc` be ["he", "ll", "o!"] ==> "hello!"
81 , 6`wc` be ["he", "ll", "o!", "wo", "rl", "d!"] ==> "hello!\nworld!"
82 , 5`wc` be ["hello", "world"] ==> "hello\nworld"
83 , 5`wc` be ["he", "llo", "world"] ==> "hello\nworld"
84 , 5`wc` be ["he", "ll", "o!"] ==> "hell\no!"
85 , 4`wc` be ["hello", "world"] ==> "hello\nworld"
86 , 4`wc` be ["he", "ll", "o!"] ==> "hell\no!"
87 , 4`wc` be ["he", "llo", "world"] ==> "he\nllo\nworld"
88 , 4`wc` be ["he", "llo", "w", "orld"] ==> "he\nllow\norld"
89 , 4`wc` be ["he", "ll", "o!", "wo", "rl", "d!"] ==> "hell\no!wo\nrld!"
90 , 3`wc` be ["hello", "world"] ==> "hello\nworld"
91 , 3`wc` be ["he", "ll"] ==> "he\nll"
92 , 3`wc` be ["he", "ll", "o!"] ==> "he\nll\no!"
93 , 1`wc` be ["he", "ll", "o!"] ==> "he\nll\no!"
94 , 4`wc` ["__", Doc.align $ be ["he", "ll", "o!", "wo", "rl", "d!"]] ==> "__he\n ll\n o!\n wo\n rl\n d!"
95 , 6`wc` ["__", Doc.align $ be ["he", "ll", "o!", "wo", "rl", "d!"]] ==> "__hell\n o!wo\n rld!"
96 , 16`wc` ["__", listHorV ["hello", "world"]] ==> "__[hello, world]"
97 , 4`wc` ["__", listHorV ["hello", "world"]] ==> "__[ hello\n , world\n ]"
98 , 11`wc` bs ["hello", "world"] ==> "hello world"
99 , 10`wc` bs ["hello", "world"] ==> "hello\nworld"
100 , 5`wc` bs ["hello", "world"] ==> "hello\nworld"
101 , 19`wc` fun (fun $ fun $ fun $ fun $ listHorV ["abcdefg", "abcdefg"])
102 ==> "function(function(\n function(\n function(\n function(\n [ abcdefg\n , abcdefg\n ]\n )\n )\n )\n ))"
103 , 19`wc` fun (fun $ fun $ fun $ fun $ listHorV ["abcdefgh", "abcdefgh"])
104 ==> "function(\n function(\n function(\n function(\n function(\n [ abcdefgh\n , abcdefgh\n ]\n )\n )\n )\n )\n )"
105 ]
106 ]
107
108 be :: Doc.Wrapable d => [d] -> d
109 be = Doc.foldWith Doc.breakableEmpty
110 bs :: Doc.Wrapable d => [d] -> d
111 bs = Doc.foldWith Doc.breakableSpace
112 wc :: Doc.Wrapable d => Doc.Column -> d -> d
113 wc = Doc.withWrapColumn
114
115 fun :: (Doc.Alignable d, Doc.Wrapable d) => d -> d
116 fun x = "function(" <> Doc.incrIndent 2 (Doc.ifWrap (Doc.newline<>x<>Doc.newline) x) <> ")"
117
118 listHorV :: (Doc.Alignable d, Doc.Wrapable d) => [d] -> d
119 listHorV [] = "[]"
120 listHorV [x] = "["<>x<>"]"
121 listHorV xs =
122 Doc.ifWrap
123 (Doc.align $ "[ " <> foldr1 (\a acc -> a <> Doc.newline <> ", " <> acc) xs <> Doc.newline <> "]")
124 ("[" <> Doc.intercalate ", " xs <> "]")