{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
-{-# OPTIONS_GHC -O0 -fmax-simplifier-iterations=0 #-}
module Lib.Functor.Test where
import Test.Tasty
import Data.Proxy (Proxy(..))
import Prelude hiding ((&&), not, (||))
-import Language.Symantic.Typing
-import Compiling.Term.Test
+import Language.Symantic ()
+import Language.Symantic.Lib
+import Compiling.Test
-type Ifaces =
+type SS =
[ Proxy (->)
, Proxy Bool
, Proxy Functor
, Proxy Integer
, Proxy Maybe
]
-(==>) = test_compile @Ifaces
+(==>) = test_readTerm @() @SS
tests :: TestTree
tests = testGroup "Functor"
- [ "fmap not (Just True)" ==> Right
- ( ty @Maybe :$ ty @Bool
- , Just False
- , "fmap (\\x0 -> not x0) (Just True)")
- , "not `fmap` Just True" ==> Right
- ( ty @Maybe :$ ty @Bool
- , Just False
- , "fmap (\\x0 -> not x0) (Just True)")
- , "not <$> Just True" ==> Right
- ( ty @Maybe :$ ty @Bool
- , Just False
- , "fmap (\\x0 -> not x0) (Just True)")
- , "False <$ Just True" ==> Right
- ( ty @Maybe :$ ty @Bool
- , Just False
- , "False <$ Just True" )
+ [ "fmap not (Just True)" ==> Right (tyMaybe tyBool, Just False, "fmap (\\x0 -> not x0) (Just True)")
+ , "not `fmap` Just True" ==> Right (tyMaybe tyBool, Just False, "fmap (\\x0 -> not x0) (Just True)")
+ , "not <$> Just True" ==> Right (tyMaybe tyBool, Just False, "(\\x0 -> not x0) <$> Just True")
+ , "False <$ Just True" ==> Right (tyMaybe tyBool, Just False, "False <$ Just True")
]