]> Git — Sourcephile - haskell/symantic.git/blob - TFHOE/Repr/Host/Test.hs
init
[haskell/symantic.git] / TFHOE / Repr / Host / Test.hs
1 {-# LANGUAGE ConstraintKinds #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 {-# LANGUAGE ScopedTypeVariables #-}
5 {-# LANGUAGE Rank2Types #-}
6
7 module Repr.Host.Test where
8
9 -- import Data.Function (($))
10 -- import Data.Functor.Identity (Identity)
11 import Test.Tasty
12 import Test.Tasty.HUnit
13
14 import TFHOE.Type
15 import TFHOE.Repr
16 import TFHOE.Expr
17 import qualified Expr.Fun.Test as Fun.Test
18 import qualified Expr.Bool.Test as Bool.Test
19
20 tests :: TestTree
21 tests = testGroup "Host" $
22 let (==>) (expr::forall repr. Expr_from_Type (Type_Fun_Bool_End IO) repr => repr h) expected =
23 testCase ((string_repr :: Repr_String IO _h -> String) $ expr) $
24 (>>= (@?= expected)) $
25 host_repr expr in
26 [ testGroup "Bool"
27 [ Bool.Test.e1 ==> False
28 , Bool.Test.e2 ==> True
29 , Bool.Test.e3 ==> True
30 , Bool.Test.e4 ==> True
31 ]
32 , testGroup "Fun"
33 [ testGroup "Bool"
34 [ (Fun.Test.e1 `app` bool True `app` bool True) ==> False
35 , (Fun.Test.e1 `app` bool True `app` bool False) ==> True
36 , (Fun.Test.e1 `app` bool False `app` bool True) ==> True
37 , (Fun.Test.e1 `app` bool False `app` bool False) ==> False
38
39 , (Fun.Test.e2 `app` bool True `app` bool True) ==> False
40 , (Fun.Test.e2 `app` bool True `app` bool False) ==> True
41 , (Fun.Test.e2 `app` bool False `app` bool True) ==> True
42 , (Fun.Test.e2 `app` bool False `app` bool False) ==> False
43
44 , Fun.Test.e3 ==> True
45 , Fun.Test.e4 ==> True
46
47 , (Fun.Test.e5 `app` bool True `app` bool True) ==> True
48 , (Fun.Test.e5 `app` bool True `app` bool False) ==> False
49 , (Fun.Test.e5 `app` bool False `app` bool True) ==> False
50 , (Fun.Test.e5 `app` bool False `app` bool False) ==> False
51
52 , Fun.Test.e6 ==> False
53 , (Fun.Test.e7 `app` val id) ==> True
54 , (Fun.Test.e7 `app` val neg) ==> False
55 ]
56 ]
57 {-, testGroup "If"
58 [ If.e1 ==> "if True then False else True"
59 , If.e2 ==> "if True & True then False else True"
60 ]
61 -}]
62
63