]> Git — Sourcephile - haskell/symantic-document.git/blob - tests/Golden.hs
tests: move some units to goldens
[haskell/symantic-document.git] / tests / Golden.hs
1 {-# LANGUAGE ExistentialQuantification #-}
2 module Golden where
3
4 import Control.Monad (Monad(..))
5 import Data.Char (Char)
6 import Data.Function (($))
7 import Data.Int (Int)
8 import Data.Maybe (Maybe(..))
9 import Data.Ord (Ord(..))
10 import Data.Semigroup (Semigroup(..))
11 import Data.String (IsString(..), String)
12 import Prelude (succ)
13 import System.IO (FilePath)
14 import System.IO.Unsafe (unsafePerformIO)
15 import Test.Tasty
16 import Test.Tasty.Golden
17 import Text.Printf (printf)
18 import Text.Show (Show(..))
19 import qualified Data.List as List
20
21 import Paths_symantic_formatter
22 import Symantic.Formatter
23
24 golden :: TestTree
25 golden =
26 testGroup "Golden"
27 [ testGroup "Plain" $
28 (\f -> List.zipWith f goldens [1::Int ..]) $ \(Golden fmt inps) fmtNum ->
29 let fmtDir = printf "Format%03d" fmtNum in
30 testGroup fmtDir $
31 (\f -> List.zipWith f inps [1::Int ..]) $ \inp inpNum ->
32 let plainFile = getGoldenDir $ printf "Plain/%s/Input%02d.expected.txt" fmtDir inpNum in
33 goldenVsStringDiff
34 (printf "Input%02d" inpNum) goldenDiff plainFile $ do
35 return $ fromString $ runPlain fmt inp
36 ]
37
38 getGoldenDir :: FilePath -> FilePath
39 getGoldenDir p = unsafePerformIO $ getDataFileName $ "tests/Golden/" <> p
40
41 goldenDiff :: FilePath -> FilePath -> [String]
42 goldenDiff ref new = ["diff", "-u", "-w", "-B", ref, new]
43
44 data Golden repr = forall inp. Golden (repr inp) [inp]
45 goldens ::
46 Indentable repr =>
47 Inferable Char repr =>
48 Inferable Int repr =>
49 Inferable String repr =>
50 IsString (repr ()) =>
51 Justifiable repr =>
52 Listable repr =>
53 Newlineable repr =>
54 Repeatable repr =>
55 Decorable repr =>
56 Voidable repr =>
57 Wrappable repr =>
58 [Golden repr]
59 goldens =
60 [ let fun t = "function("
61 .> breakalt t (incrIndent (spaces 2) 2 (newline.>t)<.newline)
62 <. ")" in
63 Golden
64 ( setWidth (Just 19) $ fun $ fun $ fun $ fun $ fun $ bracketList (many int)
65 )
66 [ [[1..9], [1..9]]
67 , [[0..9], [0..9]]
68 ]
69 , Golden
70 ( setWidth (Just 10) $
71 justify (unorderedList (unwords_ int))
72 )
73 [ [[1..9], [1..9]] ]
74 , Golden
75 ( setWidth (Just 11) $
76 justify (orderedList (unwords_ int))
77 )
78 [ [[1..9], [1..9]] ]
79 , Golden
80 (setWidth (Just 10) $
81 justify (unorderedList (unorderedList (unwords_ int))))
82 [ [ [[1..9], [1..9]], [[1..9], [1..9]] ] ]
83 , Golden (setWidth (Just 80) string) [ lorem ]
84 -- breakspace backtracking is bounded by the removable indentation
85 -- (hence it can actually wrap a few words in reasonable time).
86 , Golden (setWidth (Just 80) (justify string)) [ lorem ]
87 , Golden
88 ("let"+>align (unlines_ (fill 6 string<+ "::" <+>string)))
89 [
90 [ ("abcdef","Char")
91 , ("abcde","Int -> Char -> Char")
92 , ("abcdefghi","Char")
93 ]
94 ]
95 , Golden
96 ("let"+>align (unlines_ (fillOrBreak 6 string<+"::"<+>align string)))
97 [
98 [ ("abcdef","Char")
99 , ("abcde","Int -> Char -> Char")
100 , ("abcdefghi","Char ->\nChar")
101 ]
102 ]
103 , Golden (setWidth (Just 10) $ nestedAlign 6) [()]
104 , Golden (setWidth (Just 10) $ nestedAlign 7) [()]
105 , Golden (setWidth (Just 10) $ nestedAlign 8) [()]
106 , Golden (setWidth (Just 10) $ nestedAlign 9) [()]
107 , Golden (setWidth (Just 10) $ nestedAlign 10) [()]
108 , Golden (setWidth (Just 10) $ justify $ string <. nestedAlign 2)
109 [ ""
110 , "a b c de "
111 ]
112 , Golden (setWidth (Just 10) $ justify string)
113 -- justify justifies
114 [ "1 2 3 4 5 6"
115 -- justify compresses enclosed spaces
116 , "1 2 3 4 5 6"
117 , " 1 2 3 4 5 6 7 8 9"
118 , " 1 2 3 4 5 6 7 8 9"
119 , "1 2 3 4 5 6 7 8 9 "
120 , "1 2 3 4 5 6 7 8 9 "
121 -- justify does not justify on explicit newlines
122 , "1 2 3 4 5 6 7\n8 9 1 2 3 4 5"
123 ]
124 , Golden (setWidth (Just 10) $ "a b ".> "12" .> align string <.> align string)
125 [ (" 34 5", "")
126 , (" 34", "")
127 , (" 34", " ")
128 , (" 34", " 5")
129 , (" 34", " 56")
130 , (" 34", " 567")
131 , (" 34", " 5678")
132 , (" 34", " 56789")
133 ]
134 -- align flushes the buffer
135 , Golden (setWidth (Just 10) $ justify $ unorderedList $ unwords_ int)
136 [ [[1..9]] ]
137 -- unorderedList flushes the buffer
138 , Golden (setWidth (Just 10) $ justify $ unorderedList $ unwords_ int)
139 [ [[1..9], [1..9]]
140 , [[1..19], [1..19]]
141 , [[100000000..100000009], [100000000..100000009]]
142 , [[1000000000..1000000009], [1000000000..1000000009]]
143 ]
144 , Golden (setWidth (Just 10) $ justify $ unorderedList $ unorderedList $ unwords_ int)
145 [ [ [ [1..9], [1..9] ], [ [1..9], [1..9] ] ] ]
146 , Golden (setWidth (Just 10) $ justify $ orderedList $ orderedList $ unwords_ int)
147 [ [ [ [1..9], [1..9] ], [ [1..9], [1..9] ] ] ]
148 ]
149
150 nestedAlign ::
151 Indentable repr =>
152 Wrappable repr =>
153 IsString (repr ()) =>
154 Int -> repr a
155 nestedAlign n = go 1
156 where
157 go i =
158 fromString (show i) .>
159 (if n <= i
160 then empty
161 else align (breakspace .> go (succ i)))
162
163 lorem :: String
164 lorem =
165 "Lorem ipsum dolor sit amet, Nulla nec tortor. Donec id elit quis purus\
166 \ consectetur consequat. Nam congue semper tellus. Sed erat dolor,\
167 \ dapibus sit amet, venenatis ornare, ultrices ut, nisi. Aliquam ante.\
168 \ Suspendisse scelerisque dui nec velit. Duis augue augue, gravida euismod,\
169 \ vulputate ac, facilisis id, sem. Morbi in orci. Nulla purus lacus,\
170 \ pulvinar vel, malesuada ac, mattis nec, quam. Nam molestie scelerisque\
171 \ quam. Nullam feugiat cursus lacus.orem ipsum dolor sit amet, consectetur\
172 \ adipiscing elit. Donec libero risus, commodo vitae, pharetra mollis,\
173 \ posuere eu, pede. Nulla nec tortor. Donec id elit quis purus consectetur\
174 \ consequat. Nam congue semper tellus. Sed erat dolor, dapibus sit\
175 \ amet, venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse\
176 \ scelerisque dui nec velit. Duis augue augue, gravida euismod, vulputate ac,\
177 \ facilisis id, sem. Morbi in orci. Nulla purus lacus, pulvinar vel,\
178 \ malesuada ac, mattis nec, quam. Nam molestie scelerisque quam.\
179 \ Nullam feugiat cursus lacus.orem ipsum dolor sit amet, consectetur\
180 \ adipiscing elit. Donec libero risus, commodo vitae, pharetra mollis,\
181 \ posuere eu, pede. Nulla nec tortor. Donec id elit quis purus consectetur\
182 \ consequat. Nam congue semper tellus. Sed erat dolor, dapibus sit amet,\
183 \ venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse\
184 \ scelerisque dui nec velit. Duis augue augue, gravida euismod, vulputate ac,\
185 \ facilisis id, sem. Morbi in orci. Nulla purus lacus, pulvinar vel,\
186 \ malesuada ac, mattis nec, quam. Nam molestie scelerisque quam. Nullam\
187 \ feugiat cursus lacus.orem ipsum dolor sit amet, consectetur adipiscing\
188 \ elit. Donec libero risus, commodo vitae, pharetra mollis, posuere eu, pede.\
189 \ Nulla nec tortor. Donec id elit quis purus consectetur consequat. Nam\
190 \ congue semper tellus. Sed erat dolor, dapibus sit amet, venenatis ornare,\
191 \ ultrices ut, nisi."