]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Repr/Host/Test.hs
factorizing Type1_From ast Type0
[haskell/symantic.git] / Language / Symantic / Repr / Host / Test.hs
1 {-# LANGUAGE ConstraintKinds #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 {-# LANGUAGE Rank2Types #-}
5 {-# LANGUAGE ScopedTypeVariables #-}
6 {-# LANGUAGE TypeOperators #-}
7
8 module Repr.Host.Test where
9
10 -- import Data.Function (($))
11 import Test.Tasty
12 import Test.Tasty.HUnit
13
14 import Data.Text (Text)
15 import qualified Data.Text as Text
16 import Prelude hiding (and, not, or, Monad(..), id)
17
18 import Language.Symantic.Repr
19 import Language.Symantic.Expr
20 import qualified Expr.Lambda.Test as Lambda.Test
21 import qualified Expr.Bool.Test as Bool.Test
22 import qualified Expr.Maybe.Test as Maybe.Test
23 import qualified Expr.If.Test as If.Test
24 import qualified Expr.List.Test as List.Test
25 import qualified Expr.Functor.Test as Functor.Test
26 import qualified Expr.Applicative.Test as Applicative.Test
27 import qualified Expr.Foldable.Test as Foldable.Test
28
29 tests :: TestTree
30 tests = testGroup "Host" $
31 [ testGroup "Bool" $
32 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda
33 .|. Expr_Bool
34 )) repr => repr h) expected =
35 testCase (Text.unpack $ text_from_expr $ expr) $
36 -- (>>= (@?= expected)) $
37 (@?= expected) $
38 host_from_expr expr in
39 [ Bool.Test.e1 ==> False
40 , Bool.Test.e2 ==> True
41 , Bool.Test.e3 ==> True
42 , Bool.Test.e4 ==> True
43 ]
44 , testGroup "Lambda" $
45 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda
46 .|. Expr_Bool
47 )) repr => repr h) expected =
48 testCase (Text.unpack $ text_from_expr $ expr) $
49 (@?= expected) $
50 host_from_expr expr in
51 [ (Lambda.Test.e1 $$ bool True $$ bool True) ==> False
52 , (Lambda.Test.e1 $$ bool True $$ bool False) ==> True
53 , (Lambda.Test.e1 $$ bool False $$ bool True) ==> True
54 , (Lambda.Test.e1 $$ bool False $$ bool False) ==> False
55
56 , (Lambda.Test.e2 $$ bool True $$ bool True) ==> False
57 , (Lambda.Test.e2 $$ bool True $$ bool False) ==> True
58 , (Lambda.Test.e2 $$ bool False $$ bool True) ==> True
59 , (Lambda.Test.e2 $$ bool False $$ bool False) ==> False
60
61 , Lambda.Test.e3 ==> True
62 , Lambda.Test.e4 ==> True
63
64 , (Lambda.Test.e5 $$ bool True $$ bool True) ==> True
65 , (Lambda.Test.e5 $$ bool True $$ bool False) ==> False
66 , (Lambda.Test.e5 $$ bool False $$ bool True) ==> False
67 , (Lambda.Test.e5 $$ bool False $$ bool False) ==> False
68
69 , Lambda.Test.e6 ==> False
70 , (Lambda.Test.e7 $$ lam id) ==> True
71 , (Lambda.Test.e7 $$ lam not) ==> False
72 ]
73 , testGroup "Maybe" $
74 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda
75 .|. Expr_Maybe
76 .|. Expr_Bool )) repr => repr h) expected =
77 testCase (Text.unpack $ text_from_expr $ expr) $
78 (@?= expected) $
79 host_from_expr expr in
80 [ Maybe.Test.e1 ==> False
81 ]
82 , testGroup "If" $
83 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda
84 .|. Expr_If
85 .|. Expr_Bool )) repr => repr h) expected =
86 testCase (Text.unpack $ text_from_expr $ expr) $
87 (@?= expected) $
88 host_from_expr expr in
89 [ If.Test.e1 ==> False
90 ]
91 , testGroup "List" $
92 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda
93 .|. Expr_List
94 .|. Expr_Bool
95 .|. Expr_Int
96 .|. Expr_Num
97 .|. Expr_Integral
98 .|. Expr_If
99 .|. Expr_Eq )) repr => repr h) expected =
100 testCase (Text.unpack $ text_from_expr $ expr) $
101 (@?= expected) $
102 host_from_expr expr in
103 [ List.Test.e1 ==> [2::Int,4]
104 ]
105 , testGroup "Functor" $
106 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda
107 .|. Expr_List
108 .|. Expr_Functor
109 .|. Expr_Bool
110 .|. Expr_Int
111 .|. Expr_Num
112 .|. Expr_If
113 .|. Expr_Eq )) repr => repr h) expected =
114 testCase (Text.unpack $ (text_from_expr :: Repr_Text _h -> Text) $ expr) $
115 (@?= expected) $
116 host_from_expr expr in
117 [ Functor.Test.e1 ==> [2::Int,3,4]
118 ]
119 , testGroup "Applicative" $
120 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda
121 .|. Expr_List
122 .|. Expr_Functor
123 .|. Expr_Applicative
124 .|. Expr_Maybe
125 .|. Expr_Bool
126 .|. Expr_Int
127 .|. Expr_Num
128 .|. Expr_If
129 .|. Expr_Eq )) repr => repr h) expected =
130 testCase (Text.unpack $ text_from_expr $ expr) $
131 (@?= expected) $
132 host_from_expr expr in
133 [ Applicative.Test.e1 ==> Just (3::Int)
134 ]
135 , testGroup "Foldable" $
136 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda
137 .|. Expr_List
138 .|. Expr_Foldable
139 .|. Expr_Maybe
140 .|. Expr_Bool
141 .|. Expr_Int
142 .|. Expr_Num
143 .|. Expr_If
144 .|. Expr_Eq )) repr => repr h) expected =
145 testCase (Text.unpack $ text_from_expr $ expr) $
146 (@?= expected) $
147 host_from_expr expr in
148 [ Foldable.Test.e1 ==> [1::Int,1,2,2,3,3]
149 ]
150 ]