1 {-# LANGUAGE ConstraintKinds #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 {-# LANGUAGE ScopedTypeVariables #-}
5 {-# LANGUAGE Rank2Types #-}
7 module Repr.Host.Test where
9 -- import Data.Function (($))
10 -- import Data.Functor.Identity (Identity)
12 import Test.Tasty.HUnit
13 import Prelude hiding (and, not, or)
15 import Language.LOL.Symantic.Repr
16 import Language.LOL.Symantic.Expr
17 import qualified Expr.Lambda.Test as Lambda.Test
18 import qualified Expr.Bool.Test as Bool.Test
19 import qualified Expr.Maybe.Test as Maybe.Test
20 import qualified Expr.If.Test as If.Test
23 tests = testGroup "Host" $
25 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Lambda_Bool IO) repr => repr h) expected =
26 testCase ((string_from_expr :: Repr_String IO _h -> String) $ expr) $
27 (>>= (@?= expected)) $
28 host_from_expr expr in
29 [ Bool.Test.e1 ==> False
30 , Bool.Test.e2 ==> True
31 , Bool.Test.e3 ==> True
32 , Bool.Test.e4 ==> True
34 , testGroup "Lambda" $
35 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Lambda_Bool IO) repr => repr h) expected =
36 testCase ((string_from_expr :: Repr_String IO _h -> String) $ expr) $
37 (>>= (@?= expected)) $
38 host_from_expr expr in
39 [ (Lambda.Test.e1 `app` bool True `app` bool True) ==> False
40 , (Lambda.Test.e1 `app` bool True `app` bool False) ==> True
41 , (Lambda.Test.e1 `app` bool False `app` bool True) ==> True
42 , (Lambda.Test.e1 `app` bool False `app` bool False) ==> False
44 , (Lambda.Test.e2 `app` bool True `app` bool True) ==> False
45 , (Lambda.Test.e2 `app` bool True `app` bool False) ==> True
46 , (Lambda.Test.e2 `app` bool False `app` bool True) ==> True
47 , (Lambda.Test.e2 `app` bool False `app` bool False) ==> False
49 , Lambda.Test.e3 ==> True
50 , Lambda.Test.e4 ==> True
52 , (Lambda.Test.e5 `app` bool True `app` bool True) ==> True
53 , (Lambda.Test.e5 `app` bool True `app` bool False) ==> False
54 , (Lambda.Test.e5 `app` bool False `app` bool True) ==> False
55 , (Lambda.Test.e5 `app` bool False `app` bool False) ==> False
57 , Lambda.Test.e6 ==> False
58 , (Lambda.Test.e7 `app` val id) ==> True
59 , (Lambda.Test.e7 `app` val not) ==> False
62 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Lambda_Maybe_Bool IO) repr => repr h) expected =
63 testCase ((string_from_expr :: Repr_String IO _h -> String) $ expr) $
64 (>>= (@?= expected)) $
65 host_from_expr expr in
66 [ Maybe.Test.e1 ==> False
69 let (==>) (expr::forall repr. Sym_of_Expr (Expr_Lambda_If_Bool IO) repr => repr h) expected =
70 testCase ((string_from_expr :: Repr_String IO _h -> String) $ expr) $
71 (>>= (@?= expected)) $
72 host_from_expr expr in
73 [ If.Test.e1 ==> False