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