{-# LANGUAGE DataKinds #-} {-# OPTIONS_GHC -fno-warn-missing-signatures #-} module Compiling.Functor.Test where import Test.Tasty import Data.Proxy (Proxy(..)) import Prelude hiding ((&&), not, (||)) import Language.Symantic.Typing import Language.Symantic.Compiling import Compiling.Term.Test -- * Tests type Ifaces = [ Proxy (->) , Proxy Bool , Proxy Maybe , Proxy Functor ] (==>) = test_term_from (Proxy::Proxy Ifaces) tests :: TestTree tests = testGroup "Functor" [ Syntax "fmap" [ syLam (Syntax "x" []) syBool (Syntax "not" [Syntax "x" []]) , syJust [syTrue] ] ==> Right (tyMaybe :$ tyBool, Just False, "fmap (\\x0 -> (\\x1 -> not x1) x0) (Just True)") , Syntax "<$" [ syFalse , syJust [syTrue] ] ==> Right (tyMaybe :$ tyBool, Just False, "False <$ Just True") ]