{-# OPTIONS_GHC -fno-warn-missing-signatures #-} module HUnit.Map where import Test.Tasty import Data.Map.Strict (Map) import Data.Proxy (Proxy(..)) import Data.Text as Text import qualified Data.Map.Strict as Map import Language.Symantic.Lib import Testing.Compiling type SS = [ Proxy (->) , Proxy [] , Proxy Int , Proxy Integer , Proxy Map , Proxy Char , Proxy (,) , Proxy Num , Proxy Monoid ] (==>) = readTe @() @SS hunits :: TestTree hunits = testGroup "Map" [ "Map.fromList (zipWith (,) [1, 2, 3] ['a', 'b', 'c'])" ==> Right ( tyMap tyInteger tyChar , Map.fromList [(1, 'a'), (2, 'b'), (3, 'c')] , "Map.fromList (zipWith (\\x0 -> (\\x1 -> (x0, x1))) (1 : 2 : 3 : []) ('a' : 'b' : 'c' : []))" ) , Text.concat [ "Map.foldrWithKey" , " (\\(k:Integer) (v:Char) (acc:(Integer,[Char])) ->" , " (k + fst acc, v : snd acc))" , " (0, [])" , " (Map.fromList (zipWith (,) [1, 2, 3] ['a', 'b', 'c']))" ] ==> Right ( tyInteger `tyTuple2` tyString , (6, "abc") , "Map.foldrWithKey (\\x0 -> (\\x1 -> (\\x2 -> (x0 + fst x2, x1 : snd x2)))) (0, []) (Map.fromList (zipWith (\\x0 -> (\\x1 -> (x0, x1))) (1 : 2 : 3 : []) ('a' : 'b' : 'c' : [])))" ) ]