{-# LANGUAGE OverloadedStrings #-} module HUnit where import Test.Tasty import Test.Tasty.HUnit import Data.Foldable (Foldable(..)) import Data.Function (($), (.)) import Data.Functor ((<$>)) import Data.Int (Int) import Data.Maybe (Maybe(..)) import Data.Monoid (Monoid(..)) import Data.Ord (Ord(..)) import Data.Semigroup (Semigroup(..)) import Data.String (String, IsString(..)) import Prelude ((+)) import Text.Show (Show(..)) import qualified Data.List as List import Symantic.Document.API import Symantic.Document.Plain import Symantic.Document.AnsiText -- * Tests hunits :: TestTree hunits = testGroup "HUnit" $ [ hunitPlain ] hunitPlain :: TestTree hunitPlain = testList "Plain" [ newline ==> "\n" , "hello\nworld" ==> "hello\nworld" , 10`maxWidth` breakpoints ["hello", "world"] ==> "helloworld" , 9`maxWidth` breakpoints ["hello", "world"] ==> "hello\nworld" , 6`maxWidth` breakpoints ["he", "ll", "o!"] ==> "hello!" , 6`maxWidth` breakpoints ["he", "ll", "o!", "wo", "rl", "d!"] ==> "hello!\nworld!" , 5`maxWidth` breakpoints ["hello", "world"] ==> "hello\nworld" , 5`maxWidth` breakpoints ["he", "llo", "world"] ==> "hello\nworld" , 5`maxWidth` breakpoints ["he", "ll", "o!"] ==> "hell\no!" , 4`maxWidth` breakpoints ["hello", "world"] ==> "hello\nworld" , 4`maxWidth` breakpoints ["he", "ll", "o!"] ==> "hell\no!" , 4`maxWidth` breakpoints ["he", "llo", "world"] ==> "he\nllo\nworld" , 4`maxWidth` breakpoints ["he", "llo", "w", "orld"] ==> "he\nllow\norld" , 4`maxWidth` breakpoints ["he", "ll", "o!", "wo", "rl", "d!"] ==> "hell\no!wo\nrld!" , 3`maxWidth` breakpoints ["hello", "world"] ==> "hello\nworld" , 3`maxWidth` breakpoints ["he", "ll"] ==> "he\nll" , 3`maxWidth` breakpoints ["he", "ll", "o!"] ==> "he\nll\no!" , 1`maxWidth` breakpoints ["he", "ll", "o!"] ==> "he\nll\no!" , 4`maxWidth` mconcat ["__", align $ breakpoints ["he", "ll", "o!", "wo", "rl", "d!"]] ==> "__he\n ll\n o!\n wo\n rl\n d!" , 6`maxWidth` mconcat ["__", align $ breakpoints ["he", "ll", "o!", "wo", "rl", "d!"]] ==> "__hell\n o!wo\n rld!" , 16`maxWidth` mconcat ["__", listHorV ["hello", "world"]] ==> "__[hello, world]" , 4`maxWidth` mconcat ["__", listHorV ["hello", "world"]] ==> "__[ hello\n , world\n ]" , 11`maxWidth` breakspaces ["hello", "world"] ==> "hello world" , 10`maxWidth` breakspaces ["hello", "world"] ==> "hello\nworld" , 6`maxWidth` breakspaces ["hel", "lo", "wo", "rld"] ==> "hel lo\nwo rld" , 6`maxWidth` breakspaces ["hel", "lo", "wo", "rld", "HEL", "LO", "WO", "RLD"] ==> "hel lo\nwo rld\nHEL LO\nWO RLD" , 5`maxWidth` breakspaces ["hello", "world"] ==> "hello\nworld" , 19`maxWidth` fun (fun $ fun $ fun $ fun $ listHorV ["abcdefg", "abcdefg"]) ==> "function(function(\n function(\n function(\n function(\n [ abcdefg\n , abcdefg\n ]\n )\n )\n )\n ))" , 19`maxWidth` fun (fun $ fun $ fun $ fun $ listHorV ["abcdefgh", "abcdefgh"]) ==> "function(\n function(\n function(\n function(\n function(\n [ abcdefgh\n , abcdefgh\n ]\n )\n )\n )\n )\n )" , 7`maxWidth` ("hello"<>breakspace<>"world") ==> "hello\nworld" , 7`maxWidth` ("hello "<>"world") ==> "hello\nworld" , " "<> "hello\nworld\n!" ==> " hello\nworld\n!" , "__"<>align "hello\nworld\n!" ==> "__hello\n world\n !" , hang 2 "hello\nworld\n!" ==> "hello\n world\n !" , hang 2 "hello\nworld\n!"<>"\nhello\n!" ==> "hello\n world\n !\nhello\n!" , "let " <> align (catV $ (\(name, typ) -> fill 6 name <+> "::" <+> typ) <$> [ ("abcdef","Doc") , ("abcde","Int -> Doc -> Doc") , ("abcdefghi","Doc") ]) ==> "let abcdef :: Doc\n abcde :: Int -> Doc -> Doc\n abcdefghi :: Doc" , "let " <> align (catV $ (\(name, typ) -> breakfill 6 name <> " ::" <+> typ) <$> [ ("abcdef","Doc") , ("abcde","Int -> Doc -> Doc") , ("abcdefghi","Doc") ]) ==> "let abcdef :: Doc\n abcde :: Int -> Doc -> Doc\n abcdefghi\n :: Doc" , "let " <> align (catV $ (\(name, typ) -> breakfill 6 name <> " ::" <+> typ) <$> [("abcdefghi","Doc ->\nDoc")]) ==> "let abcdefghi\n :: Doc ->\n Doc" , "let " <> align (catV $ (\(name, typ) -> breakfill 6 name <> align (" ::" <+> typ)) <$> [("abcdefghi","Doc ->\nDoc")]) ==> "let abcdefghi\n :: Doc ->\n Doc" , 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" , 10 `maxWidth` "a b "<>"12"<>align (" 34 5") ==> "a b 12 34\n 5" , 10 `maxWidth` "a b "<>"12"<>align (" 34" <> align "") ==> "a b 12 34" , 10 `maxWidth` "a b "<>"12"<>align (" 34" <> align " ") ==> "a b 12 34 " , 10 `maxWidth` "a b "<>"12"<>align (" 34" <> align " 5") ==> "a b 12 34\n 5" , 10 `maxWidth` "a b "<>"12"<>align (" 34" <> align " 56") ==> "a b 12\n 34\n 56" , 10 `maxWidth` "a b "<>"12"<>align (" 34" <> align " 567") ==> "a b\n12 34 567" , 10 `maxWidth` "a b "<>"12"<>align (" 34" <> align " 5678") ==> "a b\n12 34 5678" , 10 `maxWidth` "a b "<>"12"<>align (" 34" <> align " 56789") ==> "a b\n12 34\n 56789" , 10 `maxWidth` ("1234567890" <> " ") <> "1" ==> "1234567890\n1" , 10 `maxWidth` nestedAlign 6 ==> "1 2 3 4 5\n 6" , 10 `maxWidth` nestedAlign 7 ==> "1 2 3 4\n 5\n 6\n 7" , 10 `maxWidth` nestedAlign 8 ==> "1 2 3\n 4\n 5\n 6\n 7\n 8" , 10 `maxWidth` nestedAlign 9 ==> "1 2\n 3\n 4\n 5\n 6\n 7\n 8\n 9" , 10 `maxWidth` nestedAlign 10 ==> "1\n 2\n 3\n 4\n 5\n 6\n 7\n 8\n 9\n 10" -- justify justifies , 10 `maxWidth` justify "1 2 3 4 5 6" ==> "1 2 3 4 5\n6" -- justify compress spaces , 10 `maxWidth` justify "1 2 3 4 5 6" ==> "1 2 3 4 5\n6" -- justify does not overflow the alignment , 10 `maxWidth` justify (nestedAlign 6) ==> "1 2 3 4 5\n 6" , 10 `maxWidth` justify ("a b\n" <> nestedAlign 2) ==> "a b\n1 2" , 10 `maxWidth` justify (bold ("12 34 56 78 "<> underline "90" <> " 123 456 789")) ==> "\ESC[1m12 34 56\n78 \ESC[4m90\ESC[0;1m 123\n456 789\ESC[0m" -- breakspace backtracking is bounded by the removable indentation -- (hence it can actually justify a few words in reasonable time). , 80 `maxWidth` "Lorem ipsum dolor sit amet, Nulla nec tortor. Donec id elit quis purus\ \ consectetur consequat. Nam congue semper tellus. Sed erat dolor,\ \ dapibus sit amet, venenatis ornare, ultrices ut, nisi. Aliquam ante.\ \ Suspendisse scelerisque dui nec velit. Duis augue augue, gravida euismod,\ \ vulputate ac, facilisis id, sem. Morbi in orci. Nulla purus lacus,\ \ pulvinar vel, malesuada ac, mattis nec, quam. Nam molestie scelerisque\ \ quam. Nullam feugiat cursus lacus.orem ipsum dolor sit amet, consectetur\ \ adipiscing elit. Donec libero risus, commodo vitae, pharetra mollis,\ \ posuere eu, pede. Nulla nec tortor. Donec id elit quis purus consectetur\ \ consequat. Nam congue semper tellus. Sed erat dolor, dapibus sit\ \ amet, venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse\ \ scelerisque dui nec velit. Duis augue augue, gravida euismod, vulputate ac,\ \ facilisis id, sem. Morbi in orci. Nulla purus lacus, pulvinar vel,\ \ malesuada ac, mattis nec, quam. Nam molestie scelerisque quam.\ \ Nullam feugiat cursus lacus.orem ipsum dolor sit amet, consectetur\ \ adipiscing elit. Donec libero risus, commodo vitae, pharetra mollis,\ \ posuere eu, pede. Nulla nec tortor. Donec id elit quis purus consectetur\ \ consequat. Nam congue semper tellus. Sed erat dolor, dapibus sit amet,\ \ venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse\ \ scelerisque dui nec velit. Duis augue augue, gravida euismod, vulputate ac,\ \ facilisis id, sem. Morbi in orci. Nulla purus lacus, pulvinar vel,\ \ malesuada ac, mattis nec, quam. Nam molestie scelerisque quam. Nullam\ \ feugiat cursus lacus.orem ipsum dolor sit amet, consectetur adipiscing\ \ elit. Donec libero risus, commodo vitae, pharetra mollis, posuere eu, pede.\ \ Nulla nec tortor. Donec id elit quis purus consectetur consequat. Nam\ \ congue semper tellus. Sed erat dolor, dapibus sit amet, venenatis ornare,\ \ ultrices ut, nisi." ==> "Lorem ipsum dolor sit amet, Nulla nec tortor. Donec id elit quis\ \ purus\nconsectetur consequat. Nam congue semper tellus. Sed erat dolor, dapibus\ \ sit\namet, venenatis ornare, ultrices ut, nisi. Aliquam ante. Suspendisse\ \ scelerisque\ndui nec velit. Duis augue augue, gravida euismod, vulputate ac,\ \ facilisis id,\nsem. Morbi in orci. Nulla purus lacus, pulvinar vel, malesuada\ \ ac, mattis nec,\nquam. Nam molestie scelerisque quam. Nullam feugiat cursus\ \ lacus.orem ipsum\ndolor sit amet, consectetur adipiscing elit. Donec libero\ \ risus, commodo vitae,\npharetra mollis, posuere eu, pede. Nulla nec tortor.\ \ Donec id elit quis purus\nconsectetur consequat. Nam congue semper tellus. Sed\ \ erat dolor, dapibus sit\namet, venenatis ornare, ultrices ut, nisi. Aliquam\ \ ante. Suspendisse scelerisque\ndui nec velit. Duis augue augue, gravida\ \ euismod, vulputate ac, facilisis id,\nsem. Morbi in orci. Nulla purus lacus,\ \ pulvinar vel, malesuada ac, mattis nec,\nquam. Nam molestie scelerisque quam.\ \ Nullam feugiat cursus lacus.orem ipsum\ndolor sit amet, consectetur adipiscing\ \ elit. Donec libero risus, commodo vitae,\npharetra mollis, posuere eu, pede.\ \ Nulla nec tortor. Donec id elit quis purus\nconsectetur consequat. Nam congue\ \ semper tellus. Sed erat dolor, dapibus sit\namet, venenatis ornare, ultrices\ \ ut, nisi. Aliquam ante. Suspendisse scelerisque\ndui nec velit. Duis augue\ \ augue, gravida euismod, vulputate ac, facilisis id,\nsem. Morbi in orci. Nulla\ \ purus lacus, pulvinar vel, malesuada ac, mattis nec,\nquam. Nam molestie\ \ scelerisque quam. Nullam feugiat cursus lacus.orem ipsum\ndolor sit amet,\ \ consectetur adipiscing elit. Donec libero risus, commodo vitae,\npharetra\ \ mollis, posuere eu, pede. Nulla nec tortor. Donec id elit quis\ \ purus\nconsectetur consequat. Nam congue semper tellus. Sed erat dolor, dapibus\ \ sit\namet, venenatis ornare, ultrices ut, nisi." ] where (==>) :: IsString d => d ~ String => AnsiText (Plain d) -> d -> Assertion; infix 0 ==> p ==> exp = got @?= exp where got = runPlain $ runAnsiText p testList :: String -> [Assertion] -> TestTree testList n as = testGroup n $ List.zipWith testCase (show <$> [1::Int ..]) as breakpoints :: Wrappable d => Monoid d => [d] -> d breakpoints = intercalate breakpoint breakspaces :: Wrappable d => Monoid d => [d] -> d breakspaces = intercalate breakspace infix 1 `maxWidth` maxWidth :: Wrappable d => Width -> d -> d maxWidth = setWidth . Just nestedAlign :: DocFrom (Line String) d => Spaceable d => Indentable d => Wrappable d => Int -> d nestedAlign n = go 1 where go i = docFrom (Line (show i)) <> (if n <= i then mempty else align (breakspace <> go (i+1))) listHorV :: IsString d => Indentable d => Wrappable d => [d] -> d listHorV [] = "[]" listHorV [d] = "["<>d<>"]" listHorV ds = breakalt ("[" <> intercalate ("," <> space) ds <> "]") (align $ "[" <> space <> foldr1 (\a acc -> a <> newline <> "," <> space <> acc) ds <> newline <> "]") fun :: IsString d => Indentable d => Wrappable d => d -> d fun d = "function(" <> incrIndent 2 (breakalt d (newline<>d<>newline)) <> ")"