{-# OPTIONS_GHC -fno-warn-missing-signatures #-} module HUnit.Foldable where import Test.Tasty import Data.Proxy (Proxy(..)) import Language.Symantic.Lib import Testing.Compiling type SS = [ Proxy (->) , Proxy Int , Proxy Integer , Proxy [] , Proxy () , Proxy (,) , Proxy Foldable ] (==>) = readTe @() @SS hunits :: TestTree hunits = testGroup "Foldable" [ {-"[]" ==> Right (tyList (tyVar "a" varZ), [], "[]") ,-} "[1, 2, 3]" ==> Right (tyList tyInteger, [1, 2, 3], "1 : 2 : 3 : []") , "1 : 2 : 3 : []" ==> Right (tyList tyInteger, [1, 2, 3], "1 : 2 : 3 : []") , "foldMap (\\(x0:Integer) -> [x0, x0]) [1, 2, 3]" ==> Right ( tyList tyInteger , [1, 1, 2, 2, 3, 3] , "foldMap (\\x0 -> x0 : x0 : []) (1 : 2 : 3 : [])" ) ]