{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeOperators #-} module Repr.Host.Test where -- import Data.Function (($)) import Test.Tasty import Test.Tasty.HUnit import Data.Text (Text) import qualified Data.Text as Text import Prelude hiding (and, not, or, Monad(..), id) import Language.Symantic.Repr import Language.Symantic.Expr import qualified Expr.Lambda.Test as Lambda.Test import qualified Expr.Bool.Test as Bool.Test import qualified Expr.Maybe.Test as Maybe.Test import qualified Expr.If.Test as If.Test import qualified Expr.List.Test as List.Test import qualified Expr.Functor.Test as Functor.Test import qualified Expr.Applicative.Test as Applicative.Test import qualified Expr.Foldable.Test as Foldable.Test tests :: TestTree tests = testGroup "Host" $ [ testGroup "Bool" $ let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda .|. Expr_Bool )) repr => repr h) expected = testCase (Text.unpack $ text_from_expr $ expr) $ -- (>>= (@?= expected)) $ (@?= expected) $ host_from_expr expr in [ Bool.Test.e1 ==> False , Bool.Test.e2 ==> True , Bool.Test.e3 ==> True , Bool.Test.e4 ==> True ] , testGroup "Lambda" $ let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda .|. Expr_Bool )) repr => repr h) expected = testCase (Text.unpack $ text_from_expr $ expr) $ (@?= expected) $ host_from_expr expr in [ (Lambda.Test.e1 $$ bool True $$ bool True) ==> False , (Lambda.Test.e1 $$ bool True $$ bool False) ==> True , (Lambda.Test.e1 $$ bool False $$ bool True) ==> True , (Lambda.Test.e1 $$ bool False $$ bool False) ==> False , (Lambda.Test.e2 $$ bool True $$ bool True) ==> False , (Lambda.Test.e2 $$ bool True $$ bool False) ==> True , (Lambda.Test.e2 $$ bool False $$ bool True) ==> True , (Lambda.Test.e2 $$ bool False $$ bool False) ==> False , Lambda.Test.e3 ==> True , Lambda.Test.e4 ==> True , (Lambda.Test.e5 $$ bool True $$ bool True) ==> True , (Lambda.Test.e5 $$ bool True $$ bool False) ==> False , (Lambda.Test.e5 $$ bool False $$ bool True) ==> False , (Lambda.Test.e5 $$ bool False $$ bool False) ==> False , Lambda.Test.e6 ==> False , (Lambda.Test.e7 $$ lam id) ==> True , (Lambda.Test.e7 $$ lam not) ==> False ] , testGroup "Maybe" $ let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda .|. Expr_Maybe .|. Expr_Bool )) repr => repr h) expected = testCase (Text.unpack $ text_from_expr $ expr) $ (@?= expected) $ host_from_expr expr in [ Maybe.Test.e1 ==> False ] , testGroup "If" $ let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda .|. Expr_If .|. Expr_Bool )) repr => repr h) expected = testCase (Text.unpack $ text_from_expr $ expr) $ (@?= expected) $ host_from_expr expr in [ If.Test.e1 ==> False ] , testGroup "List" $ let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda .|. Expr_List .|. Expr_Bool .|. Expr_Int .|. Expr_If .|. Expr_Eq )) repr => repr h) expected = testCase (Text.unpack $ text_from_expr $ expr) $ (@?= expected) $ host_from_expr expr in [ List.Test.e1 ==> [2::Int,4] ] , testGroup "Functor" $ let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda .|. Expr_List .|. Expr_Functor .|. Expr_Bool .|. Expr_Int .|. Expr_If .|. Expr_Eq )) repr => repr h) expected = testCase (Text.unpack $ (text_from_expr :: Repr_Text _h -> Text) $ expr) $ (@?= expected) $ host_from_expr expr in [ Functor.Test.e1 ==> [2::Int,3,4] ] , testGroup "Applicative" $ let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda .|. Expr_List .|. Expr_Functor .|. Expr_Applicative .|. Expr_Maybe .|. Expr_Bool .|. Expr_Int .|. Expr_If .|. Expr_Eq )) repr => repr h) expected = testCase (Text.unpack $ text_from_expr $ expr) $ (@?= expected) $ host_from_expr expr in [ Applicative.Test.e1 ==> Just (3::Int) ] , testGroup "Foldable" $ let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda .|. Expr_List .|. Expr_Foldable .|. Expr_Maybe .|. Expr_Bool .|. Expr_Int .|. Expr_If .|. Expr_Eq )) repr => repr h) expected = testCase (Text.unpack $ text_from_expr $ expr) $ (@?= expected) $ host_from_expr expr in [ Foldable.Test.e1 ==> [1::Int,1,2,2,3,3] ] ]