]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Repr/Host/Test.hs
init
[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 Data.Functor.Identity (Identity)
12 import Test.Tasty
13 import Test.Tasty.HUnit
14
15 import Data.Text (Text)
16 import qualified Data.Text as Text
17 import Prelude hiding (and, not, or)
18
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
28
29 tests :: TestTree
30 tests = testGroup "Host" $
31 [ testGroup "Bool" $
32 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda_App IO
33 .|. Expr_Lambda_Val IO
34 .|. Expr_Bool
35 )) repr => repr h) expected =
36 testCase (Text.unpack $ (text_from_expr :: Repr_Text IO _h -> Text) $ expr) $
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_App IO
46 .|. Expr_Lambda_Val IO
47 .|. Expr_Bool
48 )) repr => repr h) expected =
49 testCase (Text.unpack $ (text_from_expr :: Repr_Text IO _h -> Text) $ expr) $
50 (>>= (@?= expected)) $
51 host_from_expr expr in
52 [ (Lambda.Test.e1 `app` bool True `app` bool True) ==> False
53 , (Lambda.Test.e1 `app` bool True `app` bool False) ==> True
54 , (Lambda.Test.e1 `app` bool False `app` bool True) ==> True
55 , (Lambda.Test.e1 `app` bool False `app` bool False) ==> False
56
57 , (Lambda.Test.e2 `app` bool True `app` bool True) ==> False
58 , (Lambda.Test.e2 `app` bool True `app` bool False) ==> True
59 , (Lambda.Test.e2 `app` bool False `app` bool True) ==> True
60 , (Lambda.Test.e2 `app` bool False `app` bool False) ==> False
61
62 , Lambda.Test.e3 ==> True
63 , Lambda.Test.e4 ==> True
64
65 , (Lambda.Test.e5 `app` bool True `app` bool True) ==> True
66 , (Lambda.Test.e5 `app` bool True `app` bool False) ==> False
67 , (Lambda.Test.e5 `app` bool False `app` bool True) ==> False
68 , (Lambda.Test.e5 `app` bool False `app` bool False) ==> False
69
70 , Lambda.Test.e6 ==> False
71 , (Lambda.Test.e7 `app` val id) ==> True
72 , (Lambda.Test.e7 `app` val not) ==> False
73 ]
74 , testGroup "Maybe" $
75 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda_App IO
76 .|. Expr_Lambda_Val IO
77 .|. Expr_Maybe IO
78 .|. Expr_Bool )) repr => repr h) expected =
79 testCase (Text.unpack $ (text_from_expr :: Repr_Text IO _h -> Text) $ expr) $
80 (>>= (@?= expected)) $
81 host_from_expr expr in
82 [ Maybe.Test.e1 ==> False
83 ]
84 , testGroup "If" $
85 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda_App IO
86 .|. Expr_Lambda_Val IO
87 .|. Expr_If
88 .|. Expr_Bool )) 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 [ If.Test.e1 ==> False
93 ]
94 , testGroup "List" $
95 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda_App IO
96 .|. Expr_Lambda_Val IO
97 .|. Expr_List IO
98 .|. Expr_Bool
99 .|. Expr_Int
100 .|. Expr_If
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 [ List.Test.e1 ==> [2::Int,4]
106 ]
107 , testGroup "Functor" $
108 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda_App IO
109 .|. Expr_Lambda_Val IO
110 .|. Expr_List IO
111 .|. Expr_Functor IO
112 .|. Expr_Bool
113 .|. Expr_Int
114 .|. Expr_If
115 .|. Expr_Eq )) repr => repr h) expected =
116 testCase (Text.unpack $ (text_from_expr :: Repr_Text IO _h -> Text) $ expr) $
117 (>>= (@?= expected)) $
118 host_from_expr expr in
119 [ Functor.Test.e1 ==> [2::Int,3,4]
120 ]
121 , testGroup "Applicative" $
122 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Root ( Expr_Lambda_App IO
123 .|. Expr_Lambda_Val IO
124 .|. Expr_List IO
125 .|. Expr_Functor IO
126 .|. Expr_Applicative IO
127 .|. Expr_Maybe IO
128 .|. Expr_Bool
129 .|. Expr_Int
130 .|. Expr_If
131 .|. Expr_Eq )) repr => repr h) expected =
132 testCase (Text.unpack $ (text_from_expr :: Repr_Text IO _h -> Text) $ expr) $
133 (>>= (@?= expected)) $
134 host_from_expr expr in
135 [ Applicative.Test.e1 ==> Just (3::Int)
136 ]
137 ]