{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
-{-# OPTIONS_GHC -O0 -fmax-simplifier-iterations=0 #-}
module Lib.Map.Test where
import Test.Tasty
import Data.Map.Strict (Map)
-import qualified Data.Map.Strict as Map
import Data.Proxy (Proxy(..))
+import Data.Text as Text
import Prelude hiding (zipWith)
+import qualified Data.Map.Strict as Map
-import Language.Symantic.Typing
-import Compiling.Term.Test
+import Language.Symantic.Lib
+import Compiling.Test
-type Ifaces =
+type SS =
[ Proxy (->)
, Proxy []
, Proxy Int
, Proxy Num
, Proxy Monoid
]
-(==>) = test_compile @Ifaces
+(==>) = test_readTerm @() @SS
tests :: TestTree
tests = testGroup "Map"
- [ "Map.fromList (zipWith (\\(x:Integer) (y:Char) -> (x, y)) [1, 2, 3] ['a', 'b', 'c'])" ==> Right
- ( (ty @Map :$ ty @Integer) :$ ty @Char
+ [ "Map.fromList (zipWith (,) [1, 2, 3] ['a', 'b', 'c'])" ==> Right
+ ( tyMap tyInteger tyChar
, Map.fromList [(1, 'a'), (2, 'b'), (3, 'c')]
- , "Map.fromList (((\\x0 -> (\\x1 -> zipWith (\\x2 -> (\\x3 -> (x2, x3))) x0 x1)) (1 : 2 : 3 : [])) ('a' : 'b' : 'c' : []))" )
- , concat
+ , "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, [] @Char)"
- , " (Map.fromList (zipWith (\\(x:Integer) (y:Char) -> (x,y)) [1, 2, 3] ['a', 'b', 'c']))"
+ , " (0, [])"
+ , " (Map.fromList (zipWith (,) [1, 2, 3] ['a', 'b', 'c']))"
] ==> Right
- ( (ty @(,) :$ ty @Integer) :$ (ty @[] :$ ty @Char)
+ ( tyInteger `tyTuple2` tyString
, (6, "abc")
- , "((\\x0 -> (\\x1 -> Map.foldrWithKey (\\x2 -> (\\x3 -> (\\x4 -> ((\\x5 -> x2 + x5) (fst x4), x3 : snd x4)))) x0 x1)) (0, [])) (Map.fromList (((\\x0 -> (\\x1 -> zipWith (\\x2 -> (\\x3 -> (x2, x3))) x0 x1)) (1 : 2 : 3 : [])) ('a' : 'b' : 'c' : [])))" )
+ , "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' : [])))" )
]