1 {-# LANGUAGE ExistentialQuantification #-}
4 import Control.Monad (Monad(..))
5 import Data.Char (Char)
6 import Data.Function (($))
8 import Data.Maybe (Maybe(..))
9 import Data.Ord (Ord(..))
10 import Data.Semigroup (Semigroup(..))
11 import Data.String (IsString(..), String)
13 import System.IO (FilePath)
14 import System.IO.Unsafe (unsafePerformIO)
16 import Test.Tasty.Golden
17 import Text.Printf (printf)
18 import Text.Show (Show(..))
19 import qualified Data.List as List
21 import Paths_symantic_formatter
22 import Symantic.Formatter
28 (\f -> List.zipWith f goldens [1::Int ..]) $ \(Golden fmt inps) fmtNum ->
29 let fmtDir = printf "Format%03d" fmtNum in
31 (\f -> List.zipWith f inps [1::Int ..]) $ \inp inpNum ->
32 let plainFile = getGoldenDir $ printf "Plain/%s/Input%02d.expected.txt" fmtDir inpNum in
34 (printf "Input%02d" inpNum) goldenDiff plainFile $ do
35 return $ fromString $ runPlain fmt inp
38 getGoldenDir :: FilePath -> FilePath
39 getGoldenDir p = unsafePerformIO $ getDataFileName $ "tests/Golden/" <> p
41 goldenDiff :: FilePath -> FilePath -> [String]
42 goldenDiff ref new = ["diff", "-u", "-w", "-B", ref, new]
44 data Golden repr = forall inp. Golden (repr inp) [inp]
47 Inferable Char repr =>
49 Inferable String repr =>
60 [ let fun t = "function("
61 .> breakalt t (incrIndent (spaces 2) 2 (newline.>t)<.newline)
64 ( setWidth (Just 19) $ fun $ fun $ fun $ fun $ fun $ bracketList (many int)
70 ( setWidth (Just 10) $
71 justify (unorderedList (unwords_ int))
75 ( setWidth (Just 11) $
76 justify (orderedList (unwords_ int))
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 ]
88 ("let"+>align (unlines_ (fill 6 string<+ "::" <+>string)))
91 , ("abcde","Int -> Char -> Char")
92 , ("abcdefghi","Char")
96 ("let"+>align (unlines_ (fillOrBreak 6 string<+"::"<+>align string)))
99 , ("abcde","Int -> Char -> Char")
100 , ("abcdefghi","Char ->\nChar")
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)
112 , Golden (setWidth (Just 10) $ justify string)
115 -- justify compresses enclosed spaces
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"
124 , Golden (setWidth (Just 10) $ "a b ".> "12" .> align string <.> align string)
134 -- align flushes the buffer
135 , Golden (setWidth (Just 10) $ justify $ unorderedList $ unwords_ int)
137 -- unorderedList flushes the buffer
138 , Golden (setWidth (Just 10) $ justify $ unorderedList $ unwords_ int)
141 , [[100000000..100000009], [100000000..100000009]]
142 , [[1000000000..1000000009], [1000000000..1000000009]]
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] ] ] ]
153 IsString (repr ()) =>
158 fromString (show i) .>
161 else align (breakspace .> go (succ i)))
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."