{-# LANGUAGE Safe #-}
module Test.TypeInstance (tests) where
import Control.Monad (when)
import qualified Data.Map as Map
import Base.CompileError
import Base.CompileInfo
import Base.MergeTree
import Base.Mergeable
import Parser.TypeInstance ()
import Test.Common
import Types.GeneralType
import Types.Positional
import Types.TypeInstance
import Types.Variance
tests :: [IO (CompileInfo ())]
tests :: [IO (CompileInfo ())]
tests = [
String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess
String
"Type0"
(TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type0") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])),
String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess
String
"Type0<Type1,Type2>"
(TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type0") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type1") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type2") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])
])),
String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess
String
"#x"
(TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ Bool -> ParamName -> TypeInstanceOrParam
JustParamName Bool
False (ParamName -> TypeInstanceOrParam)
-> ParamName -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ String -> ParamName
ParamName String
"#x"),
String -> IO (CompileInfo ())
checkParseFail String
"x",
String -> IO (CompileInfo ())
checkParseFail String
"",
String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess
String
"[Type0&Type0]"
(TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type0") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])),
String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess
String
"[Type0|Type0]"
(TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type0") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])),
String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess String
"all" GeneralInstance
forall a. Bounded a => a
minBound,
String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess String
"any" GeneralInstance
forall a. Bounded a => a
maxBound,
String -> IO (CompileInfo ())
checkParseFail String
"[Type0]",
String -> IO (CompileInfo ())
checkParseFail String
"[]",
String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess
String
"[Type1&Type0&Type1]"
([GeneralInstance] -> GeneralInstance
forall a (f :: * -> *). (Mergeable a, Foldable f) => f a -> a
mergeAll [
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type0") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type1") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])
]),
String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess
String
"[Type1|Type0|Type1]"
([GeneralInstance] -> GeneralInstance
forall a (f :: * -> *). (Mergeable a, Foldable f) => f a -> a
mergeAny [
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type0") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type1") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])
]),
String -> IO (CompileInfo ())
checkParseFail String
"[Type0&Type1|Type2]",
String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess
String
"[Type0<#x>&#x]"
([GeneralInstance] -> GeneralInstance
forall a (f :: * -> *). (Mergeable a, Foldable f) => f a -> a
mergeAll [
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type0") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ Bool -> ParamName -> TypeInstanceOrParam
JustParamName Bool
False (ParamName -> TypeInstanceOrParam)
-> ParamName -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ String -> ParamName
ParamName String
"#x"
]),
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ Bool -> ParamName -> TypeInstanceOrParam
JustParamName Bool
False (ParamName -> TypeInstanceOrParam)
-> ParamName -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ String -> ParamName
ParamName String
"#x"
]),
String -> IO (CompileInfo ())
checkParseFail String
"[Type0&]",
String -> IO (CompileInfo ())
checkParseFail String
"[Type0|]",
String -> IO (CompileInfo ())
checkParseFail String
"[Type0 Type1]",
String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess
String
"[Type0&[Type1&Type3]&Type2]"
([GeneralInstance] -> GeneralInstance
forall a (f :: * -> *). (Mergeable a, Foldable f) => f a -> a
mergeAll [
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type0") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type1") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type2") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type3") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])
]),
String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess
String
"[Type0|[Type1|Type3]|Type2]"
([GeneralInstance] -> GeneralInstance
forall a (f :: * -> *). (Mergeable a, Foldable f) => f a -> a
mergeAny [
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type0") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type1") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type2") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type3") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])
]),
String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess
String
"[Type0&[Type1|Type3]&Type2]"
([GeneralInstance] -> GeneralInstance
forall a (f :: * -> *). (Mergeable a, Foldable f) => f a -> a
mergeAll [
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type0") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type2") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
[GeneralInstance] -> GeneralInstance
forall a (f :: * -> *). (Mergeable a, Foldable f) => f a -> a
mergeAny [
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type1") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type3") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])
]
]),
String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess
String
"[Type0|[Type1&Type3]|Type2]"
([GeneralInstance] -> GeneralInstance
forall a (f :: * -> *). (Mergeable a, Foldable f) => f a -> a
mergeAny [
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type0") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type2") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
[GeneralInstance] -> GeneralInstance
forall a (f :: * -> *). (Mergeable a, Foldable f) => f a -> a
mergeAll [
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type1") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstance -> TypeInstanceOrParam
JustTypeInstance (TypeInstance -> TypeInstanceOrParam)
-> TypeInstance -> TypeInstanceOrParam
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Type3") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])
]
]),
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"Type0"
String
"Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"Type3"
String
"Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"Type0"
String
"Type3",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"Type1<Type0>"
String
"Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"Type0"
String
"Type1<Type0>",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"Type2<Type0,Type0,Type0>"
String
"Type2<Type0,Type0,Type0>",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"Type2<Type0,Type0,Type3>"
String
"Type2<Type3,Type0,Type0>",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"Type2<Type3,Type0,Type3>"
String
"Type2<Type0,Type0,Type0>",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"Type2<Type0,Type0,Type0>"
String
"Type2<Type3,Type0,Type3>",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"Type2<Type0,Type3,Type0>"
String
"Type2<Type0,Type0,Type0>",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"Type2<Type0,Type0,Type0>"
String
"Type2<Type0,Type3,Type0>",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"Type3"
String
"[Type0|Type3]",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"Type3"
String
"[Type0|Type1<Type0>]",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"[Type3|Type1<Type0>]"
String
"Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"[Type0&Type3]"
String
"Type3",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"[Type3|Type3]"
String
"Type3",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"[Type1<Type0>&Type3]"
String
"[Type1<Type0>|Type3]",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"[Type0|Type3]"
String
"Type3",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"Type0"
String
"[Type0&Type3]",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"[Type0|Type3]"
String
"[Type0&Type3]",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"[Type1<Type0>&Type4<Type0>]"
String
"[[Type1<Type0>&Type4<Type0>]|Type5<Type0>]",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"[[Type1<Type0>|Type4<Type0>]&Type5<Type0>]"
String
"[Type1<Type0>|Type4<Type0>]",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"any"
String
"any",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"Type0"
String
"any",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"any"
String
"Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"all"
String
"all",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"Type0"
String
"all",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"all"
String
"Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"all"
String
"any",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"any"
String
"all",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"Type1<Type0>"
String
"Type1<any>",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"Type1<all>"
String
"Type1<Type0>",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"Type1<all>"
String
"Type1<any>",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"Type1<any>"
String
"Type1<all>",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"Type1<any>"
String
"Type1<any>",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"Type1<all>"
String
"Type1<all>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[])]
String
"#x" String
"#x",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail
[(String
"#x",[]),
(String
"#y",[])]
String
"#x" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires #y"]),
(String
"#y",[String
"allows #x"])]
String
"#x" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires #y"]),
(String
"#y",[])]
String
"#x" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[]),
(String
"#y",[String
"allows #x"])]
String
"#x" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires #y",String
"defines Instance0"]),
(String
"#y",[String
"allows #x"])]
String
"#x" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires #y"]),
(String
"#y",[String
"allows #x",String
"defines Instance0"])]
String
"#x" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires #y",String
"defines Instance0"]),
(String
"#y",[String
"allows #x",String
"defines Instance0"])]
String
"#x" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail
[(String
"#x",[String
"defines Instance0"]),
(String
"#y",[String
"defines Instance0"])]
String
"#x" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires Type0",String
"defines Instance0"])]
String
"#x" String
"Type0",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"allows Type0",String
"defines Instance0"])]
String
"Type0" String
"#x",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires #z"]),
(String
"#y",[String
"allows #z"]),
(String
"#z",[])]
String
"#x" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires #z"]),
(String
"#y",[]),
(String
"#z",[String
"requires #y"])]
String
"#x" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail
[(String
"#w",[String
"allows #x"]),
(String
"#x",[]),
(String
"#y",[]),
(String
"#z",[String
"allows #w",String
"requires #y"])]
String
"#x" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires Type3"]),
(String
"#y",[String
"allows Type0"])]
String
"#x" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires #y"]),
(String
"#y",[String
"requires Type3"])]
String
"#x" String
"Type0",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"allows #y"]),
(String
"#y",[String
"allows Type0"])]
String
"Type3" String
"#x",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[])]
String
"Type2<Type0,Type0,#x>" String
"Type2<Type0,Type0,#x>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail
[(String
"#x",[]),
(String
"#y",[])]
String
"Type2<Type0,Type0,#x>" String
"Type2<Type0,Type0,#y>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires #y"]),
(String
"#y",[String
"allows #x"])]
String
"Type2<Type0,Type0,#x>" String
"Type2<Type0,Type0,#y>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires #y"]),
(String
"#y",[])]
String
"Type2<Type0,Type0,#x>" String
"Type2<Type0,Type0,#y>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[]),
(String
"#y",[String
"allows #x"])]
String
"Type2<Type0,Type0,#x>" String
"Type2<Type0,Type0,#y>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[])]
String
"Type2<#x,Type0,Type0>" String
"Type2<#x,Type0,Type0>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail
[(String
"#x",[]),
(String
"#y",[])]
String
"Type2<#x,Type0,Type0>" String
"Type2<#y,Type0,Type0>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail
[(String
"#x",[String
"requires #y"]),
(String
"#y",[String
"allows #x"])]
String
"Type2<#x,Type0,Type0>" String
"Type2<#y,Type0,Type0>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail
[(String
"#x",[String
"requires #y"]),
(String
"#y",[])]
String
"Type2<#x,Type0,Type0>" String
"Type2<#y,Type0,Type0>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail
[(String
"#x",[]),
(String
"#y",[String
"allows #x"])]
String
"Type2<#x,Type0,Type0>" String
"Type2<#y,Type0,Type0>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"allows #y"]),
(String
"#y",[String
"requires #x"])]
String
"Type2<#x,Type0,Type0>" String
"Type2<#y,Type0,Type0>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"allows #y"]),
(String
"#y",[])]
String
"Type2<#x,Type0,Type0>" String
"Type2<#y,Type0,Type0>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[]),
(String
"#y",[String
"requires #x"])]
String
"Type2<#x,Type0,Type0>" String
"Type2<#y,Type0,Type0>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail
[(String
"#x",[])]
String
"#x" String
"Type0",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires Type0"])]
String
"#x" String
"Type0",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires Type3"])]
String
"#x" String
"Type0",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail
[(String
"#x",[])]
String
"Type0" String
"#x",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"allows Type0"])]
String
"Type0" String
"#x",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"allows Type0"])]
String
"Type3" String
"#x",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail
[(String
"#x",[])]
String
"Type2<#x,Type0,Type0>" String
"Type2<Type0,Type0,Type0>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"allows Type0"])]
String
"Type2<#x,Type0,Type0>" String
"Type2<Type0,Type0,Type0>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"allows Type0"])]
String
"Type2<#x,Type0,Type0>" String
"Type2<Type3,Type0,Type0>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail
[(String
"#x",[])]
String
"Type2<Type0,Type0,Type0>" String
"Type2<#x,Type0,Type0>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires Type0"])]
String
"Type2<Type0,Type0,Type0>" String
"Type2<#x,Type0,Type0>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires Type3"])]
String
"Type2<Type0,Type0,Type0>" String
"Type2<#x,Type0,Type0>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[]
String
"Type4<Type0>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[String
"allows Type0"])]
String
"Type4<[#x&Type0]>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[String
"allows Type0"])]
String
"Type4<[#x|Type0]>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[String
"allows Type0"])]
String
"Type4<[#x|Type3]>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail Resolver
Resolver
[]
String
"Type5<#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[])]
String
"Type5<#x>",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires #y"]),
(String
"#y",[String
"requires #z"]),
(String
"#z",[])]
String
"#x" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"allows #z"]),
(String
"#y",[String
"allows #x"]),
(String
"#z",[])]
String
"#x" String
"#y",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"any"
String
"any",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"all"
String
"all",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"all"
String
"any",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[]),
(String
"#y",[])]
String
"[#x&#y]" String
"[#x&#y]",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[]),
(String
"#y",[])]
String
"[#x&#y]" String
"[#x|#y]",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[]),
(String
"#y",[])]
String
"[#x|#y]" String
"[#x|#y]",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[]),
(String
"#y",[String
"defines Instance0"])]
String
"[#x&#y]" String
"[#x|#y]",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[]),
(String
"#y",[String
"defines Instance0"])]
String
"[#x&#y]" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail
[(String
"#x",[]),
(String
"#y",[String
"defines Instance0"])]
String
"[#x|#y]" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[]),
(String
"#y",[String
"requires Type3"])]
String
"[#x&#y]" String
"[#x|#y]",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[]),
(String
"#y",[String
"requires Type3"])]
String
"[#x&#y]" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail
[(String
"#x",[]),
(String
"#y",[String
"requires Type3"])]
String
"[#x|#y]" String
"#y",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[])]
String
"all" String
"#x",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"defines Instance0"])]
String
"all" String
"#x",
[(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess
[(String
"#x",[String
"requires Type3"])]
String
"all" String
"#x",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"optional Type0"
String
"optional Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"weak Type0"
String
"weak Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"Type0"
String
"optional Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"Type0"
String
"weak Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"optional Type0"
String
"weak Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"optional Type0"
String
"Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"weak Type0"
String
"Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertFail
String
"weak Type0"
String
"optional Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"optional Type3"
String
"optional Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"weak Type3"
String
"weak Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"Type3"
String
"optional Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"Type3"
String
"weak Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"optional Type3"
String
"weak Type0",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"any"
String
"optional any",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"Type3"
String
"optional any",
String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess
String
"optional all"
String
"optional Type3",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[])]
String
"#x",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail Resolver
Resolver
[(String
"#x",[])]
String
"Type1<#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail Resolver
Resolver
[(String
"#x",[String
"requires Type3"])]
String
"Type1<#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail Resolver
Resolver
[(String
"#x",[String
"defines Instance0"])]
String
"Type1<#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail Resolver
Resolver
[]
String
"Type1<all>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[String
"requires Type3",String
"defines Instance0"])]
String
"Type1<#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[]
String
"Type1<Type3>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail Resolver
Resolver
[]
String
"Type1<Type1<Type3>>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[]
String
"Type2<Type0,Type0,Type0>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail Resolver
Resolver
[]
String
"Type2<all,Type0,Type0>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail Resolver
Resolver
[]
String
"Type2<any,Type0,Type0>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[]
String
"Type4<any>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail Resolver
Resolver
[]
String
"Type4<all>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[String
"defines Instance1<Type0>",
String
"defines Instance1<#x>",
String
"defines Instance1<Type3>"])]
String
"Type2<#x,#x,#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail Resolver
Resolver
[(String
"#x",[String
"defines Instance1<#x>",
String
"defines Instance1<Type3>"])]
String
"Type2<#x,#x,#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail Resolver
Resolver
[(String
"#x",[String
"defines Instance1<Type0>",
String
"defines Instance1<Type3>"])]
String
"Type2<#x,#x,#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[String
"defines Instance1<Type0>",
String
"defines Instance1<#x>"])]
String
"Type2<#x,#x,#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[String
"allows Type0",
String
"defines Instance1<#x>"])]
String
"Type2<#x,#x,#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail Resolver
Resolver
[(String
"#x",[String
"allows Type3",
String
"defines Instance1<#x>"])]
String
"Type2<#x,#x,#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[]
String
"Type4<Type0>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail Resolver
Resolver
[]
String
"Type5<#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[])]
String
"Type5<#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[]
String
"[Type4<Type0>|Type1<Type3>]",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[]
String
"[Type4<Type0>&Type1<Type3>]",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[])]
String
"[Type5<#x>|Type1<Type3>]",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[])]
String
"[Type5<#x>&Type1<Type3>]",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[])]
String
"[#x|Type1<Type3>]",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[])]
String
"[#x&Type1<Type3>]",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail Resolver
Resolver
[(String
"#x",[])]
String
"[Type4<Type0>|Instance0]",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail Resolver
Resolver
[(String
"#x",[])]
String
"[Type4<Type0>&Instance0]",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[]
String
"[[Type4<Type0>&Type1<Type3>]|Type1<Type3>]",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[]
String
"[[Type4<Type0>|Type1<Type3>]&Type1<Type3>]",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[])]
String
"[[Type4<Type0>&#x]|Type1<Type3>]",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess Resolver
Resolver
[(String
"#x",[])]
String
"[[Type4<Type0>|#x]&Type1<Type3>]",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkDefinesFail Resolver
Resolver
[(String
"#x",[])]
String
"Instance1<#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkDefinesSuccess Resolver
Resolver
[(String
"#x",[String
"requires Type3"])]
String
"Instance1<#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkDefinesFail Resolver
Resolver
[(String
"#x",[String
"defines Instance1<#x>"])]
String
"Instance1<#x>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkDefinesSuccess Resolver
Resolver
[]
String
"Instance1<Type3>",
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ Resolver -> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkDefinesSuccess Resolver
Resolver
[]
String
"Instance1<Type1<Type3>>",
[(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceSuccess
[(String
"#x",[])] [String
"#x"]
String
"Type1<Type0>" String
"Type1<#x>"
((String, String, Variance) -> MergeTree (String, String, Variance)
forall a. a -> MergeTree a
mergeLeaf (String
"#x",String
"Type0",Variance
Invariant)),
[(String, [String])]
-> [String] -> String -> String -> IO (CompileInfo ())
checkInferenceFail
[(String
"#x",[])] [String
"#x"]
String
"Type1<Type3>" String
"Type4<#x>",
[(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceSuccess
[(String
"#x",[])] [String
"#x"]
String
"Type1<Type1<Type1<Type0>>>" String
"Type1<Type1<Type1<#x>>>"
((String, String, Variance) -> MergeTree (String, String, Variance)
forall a. a -> MergeTree a
mergeLeaf (String
"#x",String
"Type0",Variance
Invariant)),
[(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceSuccess
[(String
"#x",[])] [String
"#x"]
String
"Instance1<Type1<Type3>>" String
"Instance1<#x>"
((String, String, Variance) -> MergeTree (String, String, Variance)
forall a. a -> MergeTree a
mergeLeaf (String
"#x",String
"Type1<Type3>",Variance
Contravariant)),
[(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceSuccess
[(String
"#x",[])] [String
"#x"]
String
"Instance1<Type1<Type3>>" String
"Instance1<Type1<#x>>"
((String, String, Variance) -> MergeTree (String, String, Variance)
forall a. a -> MergeTree a
mergeLeaf (String
"#x",String
"Type3",Variance
Invariant)),
[(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceSuccess
[(String
"#x",[])] [String
"#x"]
String
"Type2<Type3,Type0,Type3>" String
"Type2<#x,Type0,#x>"
([MergeTree (String, String, Variance)]
-> MergeTree (String, String, Variance)
forall a (f :: * -> *). (Mergeable a, Foldable f) => f a -> a
mergeAll [(String, String, Variance) -> MergeTree (String, String, Variance)
forall a. a -> MergeTree a
mergeLeaf (String
"#x",String
"Type3",Variance
Contravariant),
(String, String, Variance) -> MergeTree (String, String, Variance)
forall a. a -> MergeTree a
mergeLeaf (String
"#x",String
"Type3",Variance
Covariant)]),
[(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceSuccess
[(String
"#x",[]),(String
"#y",[])] [String
"#x"]
String
"Type2<Type3,#y,Type3>" String
"Type2<#x,#y,#x>"
([MergeTree (String, String, Variance)]
-> MergeTree (String, String, Variance)
forall a (f :: * -> *). (Mergeable a, Foldable f) => f a -> a
mergeAll [(String, String, Variance) -> MergeTree (String, String, Variance)
forall a. a -> MergeTree a
mergeLeaf (String
"#x",String
"Type3",Variance
Contravariant),
(String, String, Variance) -> MergeTree (String, String, Variance)
forall a. a -> MergeTree a
mergeLeaf (String
"#x",String
"Type3",Variance
Covariant)]),
[(String, [String])]
-> [String] -> String -> String -> IO (CompileInfo ())
checkInferenceFail
[(String
"#x",[]),(String
"#y",[])] [String
"#x"]
String
"Type2<Type3,Type0,Type3>" String
"Type2<#x,#y,#x>",
[(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceSuccess
[(String
"#x",[]),(String
"#y",[])] [String
"#x"]
String
"Type2<Type3,#y,Type0>" String
"Type1<#x>"
((String, String, Variance) -> MergeTree (String, String, Variance)
forall a. a -> MergeTree a
mergeLeaf (String
"#x",String
"Type3",Variance
Invariant)),
[(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceSuccess
[(String
"#x",[]),(String
"#y",[])] [String
"#x"]
String
"Instance1<#y>" String
"Instance1<#x>"
((String, String, Variance) -> MergeTree (String, String, Variance)
forall a. a -> MergeTree a
mergeLeaf (String
"#x",String
"#y",Variance
Contravariant)),
[(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceSuccess
[(String
"#x",[])] [String
"#x"]
String
"Instance1<Instance0>" String
"Instance1<[#x&Type0]>"
((String, String, Variance) -> MergeTree (String, String, Variance)
forall a. a -> MergeTree a
mergeLeaf (String
"#x",String
"Instance0",Variance
Contravariant)),
[(String, [String])]
-> [String] -> String -> String -> IO (CompileInfo ())
checkInferenceFail
[(String
"#x",[])] [String
"#x"]
String
"Instance1<Instance0>" String
"Instance1<[#x|Type0]>",
[(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceSuccess
[(String
"#x",[])] [String
"#x"]
String
"Instance1<Type1<Type0>>" String
"Instance1<[Type0&Type1<#x>]>"
((String, String, Variance) -> MergeTree (String, String, Variance)
forall a. a -> MergeTree a
mergeLeaf (String
"#x",String
"Type0",Variance
Invariant)),
[(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceSuccess
[(String
"#x",[])] [String
"#x"]
String
"Instance1<Type1<Type0>>" String
"Instance1<[#x&Type1<#x>]>"
([MergeTree (String, String, Variance)]
-> MergeTree (String, String, Variance)
forall a (f :: * -> *). (Mergeable a, Foldable f) => f a -> a
mergeAny [(String, String, Variance) -> MergeTree (String, String, Variance)
forall a. a -> MergeTree a
mergeLeaf (String
"#x",String
"Type0",Variance
Invariant),
(String, String, Variance) -> MergeTree (String, String, Variance)
forall a. a -> MergeTree a
mergeLeaf (String
"#x",String
"Type1<Type0>",Variance
Contravariant)]),
[(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceSuccess
[(String
"#x",[]),(String
"#y",[String
"allows #x"])] [String
"#x"]
String
"Type0" String
"#y"
((String, String, Variance) -> MergeTree (String, String, Variance)
forall a. a -> MergeTree a
mergeLeaf (String
"#x",String
"Type0",Variance
Covariant))
]
type0 :: CategoryName
type0 :: CategoryName
type0 = String -> CategoryName
CategoryName String
"Type0"
type1 :: CategoryName
type1 :: CategoryName
type1 = String -> CategoryName
CategoryName String
"Type1"
type2 :: CategoryName
type2 :: CategoryName
type2 = String -> CategoryName
CategoryName String
"Type2"
type3 :: CategoryName
type3 :: CategoryName
type3 = String -> CategoryName
CategoryName String
"Type3"
type4 :: CategoryName
type4 :: CategoryName
type4 = String -> CategoryName
CategoryName String
"Type4"
type5 :: CategoryName
type5 :: CategoryName
type5 = String -> CategoryName
CategoryName String
"Type5"
instance0 :: CategoryName
instance0 :: CategoryName
instance0 = String -> CategoryName
CategoryName String
"Instance0"
instance1 :: CategoryName
instance1 :: CategoryName
instance1 = String -> CategoryName
CategoryName String
"Instance1"
variances :: Map.Map CategoryName InstanceVariances
variances :: Map CategoryName InstanceVariances
variances = [(CategoryName, InstanceVariances)]
-> Map CategoryName InstanceVariances
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName, InstanceVariances)]
-> Map CategoryName InstanceVariances)
-> [(CategoryName, InstanceVariances)]
-> Map CategoryName InstanceVariances
forall a b. (a -> b) -> a -> b
$ [
(CategoryName
type0,[Variance] -> InstanceVariances
forall a. [a] -> Positional a
Positional []),
(CategoryName
type1,[Variance] -> InstanceVariances
forall a. [a] -> Positional a
Positional [Variance
Invariant]),
(CategoryName
type2,[Variance] -> InstanceVariances
forall a. [a] -> Positional a
Positional [Variance
Contravariant,Variance
Invariant,Variance
Covariant]),
(CategoryName
type3,[Variance] -> InstanceVariances
forall a. [a] -> Positional a
Positional []),
(CategoryName
type4,[Variance] -> InstanceVariances
forall a. [a] -> Positional a
Positional [Variance
Invariant]),
(CategoryName
type5,[Variance] -> InstanceVariances
forall a. [a] -> Positional a
Positional [Variance
Invariant]),
(CategoryName
instance0,[Variance] -> InstanceVariances
forall a. [a] -> Positional a
Positional []),
(CategoryName
instance1,[Variance] -> InstanceVariances
forall a. [a] -> Positional a
Positional [Variance
Contravariant])
]
refines :: Map.Map CategoryName (Map.Map CategoryName (InstanceParams -> InstanceParams))
refines :: Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
refines = [(CategoryName,
Map CategoryName (InstanceParams -> InstanceParams))]
-> Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName,
Map CategoryName (InstanceParams -> InstanceParams))]
-> Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams)))
-> [(CategoryName,
Map CategoryName (InstanceParams -> InstanceParams))]
-> Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
forall a b. (a -> b) -> a -> b
$ [
(CategoryName
type0,[(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams))
-> [(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall a b. (a -> b) -> a -> b
$ []),
(CategoryName
type1,[(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams))
-> [(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall a b. (a -> b) -> a -> b
$ [
(CategoryName
type0,\(Positional [GeneralInstance
_]) ->
[GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])
]),
(CategoryName
type2,[(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams))
-> [(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall a b. (a -> b) -> a -> b
$ [
(CategoryName
type0,\(Positional [GeneralInstance
_,GeneralInstance
_,GeneralInstance
_]) ->
[GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
(CategoryName
type1,\(Positional [GeneralInstance
x,GeneralInstance
_,GeneralInstance
_]) ->
[GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [GeneralInstance
x])
]),
(CategoryName
type3,[(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams))
-> [(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall a b. (a -> b) -> a -> b
$ [
(CategoryName
type0,\(Positional []) ->
[GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])
]),
(CategoryName
type4,[(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams))
-> [(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall a b. (a -> b) -> a -> b
$ []),
(CategoryName
type5,[(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams))
-> [(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall a b. (a -> b) -> a -> b
$ [])
]
defines :: Map.Map CategoryName (Map.Map CategoryName (InstanceParams -> InstanceParams))
defines :: Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
defines = [(CategoryName,
Map CategoryName (InstanceParams -> InstanceParams))]
-> Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName,
Map CategoryName (InstanceParams -> InstanceParams))]
-> Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams)))
-> [(CategoryName,
Map CategoryName (InstanceParams -> InstanceParams))]
-> Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
forall a b. (a -> b) -> a -> b
$ [
(CategoryName
type0,[(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams))
-> [(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall a b. (a -> b) -> a -> b
$ [
(CategoryName
instance1,\(Positional []) ->
[GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [String -> GeneralInstance
forall a. ParseFromSource a => String -> a
forceParse String
"Type0"])
]),
(CategoryName
type1,[(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams))
-> [(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall a b. (a -> b) -> a -> b
$ []),
(CategoryName
type2,[(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams))
-> [(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall a b. (a -> b) -> a -> b
$ []),
(CategoryName
type3,[(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams))
-> [(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall a b. (a -> b) -> a -> b
$ [
(CategoryName
instance0,\(Positional []) ->
[GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])
]),
(CategoryName
type4,[(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams))
-> [(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall a b. (a -> b) -> a -> b
$ []),
(CategoryName
type5,[(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams))
-> [(CategoryName, InstanceParams -> InstanceParams)]
-> Map CategoryName (InstanceParams -> InstanceParams)
forall a b. (a -> b) -> a -> b
$ [])
]
typeFilters :: Map.Map CategoryName (InstanceParams -> InstanceFilters)
typeFilters :: Map CategoryName (InstanceParams -> InstanceFilters)
typeFilters = [(CategoryName, InstanceParams -> InstanceFilters)]
-> Map CategoryName (InstanceParams -> InstanceFilters)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName, InstanceParams -> InstanceFilters)]
-> Map CategoryName (InstanceParams -> InstanceFilters))
-> [(CategoryName, InstanceParams -> InstanceFilters)]
-> Map CategoryName (InstanceParams -> InstanceFilters)
forall a b. (a -> b) -> a -> b
$ [
(CategoryName
type0,\(Positional []) -> [[TypeFilter]] -> InstanceFilters
forall a. [a] -> Positional a
Positional []),
(CategoryName
type1,\(Positional [GeneralInstance
_]) ->
[[TypeFilter]] -> InstanceFilters
forall a. [a] -> Positional a
Positional [
[String -> TypeFilter
forall a. ParseFromSource a => String -> a
forceParse String
"requires Type0",String -> TypeFilter
forall a. ParseFromSource a => String -> a
forceParse String
"defines Instance0"]
]),
(CategoryName
type2,\(Positional [GeneralInstance
_,GeneralInstance
y,GeneralInstance
_]) ->
[[TypeFilter]] -> InstanceFilters
forall a. [a] -> Positional a
Positional [
[String -> TypeFilter
forall a. ParseFromSource a => String -> a
forceParse (String -> TypeFilter) -> String -> TypeFilter
forall a b. (a -> b) -> a -> b
$ String
"defines Instance1<Type3>"],
[String -> TypeFilter
forall a. ParseFromSource a => String -> a
forceParse (String -> TypeFilter) -> String -> TypeFilter
forall a b. (a -> b) -> a -> b
$ String
"defines Instance1<" String -> String -> String
forall a. [a] -> [a] -> [a]
++ GeneralInstance -> String
forall a. Show a => a -> String
show GeneralInstance
y String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
">"],
[String -> TypeFilter
forall a. ParseFromSource a => String -> a
forceParse (String -> TypeFilter) -> String -> TypeFilter
forall a b. (a -> b) -> a -> b
$ String
"defines Instance1<Type0>"]
]),
(CategoryName
type3,\(Positional []) -> [[TypeFilter]] -> InstanceFilters
forall a. [a] -> Positional a
Positional []),
(CategoryName
type4,\(Positional [GeneralInstance
_]) ->
[[TypeFilter]] -> InstanceFilters
forall a. [a] -> Positional a
Positional [
[String -> TypeFilter
forall a. ParseFromSource a => String -> a
forceParse String
"allows Type0"]
]),
(CategoryName
type5,\(Positional [GeneralInstance
_]) -> [[TypeFilter]] -> InstanceFilters
forall a. [a] -> Positional a
Positional [[]])
]
definesFilters :: Map.Map CategoryName (InstanceParams -> InstanceFilters)
definesFilters :: Map CategoryName (InstanceParams -> InstanceFilters)
definesFilters = [(CategoryName, InstanceParams -> InstanceFilters)]
-> Map CategoryName (InstanceParams -> InstanceFilters)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(CategoryName, InstanceParams -> InstanceFilters)]
-> Map CategoryName (InstanceParams -> InstanceFilters))
-> [(CategoryName, InstanceParams -> InstanceFilters)]
-> Map CategoryName (InstanceParams -> InstanceFilters)
forall a b. (a -> b) -> a -> b
$ [
(CategoryName
instance0,\(Positional []) -> [[TypeFilter]] -> InstanceFilters
forall a. [a] -> Positional a
Positional []),
(CategoryName
instance1,\(Positional [GeneralInstance
_]) ->
[[TypeFilter]] -> InstanceFilters
forall a. [a] -> Positional a
Positional [
[String -> TypeFilter
forall a. ParseFromSource a => String -> a
forceParse String
"requires Type0"]
])
]
checkParseSuccess :: String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess :: String -> GeneralInstance -> IO (CompileInfo ())
checkParseSuccess String
x GeneralInstance
y = CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ do
GeneralInstance
t <- String -> String -> CompileInfo GeneralInstance
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
x CompileInfo GeneralInstance
-> String -> CompileInfo GeneralInstance
forall (m :: * -> *) a. CompileErrorM m => m a -> String -> m a
<!! (String
"When parsing " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
x)
Bool -> CompileInfo () -> CompileInfo ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (GeneralInstance
t GeneralInstance -> GeneralInstance -> Bool
forall a. Eq a => a -> a -> Bool
/= GeneralInstance
y) (CompileInfo () -> CompileInfo ())
-> CompileInfo () -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ String -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> CompileInfo ()) -> String -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ String
"Expected " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" to parse as " String -> String -> String
forall a. [a] -> [a] -> [a]
++ GeneralInstance -> String
forall a. Show a => a -> String
show GeneralInstance
y
checkParseFail :: String -> IO (CompileInfo ())
checkParseFail :: String -> IO (CompileInfo ())
checkParseFail String
x = CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ do
let t :: CompileInfo GeneralInstance
t = String -> String -> CompileInfo GeneralInstance
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
x :: CompileInfo GeneralInstance
Bool -> CompileInfo () -> CompileInfo ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ CompileInfo GeneralInstance -> Bool
forall a. CompileInfo a -> Bool
isCompileError CompileInfo GeneralInstance
t) (CompileInfo () -> CompileInfo ())
-> CompileInfo () -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$
String -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> CompileInfo ()) -> String -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ String
"Expected failure to parse " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
x String -> String -> String
forall a. [a] -> [a] -> [a]
++
String
" but got " String -> String -> String
forall a. [a] -> [a] -> [a]
++ GeneralInstance -> String
forall a. Show a => a -> String
show (CompileInfo GeneralInstance -> GeneralInstance
forall a. CompileInfo a -> a
getCompileSuccess CompileInfo GeneralInstance
t)
checkSimpleConvertSuccess :: String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess :: String -> String -> IO (CompileInfo ())
checkSimpleConvertSuccess = [(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess []
checkSimpleConvertFail :: String -> String -> IO (CompileInfo ())
checkSimpleConvertFail :: String -> String -> IO (CompileInfo ())
checkSimpleConvertFail = [(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail []
checkConvertSuccess :: [(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess :: [(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertSuccess [(String, [String])]
pa String
x String
y = CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return CompileInfo ()
checked where
prefix :: String
prefix = String
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" -> " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
y String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, [String])] -> String
showParams [(String, [String])]
pa
checked :: CompileInfo ()
checked = do
([ValueType
t1,ValueType
t2],ParamFilters
pa2) <- [(String, [String])]
-> [String] -> CompileInfo ([ValueType], ParamFilters)
forall a.
ParseFromSource a =>
[(String, [String])] -> [String] -> CompileInfo ([a], ParamFilters)
parseTheTest [(String, [String])]
pa [String
x,String
y]
CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => CompileInfo a -> m ()
check (CompileInfo () -> CompileInfo ())
-> CompileInfo () -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ Resolver
-> ParamFilters -> ValueType -> ValueType -> CompileInfo ()
forall (m :: * -> *) r.
(CompileErrorM m, TypeResolver r) =>
r -> ParamFilters -> ValueType -> ValueType -> m ()
checkValueAssignment Resolver
Resolver ParamFilters
pa2 ValueType
t1 ValueType
t2
check :: CompileInfo a -> m ()
check CompileInfo a
c
| CompileInfo a -> Bool
forall a. CompileInfo a -> Bool
isCompileError CompileInfo a
c = String -> m ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CompileMessage -> String
forall a. Show a => a -> String
show (CompileInfo a -> CompileMessage
forall a. CompileInfo a -> CompileMessage
getCompileError CompileInfo a
c)
| Bool
otherwise = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
checkInferenceSuccess :: [(String, [String])] -> [String] -> String ->
String -> MergeTree (String,String,Variance) -> IO (CompileInfo ())
checkInferenceSuccess :: [(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceSuccess [(String, [String])]
pa [String]
is String
x String
y MergeTree (String, String, Variance)
gs = (MergeTree InferredTypeGuess
-> CompileInfo (MergeTree InferredTypeGuess) -> CompileInfo ())
-> [(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceCommon MergeTree InferredTypeGuess
-> CompileInfo (MergeTree InferredTypeGuess) -> CompileInfo ()
forall a. (Eq a, Show a) => a -> CompileInfo a -> CompileInfo ()
check [(String, [String])]
pa [String]
is String
x String
y MergeTree (String, String, Variance)
gs where
prefix :: String
prefix = String
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" -> " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
y String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, [String])] -> String
showParams [(String, [String])]
pa
check :: a -> CompileInfo a -> CompileInfo ()
check a
gs2 CompileInfo a
c
| CompileInfo a -> Bool
forall a. CompileInfo a -> Bool
isCompileError CompileInfo a
c = String -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> CompileInfo ()) -> String -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CompileMessage -> String
forall a. Show a => a -> String
show (CompileInfo a -> CompileMessage
forall a. CompileInfo a -> CompileMessage
getCompileError CompileInfo a
c)
| Bool
otherwise = CompileInfo a -> a
forall a. CompileInfo a -> a
getCompileSuccess CompileInfo a
c a -> a -> CompileInfo ()
forall a. (Eq a, Show a) => a -> a -> CompileInfo ()
`checkEquals` a
gs2
checkInferenceFail :: [(String, [String])] -> [String] -> String ->
String -> IO (CompileInfo ())
checkInferenceFail :: [(String, [String])]
-> [String] -> String -> String -> IO (CompileInfo ())
checkInferenceFail [(String, [String])]
pa [String]
is String
x String
y = (MergeTree InferredTypeGuess
-> CompileInfo (MergeTree InferredTypeGuess) -> CompileInfo ())
-> [(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceCommon MergeTree InferredTypeGuess
-> CompileInfo (MergeTree InferredTypeGuess) -> CompileInfo ()
forall (m :: * -> *) p a.
CompileErrorM m =>
p -> CompileInfo a -> m ()
check [(String, [String])]
pa [String]
is String
x String
y ([MergeTree (String, String, Variance)]
-> MergeTree (String, String, Variance)
forall a (f :: * -> *). (Mergeable a, Foldable f) => f a -> a
mergeAll []) where
prefix :: String
prefix = String
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" -> " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
y String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, [String])] -> String
showParams [(String, [String])]
pa
check :: p -> CompileInfo a -> m ()
check p
_ CompileInfo a
c
| CompileInfo a -> Bool
forall a. CompileInfo a -> Bool
isCompileError CompileInfo a
c = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = String -> m ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": Expected failure\n"
checkInferenceCommon ::
(MergeTree InferredTypeGuess -> CompileInfo (MergeTree InferredTypeGuess) -> CompileInfo ()) ->
[(String, [String])] -> [String] -> String -> String ->
MergeTree (String,String,Variance) -> IO (CompileInfo ())
checkInferenceCommon :: (MergeTree InferredTypeGuess
-> CompileInfo (MergeTree InferredTypeGuess) -> CompileInfo ())
-> [(String, [String])]
-> [String]
-> String
-> String
-> MergeTree (String, String, Variance)
-> IO (CompileInfo ())
checkInferenceCommon MergeTree InferredTypeGuess
-> CompileInfo (MergeTree InferredTypeGuess) -> CompileInfo ()
check [(String, [String])]
pa [String]
is String
x String
y MergeTree (String, String, Variance)
gs = CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ CompileInfo ()
checked CompileInfo () -> String -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => m a -> String -> m a
<!! String
context where
context :: String
context = String
"With params = " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, [String])] -> String
forall a. Show a => a -> String
show [(String, [String])]
pa String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
", pair = (" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"," String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
y String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
")"
checked :: CompileInfo ()
checked = do
([GeneralInstance
t1,GeneralInstance
t2],ParamFilters
pa2) <- [(String, [String])]
-> [String] -> CompileInfo ([GeneralInstance], ParamFilters)
forall a.
ParseFromSource a =>
[(String, [String])] -> [String] -> CompileInfo ([a], ParamFilters)
parseTheTest [(String, [String])]
pa [String
x,String
y]
[(ParamName, GeneralInstance)]
ia2 <- (String -> CompileInfoT Identity (ParamName, GeneralInstance))
-> [String] -> CompileInfoT Identity [(ParamName, GeneralInstance)]
forall (m :: * -> *) a b.
CompileErrorM m =>
(a -> m b) -> [a] -> m [b]
mapErrorsM String -> CompileInfoT Identity (ParamName, GeneralInstance)
readInferred [String]
is
MergeTree InferredTypeGuess
gs' <- MergeTree (CompileInfoT Identity InferredTypeGuess)
-> CompileInfo (MergeTree InferredTypeGuess)
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence (MergeTree (CompileInfoT Identity InferredTypeGuess)
-> CompileInfo (MergeTree InferredTypeGuess))
-> MergeTree (CompileInfoT Identity InferredTypeGuess)
-> CompileInfo (MergeTree InferredTypeGuess)
forall a b. (a -> b) -> a -> b
$ ((String, String, Variance)
-> CompileInfoT Identity InferredTypeGuess)
-> MergeTree (String, String, Variance)
-> MergeTree (CompileInfoT Identity InferredTypeGuess)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (String, String, Variance)
-> CompileInfoT Identity InferredTypeGuess
parseGuess MergeTree (String, String, Variance)
gs
let iaMap :: Map ParamName GeneralInstance
iaMap = [(ParamName, GeneralInstance)] -> Map ParamName GeneralInstance
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(ParamName, GeneralInstance)]
ia2
ParamFilters
pa3 <- ([(ParamName, [TypeFilter])] -> ParamFilters)
-> CompileInfoT Identity [(ParamName, [TypeFilter])]
-> CompileInfoT Identity ParamFilters
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [(ParamName, [TypeFilter])] -> ParamFilters
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList (CompileInfoT Identity [(ParamName, [TypeFilter])]
-> CompileInfoT Identity ParamFilters)
-> CompileInfoT Identity [(ParamName, [TypeFilter])]
-> CompileInfoT Identity ParamFilters
forall a b. (a -> b) -> a -> b
$ ((ParamName, [TypeFilter])
-> CompileInfoT Identity (ParamName, [TypeFilter]))
-> [(ParamName, [TypeFilter])]
-> CompileInfoT Identity [(ParamName, [TypeFilter])]
forall (m :: * -> *) a b.
CompileErrorM m =>
(a -> m b) -> [a] -> m [b]
mapErrorsM (Map ParamName GeneralInstance
-> (ParamName, [TypeFilter])
-> CompileInfoT Identity (ParamName, [TypeFilter])
forall (m :: * -> *) a.
CompileErrorM m =>
Map ParamName GeneralInstance
-> (a, [TypeFilter]) -> m (a, [TypeFilter])
filterSub Map ParamName GeneralInstance
iaMap) ([(ParamName, [TypeFilter])]
-> CompileInfoT Identity [(ParamName, [TypeFilter])])
-> [(ParamName, [TypeFilter])]
-> CompileInfoT Identity [(ParamName, [TypeFilter])]
forall a b. (a -> b) -> a -> b
$ ParamFilters -> [(ParamName, [TypeFilter])]
forall k a. Map k a -> [(k, a)]
Map.toList ParamFilters
pa2
GeneralInstance
t2' <- (ParamName -> CompileInfo GeneralInstance)
-> GeneralInstance -> CompileInfo GeneralInstance
forall (m :: * -> *).
CompileErrorM m =>
(ParamName -> m GeneralInstance)
-> GeneralInstance -> m GeneralInstance
uncheckedSubInstance (Map ParamName GeneralInstance
-> ParamName -> CompileInfo GeneralInstance
forall (m :: * -> *).
Monad m =>
Map ParamName GeneralInstance -> ParamName -> m GeneralInstance
weakLookup Map ParamName GeneralInstance
iaMap) GeneralInstance
t2
MergeTree InferredTypeGuess
-> CompileInfo (MergeTree InferredTypeGuess) -> CompileInfo ()
check MergeTree InferredTypeGuess
gs' (CompileInfo (MergeTree InferredTypeGuess) -> CompileInfo ())
-> CompileInfo (MergeTree InferredTypeGuess) -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ Resolver
-> ParamFilters
-> Variance
-> GeneralInstance
-> GeneralInstance
-> CompileInfo (MergeTree InferredTypeGuess)
forall (m :: * -> *) r.
(CompileErrorM m, TypeResolver r) =>
r
-> ParamFilters
-> Variance
-> GeneralInstance
-> GeneralInstance
-> m (MergeTree InferredTypeGuess)
checkGeneralMatch Resolver
Resolver ParamFilters
pa3 Variance
Covariant GeneralInstance
t1 GeneralInstance
t2'
readInferred :: String -> CompileInfoT Identity (ParamName, GeneralInstance)
readInferred String
p = do
ParamName
p' <- String -> String -> CompileInfo ParamName
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
p
(ParamName, GeneralInstance)
-> CompileInfoT Identity (ParamName, GeneralInstance)
forall (m :: * -> *) a. Monad m => a -> m a
return (ParamName
p',TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ ParamName -> TypeInstanceOrParam
JustInferredType ParamName
p')
parseGuess :: (String, String, Variance)
-> CompileInfoT Identity InferredTypeGuess
parseGuess (String
p,String
t,Variance
v) = do
ParamName
p' <- String -> String -> CompileInfo ParamName
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
p
GeneralInstance
t' <- String -> String -> CompileInfo GeneralInstance
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
t
InferredTypeGuess -> CompileInfoT Identity InferredTypeGuess
forall (m :: * -> *) a. Monad m => a -> m a
return (InferredTypeGuess -> CompileInfoT Identity InferredTypeGuess)
-> InferredTypeGuess -> CompileInfoT Identity InferredTypeGuess
forall a b. (a -> b) -> a -> b
$ ParamName -> GeneralInstance -> Variance -> InferredTypeGuess
InferredTypeGuess ParamName
p' GeneralInstance
t' Variance
v
weakLookup :: Map ParamName GeneralInstance -> ParamName -> m GeneralInstance
weakLookup Map ParamName GeneralInstance
tm ParamName
n =
case ParamName
n ParamName -> Map ParamName GeneralInstance -> Maybe GeneralInstance
forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` Map ParamName GeneralInstance
tm of
Just GeneralInstance
t -> GeneralInstance -> m GeneralInstance
forall (m :: * -> *) a. Monad m => a -> m a
return GeneralInstance
t
Maybe GeneralInstance
Nothing -> GeneralInstance -> m GeneralInstance
forall (m :: * -> *) a. Monad m => a -> m a
return (GeneralInstance -> m GeneralInstance)
-> GeneralInstance -> m GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ Bool -> ParamName -> TypeInstanceOrParam
JustParamName Bool
True ParamName
n
filterSub :: Map ParamName GeneralInstance
-> (a, [TypeFilter]) -> m (a, [TypeFilter])
filterSub Map ParamName GeneralInstance
im (a
k,[TypeFilter]
fs) = do
[TypeFilter]
fs' <- (TypeFilter -> m TypeFilter) -> [TypeFilter] -> m [TypeFilter]
forall (m :: * -> *) a b.
CompileErrorM m =>
(a -> m b) -> [a] -> m [b]
mapErrorsM ((ParamName -> m GeneralInstance) -> TypeFilter -> m TypeFilter
forall (m :: * -> *).
CompileErrorM m =>
(ParamName -> m GeneralInstance) -> TypeFilter -> m TypeFilter
uncheckedSubFilter (Map ParamName GeneralInstance -> ParamName -> m GeneralInstance
forall (m :: * -> *).
Monad m =>
Map ParamName GeneralInstance -> ParamName -> m GeneralInstance
weakLookup Map ParamName GeneralInstance
im)) [TypeFilter]
fs
(a, [TypeFilter]) -> m (a, [TypeFilter])
forall (m :: * -> *) a. Monad m => a -> m a
return (a
k,[TypeFilter]
fs')
checkConvertFail :: [(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail :: [(String, [String])] -> String -> String -> IO (CompileInfo ())
checkConvertFail [(String, [String])]
pa String
x String
y = CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return CompileInfo ()
checked where
prefix :: String
prefix = String
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" /> " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
y String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, [String])] -> String
showParams [(String, [String])]
pa
checked :: CompileInfo ()
checked = do
([ValueType
t1,ValueType
t2],ParamFilters
pa2) <- [(String, [String])]
-> [String] -> CompileInfo ([ValueType], ParamFilters)
forall a.
ParseFromSource a =>
[(String, [String])] -> [String] -> CompileInfo ([a], ParamFilters)
parseTheTest [(String, [String])]
pa [String
x,String
y]
CompileInfo () -> CompileInfo ()
forall a. CompileInfo a -> CompileInfo ()
check (CompileInfo () -> CompileInfo ())
-> CompileInfo () -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ Resolver
-> ParamFilters -> ValueType -> ValueType -> CompileInfo ()
forall (m :: * -> *) r.
(CompileErrorM m, TypeResolver r) =>
r -> ParamFilters -> ValueType -> ValueType -> m ()
checkValueAssignment Resolver
Resolver ParamFilters
pa2 ValueType
t1 ValueType
t2
check :: CompileInfo a -> CompileInfo ()
check :: CompileInfo a -> CompileInfo ()
check CompileInfo a
c
| CompileInfo a -> Bool
forall a. CompileInfo a -> Bool
isCompileError CompileInfo a
c = () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = String -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> CompileInfo ()) -> String -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": Expected failure\n"
data Resolver = Resolver
instance TypeResolver Resolver where
trRefines :: Resolver -> TypeInstance -> CategoryName -> m InstanceParams
trRefines Resolver
_ = Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
-> TypeInstance -> CategoryName -> m InstanceParams
forall (m :: * -> *).
CompileErrorM m =>
Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
-> TypeInstance -> CategoryName -> m InstanceParams
getParams Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
refines
trDefines :: Resolver -> TypeInstance -> CategoryName -> m InstanceParams
trDefines Resolver
_ = Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
-> TypeInstance -> CategoryName -> m InstanceParams
forall (m :: * -> *).
CompileErrorM m =>
Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
-> TypeInstance -> CategoryName -> m InstanceParams
getParams Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
defines
trVariance :: Resolver -> CategoryName -> m InstanceVariances
trVariance Resolver
_ = Map CategoryName InstanceVariances
-> CategoryName -> m InstanceVariances
forall n (m :: * -> *) a.
(Ord n, Show n, CompileErrorM m) =>
Map n a -> n -> m a
mapLookup Map CategoryName InstanceVariances
variances
trTypeFilters :: Resolver -> TypeInstance -> m InstanceFilters
trTypeFilters Resolver
_ = TypeInstance -> m InstanceFilters
forall (m :: * -> *).
CompileErrorM m =>
TypeInstance -> m InstanceFilters
getTypeFilters
trDefinesFilters :: Resolver -> DefinesInstance -> m InstanceFilters
trDefinesFilters Resolver
_ = DefinesInstance -> m InstanceFilters
forall (m :: * -> *).
CompileErrorM m =>
DefinesInstance -> m InstanceFilters
getDefinesFilters
trConcrete :: Resolver -> CategoryName -> m Bool
trConcrete Resolver
_ = \CategoryName
t -> Bool -> m Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (CategoryName
t CategoryName -> CategoryName -> Bool
forall a. Eq a => a -> a -> Bool
== CategoryName
type5)
getParams :: CompileErrorM m =>
Map.Map CategoryName (Map.Map CategoryName (InstanceParams -> InstanceParams))
-> TypeInstance -> CategoryName -> m InstanceParams
getParams :: Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
-> TypeInstance -> CategoryName -> m InstanceParams
getParams Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
ma (TypeInstance CategoryName
n1 InstanceParams
ps1) CategoryName
n2 = do
Map CategoryName (InstanceParams -> InstanceParams)
ra <- Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
-> CategoryName
-> m (Map CategoryName (InstanceParams -> InstanceParams))
forall n (m :: * -> *) a.
(Ord n, Show n, CompileErrorM m) =>
Map n a -> n -> m a
mapLookup Map
CategoryName (Map CategoryName (InstanceParams -> InstanceParams))
ma CategoryName
n1 m (Map CategoryName (InstanceParams -> InstanceParams))
-> String
-> m (Map CategoryName (InstanceParams -> InstanceParams))
forall (m :: * -> *) a. CompileErrorM m => m a -> String -> m a
<?? (String
"In lookup of category " String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n1)
InstanceParams -> InstanceParams
f <- Map CategoryName (InstanceParams -> InstanceParams)
-> CategoryName -> m (InstanceParams -> InstanceParams)
forall n (m :: * -> *) a.
(Ord n, Show n, CompileErrorM m) =>
Map n a -> n -> m a
mapLookup Map CategoryName (InstanceParams -> InstanceParams)
ra CategoryName
n2 m (InstanceParams -> InstanceParams)
-> String -> m (InstanceParams -> InstanceParams)
forall (m :: * -> *) a. CompileErrorM m => m a -> String -> m a
<?? (String
"In lookup of parent " String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n2 String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" of " String -> String -> String
forall a. [a] -> [a] -> [a]
++ CategoryName -> String
forall a. Show a => a -> String
show CategoryName
n1)
InstanceParams -> m InstanceParams
forall (m :: * -> *) a. Monad m => a -> m a
return (InstanceParams -> m InstanceParams)
-> InstanceParams -> m InstanceParams
forall a b. (a -> b) -> a -> b
$ InstanceParams -> InstanceParams
f InstanceParams
ps1
getTypeFilters :: CompileErrorM m => TypeInstance -> m InstanceFilters
getTypeFilters :: TypeInstance -> m InstanceFilters
getTypeFilters (TypeInstance CategoryName
n InstanceParams
ps) = String
"In type filters lookup" String -> m InstanceFilters -> m InstanceFilters
forall (m :: * -> *) a. CompileErrorM m => String -> m a -> m a
??> do
InstanceParams -> InstanceFilters
f <- Map CategoryName (InstanceParams -> InstanceFilters)
-> CategoryName -> m (InstanceParams -> InstanceFilters)
forall n (m :: * -> *) a.
(Ord n, Show n, CompileErrorM m) =>
Map n a -> n -> m a
mapLookup Map CategoryName (InstanceParams -> InstanceFilters)
typeFilters CategoryName
n
InstanceFilters -> m InstanceFilters
forall (m :: * -> *) a. Monad m => a -> m a
return (InstanceFilters -> m InstanceFilters)
-> InstanceFilters -> m InstanceFilters
forall a b. (a -> b) -> a -> b
$ InstanceParams -> InstanceFilters
f InstanceParams
ps
getDefinesFilters :: CompileErrorM m => DefinesInstance -> m InstanceFilters
getDefinesFilters :: DefinesInstance -> m InstanceFilters
getDefinesFilters (DefinesInstance CategoryName
n InstanceParams
ps) = String
"In defines filters lookup" String -> m InstanceFilters -> m InstanceFilters
forall (m :: * -> *) a. CompileErrorM m => String -> m a -> m a
??> do
InstanceParams -> InstanceFilters
f <- Map CategoryName (InstanceParams -> InstanceFilters)
-> CategoryName -> m (InstanceParams -> InstanceFilters)
forall n (m :: * -> *) a.
(Ord n, Show n, CompileErrorM m) =>
Map n a -> n -> m a
mapLookup Map CategoryName (InstanceParams -> InstanceFilters)
definesFilters CategoryName
n
InstanceFilters -> m InstanceFilters
forall (m :: * -> *) a. Monad m => a -> m a
return (InstanceFilters -> m InstanceFilters)
-> InstanceFilters -> m InstanceFilters
forall a b. (a -> b) -> a -> b
$ InstanceParams -> InstanceFilters
f InstanceParams
ps
mapLookup :: (Ord n, Show n, CompileErrorM m) => Map.Map n a -> n -> m a
mapLookup :: Map n a -> n -> m a
mapLookup Map n a
ma n
n = Maybe a -> m a
forall (m :: * -> *) a. CompileErrorM m => Maybe a -> m a
resolve (Maybe a -> m a) -> Maybe a -> m a
forall a b. (a -> b) -> a -> b
$ n
n n -> Map n a -> Maybe a
forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` Map n a
ma where
resolve :: Maybe a -> m a
resolve (Just a
x) = a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
resolve Maybe a
_ = String -> m a
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> m a) -> String -> m a
forall a b. (a -> b) -> a -> b
$ String
"Map key " String -> String -> String
forall a. [a] -> [a] -> [a]
++ n -> String
forall a. Show a => a -> String
show n
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" not found"