]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Repr/Host/Test.hs
Map
[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_If
97 .|. Expr_Eq )) repr => repr h) expected =
98 testCase (Text.unpack $ text_from_expr $ expr) $
99 (@?= expected) $
100 host_from_expr expr in
101 [ List.Test.e1 ==> [2::Int,4]
102 ]
103 , testGroup "Functor" $
104 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda
105 .|. Expr_List
106 .|. Expr_Functor
107 .|. Expr_Bool
108 .|. Expr_Int
109 .|. Expr_If
110 .|. Expr_Eq )) repr => repr h) expected =
111 testCase (Text.unpack $ (text_from_expr :: Repr_Text _h -> Text) $ expr) $
112 (@?= expected) $
113 host_from_expr expr in
114 [ Functor.Test.e1 ==> [2::Int,3,4]
115 ]
116 , testGroup "Applicative" $
117 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda
118 .|. Expr_List
119 .|. Expr_Functor
120 .|. Expr_Applicative
121 .|. Expr_Maybe
122 .|. Expr_Bool
123 .|. Expr_Int
124 .|. Expr_If
125 .|. Expr_Eq )) repr => repr h) expected =
126 testCase (Text.unpack $ text_from_expr $ expr) $
127 (@?= expected) $
128 host_from_expr expr in
129 [ Applicative.Test.e1 ==> Just (3::Int)
130 ]
131 , testGroup "Foldable" $
132 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda
133 .|. Expr_List
134 .|. Expr_Foldable
135 .|. Expr_Maybe
136 .|. Expr_Bool
137 .|. Expr_Int
138 .|. Expr_If
139 .|. Expr_Eq )) repr => repr h) expected =
140 testCase (Text.unpack $ text_from_expr $ expr) $
141 (@?= expected) $
142 host_from_expr expr in
143 [ Foldable.Test.e1 ==> [1::Int,1,2,2,3,3]
144 ]
145 ]