{-# LANGUAGE OverloadedStrings #-} module Type.Test where import Data.Function (($)) import Data.Text.Buildable (Buildable(..)) import Test.Tasty import Test.Tasty.HUnit -- import Test.HUnit hiding (test) import Language.LOL.Typing.Type import qualified Language.LOL.Typing.Lib.Data.Text.Buildable as Build tests :: TestTree tests = testGroup "Type" [ tests_Monotype ] tests_Monotype :: TestTree tests_Monotype = testGroup "Monotype" [ testGroup "Build" $ let (==>) x expected = testCase (Build.string expected) $ build x @?= expected in [ ("a"::Monotype) ==> "a" , ("a".->."b") ==> "a -> b" , ("a".->."b".->."c") ==> "a -> b -> c" , ("a".->."b".->."c".->."d") ==> "a -> b -> c -> d" , ("a".->."b".->.("c".->."d")) ==> "a -> b -> c -> d" , (("a".->."b").->."c".->."d") ==> "(a -> b) -> c -> d" , (("a".->."b").->.("c".->."d")) ==> "(a -> b) -> c -> d" , ("a".->.("b".->."c").->."d") ==> "a -> (b -> c) -> d" , ((("a".->."b").->.("c".->."d")).->.(("e".->."f").->.("g".->."h"))) ==> "((a -> b) -> c -> d) -> (e -> f) -> g -> h" , ("T".!."a".!."b") ==> "T a b" , ("T".!."a".!."b".!.("U".!."c".!."d")) ==> "T a b (U c d)" , ("T".!."a".!."b".->."U".!."c".!."d") ==> "T a b -> U c d" , ("T".!."a".!."b".->."U".!."c".!."d".->."V".!."e".!."f") ==> "T a b -> U c d -> V e f" , ("T".!."x".!.(("a".->."b").->.("c".->."d")).!."y") ==> "T x ((a -> b) -> c -> d) y" ] ]