1 module Compiling.Term.Test where
4 import Test.Tasty.HUnit
6 import qualified Control.Arrow as Arrow
7 import qualified Control.Monad as Monad
8 -- import Control.Monad.IO.Class (MonadIO(..))
9 import Data.Proxy (Proxy(..))
10 import Data.Text (Text)
11 import Data.Type.Equality ((:~:)(Refl))
14 import Language.Symantic.Parsing
15 import Language.Symantic.Typing
16 import Language.Symantic.Compiling
17 import Language.Symantic.Interpreting
28 , Show_Const (Consts_of_Ifaces is)
30 , Sym_of_Ifaces is HostI
31 , Sym_of_Ifaces is TextI
36 -> Either (Type (Consts_of_Ifaces is) h, Either (Error_Syntax ast) (Error_Term ast is))
37 (Type (Consts_of_Ifaces is) h, h, Text)
39 test_term_from _is syn expected =
40 testCase (elide $ show syn) $
42 Left err -> Left (Left err) @?= P.snd `Arrow.left` expected
43 Right (tok::EToken ast is) ->
44 case closed_term_from tok of
45 Left err -> Left (Right err) @?= P.snd `Arrow.left` expected
46 Right (ETerm typ (Term te)) ->
48 Left (_, err) -> Right ("…"::Text) @?= Left err
49 Right (ty_expected::Type (Consts_of_Ifaces is) h, _::h, _::Text) ->
50 (Monad.>>= (@?= (\(_::Type (Consts_of_Ifaces is) h, err) -> err) `Arrow.left` expected)) $
51 case typ `eq_type` ty_expected of
52 Nothing -> Monad.return $ Left $ Right $
53 Error_Term_Constraint_Type $ Right $
55 (Right $ At Nothing $ EType typ)
56 (At Nothing $ EType ty_expected)
58 let h = host_from_term te
64 -- , (text_from_term :: Repr_Text h -> Text) r
67 elide s | P.length s P.> 42 = P.take 42 s P.++ ['…']