1 {-# LANGUAGE ConstraintKinds #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 {-# LANGUAGE Rank2Types #-}
5 {-# LANGUAGE ScopedTypeVariables #-}
6 {-# LANGUAGE TypeOperators #-}
8 module Repr.Host.Test where
10 -- import Data.Function (($))
11 -- import Data.Functor.Identity (Identity)
13 import Test.Tasty.HUnit
15 import Data.Text (Text)
16 import qualified Data.Text as Text
17 import Prelude hiding (and, not, or)
19 import Language.Symantic.Repr
20 import Language.Symantic.Expr
21 import qualified Expr.Lambda.Test as Lambda.Test
22 import qualified Expr.Bool.Test as Bool.Test
23 import qualified Expr.Maybe.Test as Maybe.Test
24 import qualified Expr.If.Test as If.Test
25 import qualified Expr.List.Test as List.Test
26 import qualified Expr.Functor.Test as Functor.Test
27 import qualified Expr.Applicative.Test as Applicative.Test
30 tests = testGroup "Host" $
32 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root (Expr_Lambda IO .|. Expr_Bool)) repr => repr h) expected =
33 testCase (Text.unpack $ (text_from_expr :: Repr_Text IO _h -> Text) $ expr) $
34 (>>= (@?= expected)) $
35 host_from_expr expr in
36 [ Bool.Test.e1 ==> False
37 , Bool.Test.e2 ==> True
38 , Bool.Test.e3 ==> True
39 , Bool.Test.e4 ==> True
41 , testGroup "Lambda" $
42 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root (Expr_Lambda IO .|. Expr_Bool)) repr => repr h) expected =
43 testCase (Text.unpack $ (text_from_expr :: Repr_Text IO _h -> Text) $ expr) $
44 (>>= (@?= expected)) $
45 host_from_expr expr in
46 [ (Lambda.Test.e1 `app` bool True `app` bool True) ==> False
47 , (Lambda.Test.e1 `app` bool True `app` bool False) ==> True
48 , (Lambda.Test.e1 `app` bool False `app` bool True) ==> True
49 , (Lambda.Test.e1 `app` bool False `app` bool False) ==> False
51 , (Lambda.Test.e2 `app` bool True `app` bool True) ==> False
52 , (Lambda.Test.e2 `app` bool True `app` bool False) ==> True
53 , (Lambda.Test.e2 `app` bool False `app` bool True) ==> True
54 , (Lambda.Test.e2 `app` bool False `app` bool False) ==> False
56 , Lambda.Test.e3 ==> True
57 , Lambda.Test.e4 ==> True
59 , (Lambda.Test.e5 `app` bool True `app` bool True) ==> True
60 , (Lambda.Test.e5 `app` bool True `app` bool False) ==> False
61 , (Lambda.Test.e5 `app` bool False `app` bool True) ==> False
62 , (Lambda.Test.e5 `app` bool False `app` bool False) ==> False
64 , Lambda.Test.e6 ==> False
65 , (Lambda.Test.e7 `app` val id) ==> True
66 , (Lambda.Test.e7 `app` val not) ==> False
69 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root (Expr_Lambda IO .|. Expr_Maybe IO .|. Expr_Bool)) repr => repr h) expected =
70 testCase (Text.unpack $ (text_from_expr :: Repr_Text IO _h -> Text) $ expr) $
71 (>>= (@?= expected)) $
72 host_from_expr expr in
73 [ Maybe.Test.e1 ==> False
76 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root (Expr_Lambda IO .|. Expr_If .|. Expr_Bool)) repr => repr h) expected =
77 testCase (Text.unpack $ (text_from_expr :: Repr_Text IO _h -> Text) $ expr) $
78 (>>= (@?= expected)) $
79 host_from_expr expr in
80 [ If.Test.e1 ==> False
83 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda IO
88 .|. Expr_Eq )) repr => repr h) expected =
89 testCase (Text.unpack $ (text_from_expr :: Repr_Text IO _h -> Text) $ expr) $
90 (>>= (@?= expected)) $
91 host_from_expr expr in
92 [ List.Test.e1 ==> [2::Int,4]
94 , testGroup "Functor" $
95 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda IO
101 .|. Expr_Eq )) repr => repr h) expected =
102 testCase (Text.unpack $ (text_from_expr :: Repr_Text IO _h -> Text) $ expr) $
103 (>>= (@?= expected)) $
104 host_from_expr expr in
105 [ Functor.Test.e1 ==> [2::Int,3,4]
107 , testGroup "Applicative" $
108 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda IO
111 .|. Expr_Applicative IO
116 .|. Expr_Eq )) repr => repr h) expected =
117 testCase (Text.unpack $ (text_from_expr :: Repr_Text IO _h -> Text) $ expr) $
118 (>>= (@?= expected)) $
119 host_from_expr expr in
120 [ Applicative.Test.e1 ==> Just (3::Int)