]> Git — Sourcephile - haskell/symantic.git/blob - Language/Symantic/Typing/Test.hs
Add Gram_Term.
[haskell/symantic.git] / Language / Symantic / Typing / Test.hs
1 {-# LANGUAGE UndecidableInstances #-}
2 {-# OPTIONS_GHC -fno-warn-orphans #-}
3 module Typing.Test where
4
5 import Test.Tasty
6 import Test.Tasty.HUnit
7
8 import Control.Applicative (Applicative(..))
9 import Control.Arrow (left)
10 import Data.Maybe (isJust)
11 import Data.Proxy
12 import GHC.Exts (Constraint)
13 import Prelude hiding (exp)
14 import qualified Text.Megaparsec as P
15
16 import Language.Symantic.Lib.Data.Type.List
17 import Language.Symantic.Parsing.Grammar
18 import Language.Symantic.Typing
19 import Language.Symantic.Compiling ((~>))
20
21 import Parsing.Grammar.Test
22
23 -- * Tests
24 type Tys = Constants ++ '[Proxy String]
25 instance
26 ( ParsecC e s
27 , Gram_Meta meta (P.ParsecT e s m)
28 ) => Gram_Type meta (P.ParsecT e s m)
29
30 tests :: TestTree
31 tests = testGroup "Typing" $
32 [ testGroup "compile_type" $
33 let (==>) inp exp = testCase inp $ got @?= Right (Right exp)
34 where
35 got :: Either (P.ParseError Char P.Dec)
36 (Either (Error_Type P.SourcePos '[Proxy Token_Type])
37 (EType Tys))
38 got = (compile_etype <$>) $ (`runParser` inp) $ unCF p
39 p :: Gram_Type P.SourcePos p => CF p (TokType P.SourcePos)
40 p = typeG <* eoi in
41 uncurry (==>) <$>
42 [ ("Bool", EType $ ty @Bool)
43 , ("[]", EType $ ty @[])
44 , ("[Char]", EType $ ty @[] :$ ty @Char)
45 , ("[Char -> [Char]]", EType $ ty @[] :$ (ty @Char ~> ty @[] :$ ty @Char))
46 , ("([])", EType $ ty @[])
47 , ("[()]", EType $ ty @[] :$ ty @())
48 , ("()", EType $ ty @())
49 , ("(())", EType $ ty @())
50 , ("(,)", EType $ ty @(,))
51 , ("((,))", EType $ ty @(,))
52 , ("(,) Int", EType $ ty @(,) :$ ty @Int)
53 , ("(Bool)", EType $ ty @Bool)
54 , ("((Bool))", EType $ ty @Bool)
55 , ("(Bool, Int)", EType $ ty @(,) :$ ty @Bool :$ ty @Int)
56 , ("((Bool, Int))", EType $ ty @(,) :$ ty @Bool :$ ty @Int)
57 , ("((Bool, Int), Char)", EType $ ty @(,) :$ (ty @(,) :$ ty @Bool :$ ty @Int) :$ ty @Char)
58 , ("(Bool, Int) -> Char", EType $ (ty @(,) :$ ty @Bool :$ ty @Int) ~> ty @Char)
59 , ("(Bool -> Int)", EType $ ty @Bool ~> ty @Int)
60 , ("String", EType $ ty @[] :$ ty @Char)
61 , ("[Char] -> String", EType $ (ty @[] :$ ty @Char) ~> (ty @[] :$ ty @Char))
62 , ("String -> [Char]", EType $ (ty @[] :$ ty @Char) ~> (ty @[] :$ ty @Char))
63 , ("Maybe Bool", EType $ ty @Maybe :$ ty @Bool)
64 , ("Either Bool Int", EType $ ty @Either :$ ty @Bool :$ ty @Int)
65 , ("Bool -> Int", EType $ ty @Bool ~> ty @Int)
66 , ("(Bool -> Int) -> Char", EType $ (ty @Bool ~> ty @Int) ~> ty @Char)
67 , ("Bool -> (Int -> Char)", EType $ ty @Bool ~> (ty @Int ~> ty @Char))
68 , ("Bool -> Int -> Char", EType $ ty @Bool ~> ty @Int ~> ty @Char)
69 , ("Bool -> (Int -> Char) -> ()", EType $ ty @Bool ~> (ty @Int ~> ty @Char) ~> ty @())
70 , ("IO", EType $ ty @IO)
71 , ("Eq", EType $ ty @Eq)
72 , ("Eq Bool", EType $ ty @Eq :$ ty @Bool)
73 , ("Traversable IO", EType $ ty @Traversable :$ ty @IO)
74 , ("Monad IO", EType $ ty @Monad :$ ty @IO)
75 , ("(->) Bool", EType $ ty @(->) :$ ty @Bool)
76 , ("(->) (IO Bool)", EType $ ty @(->) :$ (ty @IO :$ ty @Bool))
77 , ("Monad IO", EType $ ty @Monad :$ ty @IO)
78 ]
79 , testGroup "Parsing errors" $
80 let (==>) inp _exp = testCase inp $ got @?= Left ()
81 where
82 got :: Either () (TokType P.SourcePos)
83 got = left (const ()) $ (`runParser` inp) $ unCF p
84 p :: Gram_Type P.SourcePos p => CF p (TokType P.SourcePos)
85 p = typeG <* eoi in
86 uncurry (==>) <$>
87 [ ("Bool, Int", ())
88 , ("(Bool -> Int) Char", ())
89 ]
90 , testGroup "Compiling errors" $
91 let (==>) inp _exp = testCase inp $ got @?= Right (Left ())
92 where
93 got :: Either (P.ParseError Char P.Dec) (Either () (EType Tys))
94 got = (left (const ()) . compile_etype <$>) $ (`runParser` inp) $ unCF p
95 p :: Gram_Type P.SourcePos p => CF p (TokType P.SourcePos)
96 p = typeG <* eoi in
97 uncurry (==>) <$>
98 [ ("NonExistingType", ())
99 , ("Bool Int", ())
100 , ("[IO]", ())
101 , ("(->) IO", ())
102 , ("(->) Bool Int Char", ())
103 , ("Monad Eq", ())
104 ]
105 , testGroup "proj_con" $
106 let (==>) (typ::Type Constants (h::Constraint)) expected =
107 testCase (show_type typ) $
108 isJust (proj_con typ) @?= expected in
109 [ ty @Eq :$ ty @Bool ==> True
110 , ty @Ord :$ ty @Bool ==> True
111 , ty @Functor :$ ty @Maybe ==> True
112 , ty @Functor :$ ty @IO ==> True
113 , ty @Monad :$ ty @IO ==> True
114 , ty @Traversable :$ ty @IO ==> False
115 ]
116 ]