{-# 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.Ord (Ord(..)) import Data.String (String, IsString(..)) import Prelude ((+)) import Text.Show (Show(..)) import qualified Data.List as List import Symantic.Formatter.Class import Symantic.Formatter.Plain (Plain, runPlain) -- * Tests hunit :: TestTree hunit = testGroup "HUnit" [ testList "Plain" [ testPlain newline () "\n" , testPlain ("hello".>"world") () "helloworld" , testPlain ("hello".>newline.>"world") () "hello\nworld" , testPlain ("hello\nworld") () "hello\nworld" , testPlain (setWidth (Just 9) $ "hello" .> breakpoint .> "world") () "hello\nworld" , testPlain (setWidth (Just 10) $ intercalate_ breakpoint string) ["hello", "world"] "helloworld" , testPlain (setWidth (Just 6) $ intercalate_ breakpoint string) ["he", "ll", "o!"] "hello!" , testPlain (setWidth (Just 6) $ intercalate_ breakpoint string) ["he", "ll", "o!", "wo", "rl", "d!"] "hello!\nworld!" , testPlain (setWidth (Just 5) $ intercalate_ breakpoint string) ["hello", "world"] "hello\nworld" , testPlain (setWidth (Just 5) $ intercalate_ breakpoint string) ["he", "llo", "world"] "hello\nworld" , testPlain (setWidth (Just 5) $ intercalate_ breakpoint string) ["he", "ll", "o!"] "hell\no!" , testPlain (setWidth (Just 4) $ intercalate_ breakpoint string) ["hello", "world"] "hello\nworld" , testPlain (setWidth (Just 4) $ intercalate_ breakpoint string) ["he", "ll", "o!"] "hell\no!" , testPlain (setWidth (Just 4) $ intercalate_ breakpoint string) ["he", "llo", "world"] "he\nllo\nworld" , testPlain (setWidth (Just 4) $ intercalate_ breakpoint string) ["he", "llo", "w", "orld"] "he\nllow\norld" , testPlain (setWidth (Just 4) $ intercalate_ breakpoint string) ["he", "ll", "o!", "wo", "rl", "d!"] "hell\no!wo\nrld!" , testPlain (setWidth (Just 3) $ intercalate_ breakpoint string) ["hello", "world"] "hello\nworld" , testPlain (setWidth (Just 3) $ intercalate_ breakpoint string) ["he", "ll"] "he\nll" , testPlain (setWidth (Just 3) $ intercalate_ breakpoint string) ["he", "ll", "o!"] "he\nll\no!" , testPlain (setWidth (Just 1) $ intercalate_ breakpoint string) ["he", "ll", "o!"] "he\nll\no!" , testPlain (setWidth (Just 4) $ "__" .> align (intercalate_ breakpoint string)) ["he", "ll", "o!", "wo", "rl", "d!"] "__he\n ll\n o!\n wo\n rl\n d!" , testPlain (setWidth (Just 6) $ "__" .> align (intercalate_ breakpoint string)) ["he", "ll", "o!", "wo", "rl", "d!"] "__hell\n o!wo\n rld!" , testPlain (setWidth (Just 16) $ "__" .> bracketList string) ["hello", "world"] "__[hello, world]" , testPlain (setWidth (Just 11) $ intercalate_ breakspace string) ["hello", "world"] "hello world" , testPlain (setWidth (Just 10) $ intercalate_ breakspace string) ["hello", "world"] "hello\nworld" , testPlain (setWidth (Just 6) $ intercalate_ breakspace string) ["hel", "lo", "wo", "rld"] "hel lo\nwo rld" , testPlain (setWidth (Just 6) $ intercalate_ breakspace string) ["hel", "lo", "wo", "rld", "HEL", "LO", "WO", "RLD"] "hel lo\nwo rld\nHEL LO\nWO RLD" , testPlain (setWidth (Just 5) $ intercalate_ breakspace string) ["hello", "world"] "hello\nworld" , testPlain (setWidth (Just 7) $ ("hello".>breakspace.>"world")) () "hello\nworld" , testPlain (setWidth (Just 7) $ ("hello ".>"world")) () "hello\nworld" , testPlain (" ".> "hello\nworld\n!") () " hello\nworld\n!" , testPlain ("__".>align "hello\nworld\n!") () "__hello\n world\n !" , testPlain (hang 2 "hello\nworld\n!") () "hello\n world\n !" , testPlain (hang 2 "hello\nworld\n!".>"\nhello\n!") () "hello\n world\n !\nhello\n!" , testPlain (setWidth (Just 10) $ unwords_ int) [1..15] "1 2 3 4 5\n6 7 8 9 10\n11 12 13\n14 15" , testPlain (setWidth (Just 10) $ ("1234567890" .> " ") .> "1") () "1234567890\n1" -- justify respects concatenating words , testPlain (setWidth (Just 10) $ justify (setWidth (Just 11) ("1 2 3".>"4 5 6 7"))) () "1 2 34 5 6\n7" -- justify flushes the buffer before , testPlain (setWidth (Just 10) $ "__" .> align (justify "1 2 3 4 5")) () "__1 2 3 4\n 5" , testPlain (setWidth (Just 10) $ 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" -- handle escaping correctly over custom indenting , testPlain (setWidth (Just 10) $ setIndent (blue "X") 1 (red ("12".>green "4\n5" .> "6"))) () "\ESC[31m12\ESC[32m4\n\ESC[34mX\ESC[0;31;32m5\ESC[0;31m6\ESC[0m" , testPlain (setWidth (Just 10) $ setIndent (blue "X") 1 (justify (red ("1 2 3 4".>green " 5 6 " .> "7 ") .> "8"))) () "\ESC[31m1 2 3 4\ESC[32m 5\n\ESC[34mX\ESC[0;31;32m6 \ESC[0;31m7 \ESC[0m8" -- unorderedList/orderedList are empty when no item , testPlain (unorderedList int) [] "" , testPlain (unorderedList int) [] "" -- endline break spaces , testPlain (setWidth (Just 10) $ ("a".>endline.>" b")) () "a\nb" -- endline does no justify , testPlain (setWidth (Just 10) $ justify ("a b".>endline.>" c")) () "a b\nc" -- endline works overflowed , testPlain (setWidth (Just 10) $ justify ("abcdefghijk".>endline.>" a")) () "abcdefghijk\na" -- endline prints nothing , testPlain (setWidth (Just 10) $ justify ("12345678".>endline.>"90ab".>align (" cdefghijk cdefghijk"))) () "1234567890ab\n\ \ cdefghijk\n\ \ cdefghijk" -- newline stops overflow , testPlain (setWidth (Just 10) $ breakalt "fits" "over".>"\n".>"12345678901") () "fits\n\ \12345678901" -- breakalt triggers only if its first argument overflows, -- not if what's next overflows. , testPlain (setWidth (Just 10) $ spaces 2.>align(breakalt "fits" "over".>newline.>"12345678901")) () " fits\n\ \ 12345678901" ] ] where testList :: String -> [Assertion] -> TestTree testList n as = testGroup n $ List.zipWith testCase (show <$> [1::Int ..]) as testPlain :: o ~ String => Plain o a -> a -> o -> Assertion testPlain fmt a exp = runPlain fmt a @?= exp