module Test.TypeCategory (tests) where
import Control.Arrow
import Control.Monad ((>=>),when)
import System.FilePath
import Text.Regex.TDFA
import qualified Data.Map as Map
import qualified Data.Set as Set
import Base.CompilerError
import Base.GeneralType
import Base.Positional
import Base.TrackedErrors
import Parser.TextParser (SourceContext)
import Parser.TypeCategory ()
import Test.Common
import Types.TypeCategory
import Types.TypeInstance
import Types.Variance
tests :: [IO (TrackedErrors ())]
tests :: [IO (TrackedErrors ())]
tests = [
String -> IO (TrackedErrors ())
checkSingleParseSuccess (String
"testfiles" String -> String -> String
</> String
"value_interface.0rx"),
String -> IO (TrackedErrors ())
checkSingleParseSuccess (String
"testfiles" String -> String -> String
</> String
"type_interface.0rx"),
String -> IO (TrackedErrors ())
checkSingleParseSuccess (String
"testfiles" String -> String -> String
</> String
"concrete.0rx"),
String -> IO (TrackedErrors ())
checkShortParseSuccess String
"concrete Type<#x> {}",
String -> IO (TrackedErrors ())
checkShortParseSuccess String
"concrete Type {}",
String -> IO (TrackedErrors ())
checkShortParseFail String
"concrete Type<T> {}",
String -> IO (TrackedErrors ())
checkShortParseFail String
"concrete Type<optional> {}",
String -> IO (TrackedErrors ())
checkShortParseFail String
"concrete Type<optional T> {}",
String -> IO (TrackedErrors ())
checkShortParseFail String
"concrete Type<T<#x>> {}",
String -> IO (TrackedErrors ())
checkShortParseSuccess String
"concrete Type { refines T }",
String -> IO (TrackedErrors ())
checkShortParseFail String
"concrete Type { refines #x }",
String -> IO (TrackedErrors ())
checkShortParseSuccess String
"concrete Type { defines T }",
String -> IO (TrackedErrors ())
checkShortParseFail String
"concrete Type { defines #x }",
String -> IO (TrackedErrors ())
checkShortParseFail String
"concrete Type { refines optional }",
String -> IO (TrackedErrors ())
checkShortParseFail String
"concrete Type { refines optional T }",
String -> IO (TrackedErrors ())
checkShortParseSuccess String
"concrete Type<#x|#y> { #x requires #y }",
String -> IO (TrackedErrors ())
checkShortParseSuccess String
"concrete Type<#x|#y> { #x allows #y }",
String -> IO (TrackedErrors ())
checkShortParseSuccess String
"concrete Type<#x|#y> { #x defines T }",
String -> IO (TrackedErrors ())
checkShortParseFail String
"concrete Type<#x|#y> { #x defines #y }",
String -> IO (TrackedErrors ())
checkShortParseSuccess String
"@type interface Type<#x> {}",
String -> IO (TrackedErrors ())
checkShortParseSuccess String
"@type interface Type {}",
String -> IO (TrackedErrors ())
checkShortParseFail String
"@type interface Type { refines T }",
String -> IO (TrackedErrors ())
checkShortParseFail String
"@type interface Type { defines T }",
String -> IO (TrackedErrors ())
checkShortParseFail String
"@type interface Type<#x> { #x allows T }",
String -> IO (TrackedErrors ())
checkShortParseSuccess String
"@value interface Type<#x> {}",
String -> IO (TrackedErrors ())
checkShortParseSuccess String
"@value interface Type {}",
String -> IO (TrackedErrors ())
checkShortParseSuccess String
"@value interface Type { refines T }",
String -> IO (TrackedErrors ())
checkShortParseFail String
"@value interface Type { defines T }",
String -> IO (TrackedErrors ())
checkShortParseFail String
"@value interface Type<#x> { #x allows T }",
String -> IO (TrackedErrors ())
checkShortParseSuccess String
"@value interface Type { call () -> (#self) }",
String -> IO (TrackedErrors ())
checkShortParseFail String
"@value interface Type<#self> {}",
String -> IO (TrackedErrors ())
checkShortParseFail String
"@value interface Type { refines #self }",
String -> IO (TrackedErrors ())
checkShortParseFail String
"@value interface Type { #self allows Foo }",
String -> IO (TrackedErrors ())
checkShortParseFail String
"@value interface Type { #self requires Foo }",
String -> IO (TrackedErrors ())
checkShortParseFail String
"@value interface Type { #self defines Foo }",
String -> IO (TrackedErrors ())
checkShortParseSuccess String
"concrete Type<#x> { #x allows #self }",
String -> IO (TrackedErrors ())
checkShortParseSuccess String
"concrete Type<#x> { #x requires #self }",
String -> IO (TrackedErrors ())
checkShortParseFail String
"concrete Type<#x> { #x defines #self }",
String -> IO (TrackedErrors ())
checkShortParseFail String
"@value interface Type { call<#self> () -> () }",
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"value_refines_value.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"value_refines_instance.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"value_refines_concrete.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"concrete_refines_instance.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"concrete_refines_concrete.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"concrete_defines_instance.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"concrete_defines_value.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"concrete_defines_concrete.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall a b. (a -> b) -> a -> b
$ forall c. [(CategoryName, AnyCategory c)] -> CategoryMap c
toCategoryMap [
(String -> CategoryName
CategoryName String
"Parent2",forall c.
[c]
-> Namespace
-> CategoryName
-> [PragmaCategory c]
-> [ValueParam c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent2") [] [] [])
]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall a b. (a -> b) -> a -> b
$ forall c. [(CategoryName, AnyCategory c)] -> CategoryMap c
toCategoryMap [
(String -> CategoryName
CategoryName String
"Parent",forall c.
[c]
-> Namespace
-> CategoryName
-> [PragmaCategory c]
-> [ValueParam c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [])
]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"partial.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall a b. (a -> b) -> a -> b
$ forall c. [(CategoryName, AnyCategory c)] -> CategoryMap c
toCategoryMap [
(String -> CategoryName
CategoryName String
"Parent",forall c.
[c]
-> Namespace
-> CategoryName
-> [PragmaCategory c]
-> [ValueParam c]
-> [ValueRefine c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [] [])
]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"partial.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall a b. (a -> b) -> a -> b
$ forall c. [(CategoryName, AnyCategory c)] -> CategoryMap c
toCategoryMap [
(String -> CategoryName
CategoryName String
"Parent",forall c.
[c]
-> Namespace
-> CategoryName
-> [PragmaCategory c]
-> [ValueParam c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [])
]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"partial.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall a b. (a -> b) -> a -> b
$ forall c. [(CategoryName, AnyCategory c)] -> CategoryMap c
toCategoryMap [
(String -> CategoryName
CategoryName String
"Parent",forall c.
[c]
-> Namespace
-> CategoryName
-> [PragmaCategory c]
-> [FunctionVisibility c]
-> [ValueParam c]
-> [ValueRefine c]
-> [ValueDefine c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
ValueConcrete [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [] [] [] [] [])
]),
forall a.
String
-> String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFailWith String
"Parent.+not found"
(String
"testfiles" String -> String -> String
</> String
"partial.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFailWith String
"Parent.+not visible"
(String
"testfiles" String -> String -> String
</> String
"partial.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes forall a b. (a -> b) -> a -> b
$ forall c.
Map CategoryName [c]
-> Map CategoryName (AnyCategory c) -> CategoryMap c
CategoryMap (forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(String -> CategoryName
CategoryName String
"Parent",[])]) forall k a. Map k a
Map.empty),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"value_refines_value.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectionCycles forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectionCycles forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"concrete_defines_instance.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectionCycles forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"value_cycle.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectionCycles forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall a b. (a -> b) -> [a] -> [b]
map (forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. AnyCategory c -> CategoryName
getCategoryName) [AnyCategory SourceContext]
ts2 forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [
String
"Object2",String
"Object3",String
"Object1",String
"Type",String
"Parent",String
"Child"
]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2
forall c. [AnyCategory c] -> [(String, String)]
scrapeAllRefines [AnyCategory SourceContext]
ts3 forall a. (Ord a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsExactly` [
(String
"Object1",String
"Object3<#y>"),
(String
"Object1",String
"Object2"),
(String
"Object3",String
"Object2"),
(String
"Parent",String
"Object1<#x,Object3<Object2>>"),
(String
"Parent",String
"Object3<Object3<Object2>>"),
(String
"Parent",String
"Object2"),
(String
"Child",String
"Parent<Child>"),
(String
"Child",String
"Object1<Child,Object3<Object2>>"),
(String
"Child",String
"Object3<Object3<Object2>>"),
(String
"Child",String
"Object2")
]
forall c. [AnyCategory c] -> [(String, String)]
scrapeAllDefines [AnyCategory SourceContext]
ts3 forall a. (Ord a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsExactly` [
(String
"Child",String
"Type<Child>")
]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
existing <- forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall c. [(CategoryName, AnyCategory c)] -> CategoryMap c
toCategoryMap [
(String -> CategoryName
CategoryName String
"Parent2",forall c.
[c]
-> Namespace
-> CategoryName
-> [PragmaCategory c]
-> [ValueParam c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent2") [] [] [])
]
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
existing [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
existing [AnyCategory SourceContext]
ts2),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
existing <- forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall c. [(CategoryName, AnyCategory c)] -> CategoryMap c
toCategoryMap [
(String -> CategoryName
CategoryName String
"Parent",forall c.
[c]
-> Namespace
-> CategoryName
-> [PragmaCategory c]
-> [ValueParam c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [])
]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
existing [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"partial.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
existing <- forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall c. [(CategoryName, AnyCategory c)] -> CategoryMap c
toCategoryMap [
(String -> CategoryName
CategoryName String
"Parent",
forall c.
[c]
-> Namespace
-> CategoryName
-> [PragmaCategory c]
-> [ValueParam c]
-> [ValueRefine c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] []
[forall c. [c] -> TypeInstance -> ValueRefine c
ValueRefine [] forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Object1") (forall a. [a] -> Positional a
Positional []),
forall c. [c] -> TypeInstance -> ValueRefine c
ValueRefine [] forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Object2") (forall a. [a] -> Positional a
Positional [])] []),
(String -> CategoryName
CategoryName String
"Object2",
forall c.
[c]
-> Namespace
-> CategoryName
-> [PragmaCategory c]
-> [ValueParam c]
-> [ValueRefine c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Object2") [] [] [] [])
]
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
existing [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
existing [AnyCategory SourceContext]
ts2
forall c. [AnyCategory c] -> [(String, String)]
scrapeAllRefines [AnyCategory SourceContext]
ts3 forall a. (Ord a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsExactly` [
(String
"Child",String
"Parent"),
(String
"Child",String
"Object1"),
(String
"Child",String
"Object2")
]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"valid_variances.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"contravariant_refines_covariant.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"contravariant_refines_invariant.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"covariant_refines_contravariant.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"covariant_refines_invariant.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"contravariant_defines_covariant.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"contravariant_defines_invariant.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"covariant_defines_contravariant.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"covariant_defines_invariant.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"concrete_duplicate_param.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"type_duplicate_param.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"value_duplicate_param.0rx") (forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall a b. (a -> b) -> a -> b
$ forall c. [(CategoryName, AnyCategory c)] -> CategoryMap c
toCategoryMap [
(String -> CategoryName
CategoryName String
"Parent2",forall c.
[c]
-> Namespace
-> CategoryName
-> [PragmaCategory c]
-> [ValueParam c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent2") [] [] [])
]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall a b. (a -> b) -> a -> b
$ forall c. [(CategoryName, AnyCategory c)] -> CategoryMap c
toCategoryMap [
(String -> CategoryName
CategoryName String
"Parent",forall c.
[c]
-> Namespace
-> CategoryName
-> [PragmaCategory c]
-> [ValueParam c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [])
]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"partial_params.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall a b. (a -> b) -> a -> b
$ forall c. [(CategoryName, AnyCategory c)] -> CategoryMap c
toCategoryMap [
(String -> CategoryName
CategoryName String
"Parent",
forall c.
[c]
-> Namespace
-> CategoryName
-> [PragmaCategory c]
-> [ValueParam c]
-> [ValueRefine c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") []
[forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#w") Variance
Contravariant,
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#z") Variance
Covariant] [] [])
]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"partial_params.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall a b. (a -> b) -> a -> b
$ forall c. [(CategoryName, AnyCategory c)] -> CategoryMap c
toCategoryMap [
(String -> CategoryName
CategoryName String
"Parent",
forall c.
[c]
-> Namespace
-> CategoryName
-> [PragmaCategory c]
-> [ValueParam c]
-> [ValueRefine c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") []
[forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#w") Variance
Invariant,
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#z") Variance
Covariant] [] [])
]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"partial_params.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall a b. (a -> b) -> a -> b
$ forall c. [(CategoryName, AnyCategory c)] -> CategoryMap c
toCategoryMap [
(String -> CategoryName
CategoryName String
"Parent",
forall c.
[c]
-> Namespace
-> CategoryName
-> [PragmaCategory c]
-> [ValueParam c]
-> [ValueRefine c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") []
[forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#w") Variance
Contravariant,
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#z") Variance
Invariant] [] [])
]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete.0rx")
(\[AnyCategory SourceContext]
ts -> do
[String]
rs <- forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts String
"Type<#a,#b,#c,#d,#e,#f>" String
"Type"
[String]
rs forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [String
"#a",String
"#b",String
"#c",String
"#d",String
"#e",String
"#f"]
),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2
[String]
rs <- forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Object1<#a,#b>" String
"Object1"
[String]
rs forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [String
"#a",String
"#b"]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2
[String]
rs <- forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Object1<#a,#b>" String
"Object3"
[String]
rs forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [String
"#b"]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2
[String]
rs <- forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Undefined<#a,#b>" String
"Undefined"
[String]
rs forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [String
"#a",String
"#b"]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2
[String]
rs <- forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Object1<#a>" String
"Object1"
[String]
rs forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [String
"#a"]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2
[String]
rs <- forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Parent<#t>" String
"Object1"
[String]
rs forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [String
"#t",String
"Object3<Object2>"]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Parent<#t>" String
"Child"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Child" String
"Type"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Child" String
"Missing"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[String]
rs <- forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeDefines [AnyCategory SourceContext]
ts String
"Child" String
"Type"
[String]
rs forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [String
"Child"]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeDefines [AnyCategory SourceContext]
ts String
"Child" String
"Parent"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeDefines [AnyCategory SourceContext]
ts String
"Child" String
"Missing"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete.0rx")
(\[AnyCategory SourceContext]
ts -> do
[Variance]
vs <- forall c.
Show c =>
[AnyCategory c] -> String -> TrackedErrors [Variance]
getTypeVariance [AnyCategory SourceContext]
ts String
"Type"
[Variance]
vs forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [Variance
Contravariant,Variance
Contravariant,
Variance
Invariant,Variance
Invariant,
Variance
Covariant,Variance
Covariant]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
forall c.
Show c =>
[AnyCategory c] -> String -> TrackedErrors [Variance]
getTypeVariance [AnyCategory SourceContext]
ts String
"Missing"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete.0rx")
(\[AnyCategory SourceContext]
ts -> do
[[String]]
rs <- forall c.
Show c =>
[AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeFilters [AnyCategory SourceContext]
ts String
"Type<#a,#b,#c,#d,#e,#f>"
forall a.
Show a =>
(a -> a -> TrackedErrors ()) -> [a] -> [a] -> TrackedErrors ()
checkPaired forall a. (Ord a, Show a) => [a] -> [a] -> TrackedErrors ()
containsExactly [[String]]
rs [
[String
"allows Parent"],
[String
"requires Type2<#a>"],
[String
"defines Equals<#c>"],
[],
[],
[]
]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete.0rx")
(\[AnyCategory SourceContext]
ts -> do
[[String]]
rs <- forall c.
Show c =>
[AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeFilters [AnyCategory SourceContext]
ts String
"Type<Type<#t>,#b,Type3<#x>,#d,#e,#f>"
forall a.
Show a =>
(a -> a -> TrackedErrors ()) -> [a] -> [a] -> TrackedErrors ()
checkPaired forall a. (Ord a, Show a) => [a] -> [a] -> TrackedErrors ()
containsExactly [[String]]
rs [
[String
"allows Parent"],
[String
"requires Type2<Type<#t>>"],
[String
"defines Equals<Type3<#x>>"],
[],
[],
[]
]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"Child"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"[Child|Child]"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"[Child&Child]"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"Object2"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"[Object2|Object2]"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"[Object2&Object2]"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeFail CategoryResolver SourceContext
r [] String
"Type<Child>"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeFail CategoryResolver SourceContext
r [] String
"[Type<Child>|Type<Child>]"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeFail CategoryResolver SourceContext
r [] String
"[Type<Child>&Type<Child>]"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"Value0<Value1,Value2>"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"Value0<Value1,Value1>"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"Value0<Value3,Value2>"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r
[String
"#x",String
"#y"]
String
"Value0<#x,#y>"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r
[String
"#x",String
"#y"]
String
"Value0<#x,#y>"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r
[String
"#x",String
"#y"]
String
"Value0<#x,Value2>"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
forall r.
TypeResolver r =>
r -> [String] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r
[String
"#x",String
"#y"]
String
"Value0<#x,#y>"),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"requires_concrete.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts3),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"merged.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts3
[String]
rs <- forall c.
Map CategoryName (AnyCategory c)
-> String -> TrackedErrors [String]
getRefines (forall c. CategoryMap c -> Map CategoryName (AnyCategory c)
cmAvailable CategoryMap SourceContext
tm) String
"Test"
[String]
rs forall a. (Ord a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsExactly` [String
"Value0",String
"Value1",String
"Value2",String
"Value3",
String
"Value4<Value1,Value1>",String
"Inherit1",String
"Inherit2"]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"merged.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"duplicate_refine.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"duplicate_define.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"refine_wrong_direction.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"inherit_incompatible.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"merge_incompatible.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
let tm0 :: CategoryMap c
tm0 = forall c. [(CategoryName, AnyCategory c)] -> CategoryMap c
toCategoryMap [
(String -> CategoryName
CategoryName String
"Parent2",forall c.
[c]
-> Namespace
-> CategoryName
-> [PragmaCategory c]
-> [ValueParam c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent2") [] [] [])
]
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
tm0 [AnyCategory SourceContext]
ts
[String]
rs <- forall c.
Map CategoryName (AnyCategory c)
-> String -> TrackedErrors [String]
getRefines (forall c. CategoryMap c -> Map CategoryName (AnyCategory c)
cmAvailable CategoryMap SourceContext
tm) String
"Child"
[String]
rs forall a. (Ord a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsExactly` [String
"Parent<Child>",String
"Object2",
String
"Object1<Child,Object3<Object2>>",
String
"Object3<Object3<Object2>>"]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"category_function_param_match.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_param_clash.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_duplicate_param.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_filter_param.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_allows_variance.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_requires_variance.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_defines_variance.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"weak_arg.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"weak_return.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"function_filters_satisfied.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"function_requires_missed.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"function_allows_missed.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"function_defines_missed.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"valid_function_variance.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_value_arg_variance.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_value_return_variance.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_type_arg_variance.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_type_return_variance.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"valid_filter_variance.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"allows_variance_right.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"defines_variance_right.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"requires_variance_right.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"allows_variance_left.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"defines_variance_left.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"requires_variance_left.0rx")
(\[AnyCategory SourceContext]
ts -> forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"conflicting_declaration.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"conflicting_inherited.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"successful_merge.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"merge_with_refine.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"failed_merge.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"ambiguous_merge_inherit.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"merge_different_scopes.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"successful_merge_params.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"failed_merge_params.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"preserve_merged.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"conflict_in_preserved.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"resolved_in_preserved.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts2 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"valid_self.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a b. a -> b -> a
const (forall (m :: * -> *) a. Monad m => a -> m a
return ())),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_merge_self.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a b. a -> b -> a
const (forall (m :: * -> *) a. Monad m => a -> m a
return ())),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"contravariant_self.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a b. a -> b -> a
const (forall (m :: * -> *) a. Monad m => a -> m a
return ())),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"invariant_self.0rx")
(forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a b. a -> b -> a
const (forall (m :: * -> *) a. Monad m => a -> m a
return ())),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Type1",String
"#x")]
[(String
"#x",String
"Type1")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Type2",String
"#x"),(String
"Type1",String
"#x")]
[(String
"#x",String
"Type1")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[]
[]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface1<Type2>",String
"#x"),(String
"Interface1<Type1>",String
"#x")]
[(String
"#x",String
"Interface1<Type1>")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface2<Type2>",String
"#x"),(String
"Interface2<Type1>",String
"#x")]
[(String
"#x",String
"Interface2<Type2>")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface2<Type2>",String
"Interface2<#x>"),
(String
"Interface2<Type1>",String
"Interface2<#x>")]
[(String
"#x",String
"Type2")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface3<Type1>",String
"#x"),(String
"Interface3<Type1>",String
"#x")]
[(String
"#x",String
"Interface3<Type1>")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface3<Type1>",String
"#x"),(String
"Interface3<Type2>",String
"#x")]
[(String
"#x",String
"[Interface3<Type2>|Interface3<Type1>]")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface3<Type1>",String
"Interface3<#x>"),
(String
"Interface3<Type1>",String
"Interface3<#x>")]
[(String
"#x",String
"Type1")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceFail CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface3<Type1>",String
"Interface3<#x>"),
(String
"Interface3<Type2>",String
"Interface3<#x>")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Type1",String
"#x"),
(String
"Interface1<Type2>",String
"Interface1<#x>"),
(String
"Interface2<Type0>",String
"Interface2<#x>")]
[(String
"#x",String
"Type1")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface3<Type2>",String
"Interface3<#x>"),
(String
"Interface1<Type2>",String
"Interface1<#x>"),
(String
"Interface2<Type1>",String
"Interface2<#x>")]
[(String
"#x",String
"Type2")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface1<Type1>",String
"Interface1<[#x|Interface2<#x>]>")]
[(String
"#x",String
"Type1")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface1<Type2>",String
"Interface1<[#x&Type1]>")]
[(String
"#x",String
"Type2")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface2<Type1>",String
"Interface2<[#x&Interface2<#x>]>")]
[(String
"#x",String
"Type1")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface2<Type0>",String
"Interface2<[#x|Type1]>")]
[(String
"#x",String
"Type0")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface3<Type0>",String
"[Interface1<#x>&Interface3<#x>]")]
[(String
"#x",String
"Type0")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Type1",String
"#x"),(String
"Type2",String
"[Type2|Type0]")]
[(String
"#x",String
"Type1")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[]),(String
"#y",[])] [String
"#x",String
"#y"]
[(String
"Interface3<Type0>",String
"[Interface1<#x>&Interface3<#x>]"),
(String
"Interface3<Type0>",String
"[Interface1<#y>|Interface3<#y>]")]
[(String
"#x",String
"Type0"),(String
"#y",String
"Type1")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface1<any>",String
"Interface1<#x>")]
[(String
"#x",String
"any")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface2<all>",String
"Interface2<#x>")]
[(String
"#x",String
"all")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface1<all>",String
"Interface1<#x>")]
[(String
"#x",String
"all")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface2<any>",String
"Interface2<#x>")]
[(String
"#x",String
"any")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"delayed_merging.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceFail CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Type",String
"[Interface1<#x>|Interface2<#x>]")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"delayed_merging.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Base",String
"#x"),
(String
"Type",String
"[Interface1<#x>|Interface2<#x>]")]
[(String
"#x",String
"Base")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type1>|Interface3<Type2>]",String
"Interface0<#x>")]
[(String
"#x",String
"Type1")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type0>|Interface3<Type4>]",String
"Interface0<#x>")]
[(String
"#x",String
"[Type4|Type0]")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type1>&Interface3<Type2>]",String
"Interface0<#x>")]
[(String
"#x",String
"Type2")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceFail CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type0>&Interface3<Type4>]",String
"Interface0<#x>")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type1>|Interface3<Type2>]",String
"Interface1<#x>")]
[(String
"#x",String
"Type2")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type0>|Interface3<Type4>]",String
"Interface1<#x>")]
[(String
"#x",String
"[Type4&Type0]")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type1>&Interface3<Type2>]",String
"Interface1<#x>")]
[(String
"#x",String
"Type1")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceFail CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type0>&Interface3<Type4>]",String
"Interface1<#x>")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[String
"requires Type0"])] [String
"#x"]
[(String
"[Interface2<Type1>&Interface3<Type4>]",String
"Interface0<#x>")]
[(String
"#x",String
"Type1")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[String
"allows Type2"])] [String
"#x"]
[(String
"[Interface2<Type1>&Interface3<Type4>]",String
"Interface0<#x>")]
[(String
"#x",String
"Type1")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[String
"defines Defined<#x>"])] [String
"#x"]
[(String
"[Interface2<Type1>&Interface3<Type4>]",String
"Interface0<#x>")]
[(String
"#x",String
"Type4")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[String
"requires Type0"])] [String
"#x"]
[(String
"[Type1|Type2]",String
"#x")]
[(String
"#x",String
"[Type1|Type2]")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[String
"requires #x"])] [String
"#x"]
[(String
"[Type1|Type2]",String
"#x")]
[(String
"#x",String
"[Type1|Type2]")]),
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourceContext]
ts -> do
CategoryMap SourceContext
tm <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceFail CategoryMap SourceContext
tm
[(String
"#x",[String
"requires Type0"])] [String
"#x"]
[(String
"[Type1|Type4]",String
"#x")])
]
getRefines :: Map.Map CategoryName (AnyCategory c) -> String -> TrackedErrors [String]
getRefines :: forall c.
Map CategoryName (AnyCategory c)
-> String -> TrackedErrors [String]
getRefines Map CategoryName (AnyCategory c)
tm String
n =
case (String -> CategoryName
CategoryName String
n) forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` Map CategoryName (AnyCategory c)
tm of
(Just AnyCategory c
t) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. ValueRefine c -> TypeInstance
vrType) (forall c. AnyCategory c -> [ValueRefine c]
getCategoryRefines AnyCategory c
t)
Maybe (AnyCategory c)
_ -> forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ String
"Type " forall a. [a] -> [a] -> [a]
++ String
n forall a. [a] -> [a] -> [a]
++ String
" not found"
getDefines :: Map.Map CategoryName (AnyCategory c) -> String -> TrackedErrors [String]
getDefines :: forall c.
Map CategoryName (AnyCategory c)
-> String -> TrackedErrors [String]
getDefines Map CategoryName (AnyCategory c)
tm String
n =
case (String -> CategoryName
CategoryName String
n) forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` Map CategoryName (AnyCategory c)
tm of
(Just AnyCategory c
t) -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. ValueDefine c -> DefinesInstance
vdType) (forall c. AnyCategory c -> [ValueDefine c]
getCategoryDefines AnyCategory c
t)
Maybe (AnyCategory c)
_ -> forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ String
"Type " forall a. [a] -> [a] -> [a]
++ String
n forall a. [a] -> [a] -> [a]
++ String
" not found"
getTypeRefines :: Show c => [AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines :: forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory c]
ts String
s String
n = do
CategoryMap c
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory c]
ts
let r :: CategoryResolver c
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap c
ta
TypeInstance
t <- forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
s
Positional [GeneralInstance]
rs <- forall r (m :: * -> *).
(TypeResolver r, CollectErrorsM m) =>
r -> TypeInstance -> CategoryName -> m InstanceParams
trRefines CategoryResolver c
r TypeInstance
t (String -> CategoryName
CategoryName String
n)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. Show a => a -> String
show [GeneralInstance]
rs
getTypeDefines :: Show c => [AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeDefines :: forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeDefines [AnyCategory c]
ts String
s String
n = do
CategoryMap c
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory c]
ts
let r :: CategoryResolver c
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap c
ta
TypeInstance
t <- forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
s
Positional [GeneralInstance]
ds <- forall r (m :: * -> *).
(TypeResolver r, CollectErrorsM m) =>
r -> TypeInstance -> CategoryName -> m InstanceParams
trDefines CategoryResolver c
r TypeInstance
t (String -> CategoryName
CategoryName String
n)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. Show a => a -> String
show [GeneralInstance]
ds
getTypeVariance :: Show c => [AnyCategory c] -> String -> TrackedErrors [Variance]
getTypeVariance :: forall c.
Show c =>
[AnyCategory c] -> String -> TrackedErrors [Variance]
getTypeVariance [AnyCategory c]
ts String
n = do
CategoryMap c
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory c]
ts
let r :: CategoryResolver c
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap c
ta
(Positional [Variance]
vs) <- forall r (m :: * -> *).
(TypeResolver r, CollectErrorsM m) =>
r -> CategoryName -> m (Positional Variance)
trVariance CategoryResolver c
r (String -> CategoryName
CategoryName String
n)
forall (m :: * -> *) a. Monad m => a -> m a
return [Variance]
vs
getTypeFilters :: Show c => [AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeFilters :: forall c.
Show c =>
[AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeFilters [AnyCategory c]
ts String
s = do
CategoryMap c
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory c]
ts
let r :: CategoryResolver c
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap c
ta
TypeInstance
t <- forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
s
Positional [[TypeFilter]]
vs <- forall r (m :: * -> *).
(TypeResolver r, CollectErrorsM m) =>
r -> TypeInstance -> m (Positional [TypeFilter])
trTypeFilters CategoryResolver c
r TypeInstance
t
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a b. (a -> b) -> [a] -> [b]
map forall a. Show a => a -> String
show) [[TypeFilter]]
vs
getTypeDefinesFilters :: Show c => [AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeDefinesFilters :: forall c.
Show c =>
[AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeDefinesFilters [AnyCategory c]
ts String
s = do
CategoryMap c
ta <- forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes forall c. CategoryMap c
emptyCategoryMap [AnyCategory c]
ts
let r :: CategoryResolver c
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap c
ta
DefinesInstance
t <- forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
s
Positional [[TypeFilter]]
vs <- forall r (m :: * -> *).
(TypeResolver r, CollectErrorsM m) =>
r -> DefinesInstance -> m (Positional [TypeFilter])
trDefinesFilters CategoryResolver c
r DefinesInstance
t
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a b. (a -> b) -> [a] -> [b]
map forall a. Show a => a -> String
show) [[TypeFilter]]
vs
scrapeAllRefines :: [AnyCategory c] -> [(String, String)]
scrapeAllRefines :: forall c. [AnyCategory c] -> [(String, String)]
scrapeAllRefines = forall a b. (a -> b) -> [a] -> [b]
map (forall a. Show a => a -> String
show forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** forall a. Show a => a -> String
show) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall {c}. AnyCategory c -> [(CategoryName, TypeInstance)]
scrapeSingle where
scrapeSingle :: AnyCategory c -> [(CategoryName, TypeInstance)]
scrapeSingle (ValueInterface [c]
_ Namespace
_ CategoryName
n [PragmaCategory c]
_ [ValueParam c]
_ [ValueRefine c]
rs [ScopedFunction c]
_) = forall a b. (a -> b) -> [a] -> [b]
map ((,) CategoryName
n forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. ValueRefine c -> TypeInstance
vrType) [ValueRefine c]
rs
scrapeSingle (ValueConcrete [c]
_ Namespace
_ CategoryName
n [PragmaCategory c]
_ [FunctionVisibility c]
_ [ValueParam c]
_ [ValueRefine c]
rs [ValueDefine c]
_ [ParamFilter c]
_ [ScopedFunction c]
_) = forall a b. (a -> b) -> [a] -> [b]
map ((,) CategoryName
n forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. ValueRefine c -> TypeInstance
vrType) [ValueRefine c]
rs
scrapeSingle AnyCategory c
_ = []
scrapeAllDefines :: [AnyCategory c] -> [(String, String)]
scrapeAllDefines :: forall c. [AnyCategory c] -> [(String, String)]
scrapeAllDefines = forall a b. (a -> b) -> [a] -> [b]
map (forall a. Show a => a -> String
show forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** forall a. Show a => a -> String
show) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall {c}. AnyCategory c -> [(CategoryName, DefinesInstance)]
scrapeSingle where
scrapeSingle :: AnyCategory c -> [(CategoryName, DefinesInstance)]
scrapeSingle (ValueConcrete [c]
_ Namespace
_ CategoryName
n [PragmaCategory c]
_ [FunctionVisibility c]
_ [ValueParam c]
_ [ValueRefine c]
_ [ValueDefine c]
ds [ParamFilter c]
_ [ScopedFunction c]
_) = forall a b. (a -> b) -> [a] -> [b]
map ((,) CategoryName
n forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. ValueDefine c -> DefinesInstance
vdType) [ValueDefine c]
ds
scrapeSingle AnyCategory c
_ = []
checkPaired :: Show a => (a -> a -> TrackedErrors ()) -> [a] -> [a] -> TrackedErrors ()
checkPaired :: forall a.
Show a =>
(a -> a -> TrackedErrors ()) -> [a] -> [a] -> TrackedErrors ()
checkPaired a -> a -> TrackedErrors ()
f [a]
actual [a]
expected
| forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
actual forall a. Eq a => a -> a -> Bool
/= forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
expected =
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ String
"Different item counts: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show [a]
actual forall a. [a] -> [a] -> [a]
++ String
" (actual) vs. " forall a. [a] -> [a] -> [a]
++
forall a. Show a => a -> String
show [a]
expected forall a. [a] -> [a] -> [a]
++ String
" (expected)"
| Bool
otherwise = forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m ()
mapCompilerM_ forall {a}. Show a => (a, a, a) -> TrackedErrors ()
check (forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [a]
actual [a]
expected ([Int
1..] :: [Int])) where
check :: (a, a, a) -> TrackedErrors ()
check (a
a,a
e,a
n) = a -> a -> TrackedErrors ()
f a
a a
e forall (m :: * -> *) a. ErrorContextM m => m a -> String -> m a
<!! String
"Item " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
n forall a. [a] -> [a] -> [a]
++ String
" mismatch"
containsPaired :: (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
containsPaired :: forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
containsPaired = forall a.
Show a =>
(a -> a -> TrackedErrors ()) -> [a] -> [a] -> TrackedErrors ()
checkPaired forall {a} {m :: * -> *}.
(Eq a, ErrorContextM m, Show a) =>
a -> a -> m ()
checkSingle where
checkSingle :: a -> a -> m ()
checkSingle a
a a
e
| a
a forall a. Eq a => a -> a -> Bool
== a
e = forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show a
a forall a. [a] -> [a] -> [a]
++ String
" (actual) vs. " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show a
e forall a. [a] -> [a] -> [a]
++ String
" (expected)"
checkOperationSuccess :: String -> ([AnyCategory SourceContext] -> TrackedErrors a) -> IO (TrackedErrors ())
checkOperationSuccess :: forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess String
f [AnyCategory SourceContext] -> TrackedErrors a
o = do
String
contents <- String -> IO String
loadFile String
f
let parsed :: TrackedErrors [AnyCategory SourceContext]
parsed = forall a.
ParseFromSource a =>
String -> String -> TrackedErrors [a]
readMulti String
f String
contents :: TrackedErrors [AnyCategory SourceContext]
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall {m :: * -> *} {a}. ErrorContextM m => m a -> m a
check (TrackedErrors [AnyCategory SourceContext]
parsed forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [AnyCategory SourceContext] -> TrackedErrors a
o forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ())
where
check :: m a -> m a
check m a
x = m a
x forall (m :: * -> *) a. ErrorContextM m => m a -> String -> m a
<!! String
"Check " forall a. [a] -> [a] -> [a]
++ String
f forall a. [a] -> [a] -> [a]
++ String
":"
checkOperationFailWith :: String -> String -> ([AnyCategory SourceContext] -> TrackedErrors a) -> IO (TrackedErrors ())
checkOperationFailWith :: forall a.
String
-> String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFailWith String
m String
f [AnyCategory SourceContext] -> TrackedErrors a
o = do
String
contents <- String -> IO String
loadFile String
f
let parsed :: TrackedErrors [AnyCategory SourceContext]
parsed = forall a.
ParseFromSource a =>
String -> String -> TrackedErrors [a]
readMulti String
f String
contents :: TrackedErrors [AnyCategory SourceContext]
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall {f :: * -> *} {a}.
(ErrorContextM f, Show a) =>
TrackedErrorsT Identity a -> f ()
check (TrackedErrors [AnyCategory SourceContext]
parsed forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [AnyCategory SourceContext] -> TrackedErrors a
o forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ())
where
check :: TrackedErrorsT Identity a -> f ()
check TrackedErrorsT Identity a
c
| forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrorsT Identity a
c = do
let text :: String
text = forall a. Show a => a -> String
show (forall a. TrackedErrors a -> CompilerMessage
getCompilerError TrackedErrorsT Identity a
c)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ String
text forall source source1 target.
(RegexMaker Regex CompOption ExecOption source,
RegexContext Regex source1 target) =>
source1 -> source -> target
=~ String
m) forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ String
"Expected pattern " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show String
m forall a. [a] -> [a] -> [a]
++ String
" in error output but got\n" forall a. [a] -> [a] -> [a]
++ String
text
| Bool
otherwise = forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ String
"Check " forall a. [a] -> [a] -> [a]
++ String
f forall a. [a] -> [a] -> [a]
++ String
": Expected failure but got\n" forall a. [a] -> [a] -> [a]
++
forall a. Show a => a -> String
show (forall a. TrackedErrors a -> a
getCompilerSuccess TrackedErrorsT Identity a
c) forall a. [a] -> [a] -> [a]
++ String
"\n"
checkOperationFail :: String -> ([AnyCategory SourceContext] -> TrackedErrors a) -> IO (TrackedErrors ())
checkOperationFail :: forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail String
f [AnyCategory SourceContext] -> TrackedErrors a
o = do
String
contents <- String -> IO String
loadFile String
f
let parsed :: TrackedErrors [AnyCategory SourceContext]
parsed = forall a.
ParseFromSource a =>
String -> String -> TrackedErrors [a]
readMulti String
f String
contents :: TrackedErrors [AnyCategory SourceContext]
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall {f :: * -> *} {a}.
(ErrorContextM f, Show a) =>
TrackedErrorsT Identity a -> f ()
check (TrackedErrors [AnyCategory SourceContext]
parsed forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [AnyCategory SourceContext] -> TrackedErrors a
o forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ())
where
check :: TrackedErrorsT Identity a -> m ()
check TrackedErrorsT Identity a
c
| forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrorsT Identity a
c = forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ String
"Check " forall a. [a] -> [a] -> [a]
++ String
f forall a. [a] -> [a] -> [a]
++ String
": Expected failure but got\n" forall a. [a] -> [a] -> [a]
++
forall a. Show a => a -> String
show (forall a. TrackedErrors a -> a
getCompilerSuccess TrackedErrorsT Identity a
c) forall a. [a] -> [a] -> [a]
++ String
"\n"
checkSingleParseSuccess :: String -> IO (TrackedErrors ())
checkSingleParseSuccess :: String -> IO (TrackedErrors ())
checkSingleParseSuccess String
f = do
String
contents <- String -> IO String
loadFile String
f
let parsed :: TrackedErrors (AnyCategory SourceContext)
parsed = forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
f String
contents :: TrackedErrors (AnyCategory SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall {m :: * -> *} {a}.
ErrorContextM m =>
TrackedErrorsT Identity a -> m ()
check TrackedErrors (AnyCategory SourceContext)
parsed
where
check :: TrackedErrorsT Identity a -> m ()
check TrackedErrorsT Identity a
c
| forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrorsT Identity a
c = forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ String
"Parse " forall a. [a] -> [a] -> [a]
++ String
f forall a. [a] -> [a] -> [a]
++ String
":\n" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (forall a. TrackedErrors a -> CompilerMessage
getCompilerError TrackedErrorsT Identity a
c)
| Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return ()
checkSingleParseFail :: String -> IO (TrackedErrors ())
checkSingleParseFail :: String -> IO (TrackedErrors ())
checkSingleParseFail String
f = do
String
contents <- String -> IO String
loadFile String
f
let parsed :: TrackedErrors (AnyCategory SourceContext)
parsed = forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
f String
contents :: TrackedErrors (AnyCategory SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall {f :: * -> *} {a}.
(ErrorContextM f, Show a) =>
TrackedErrorsT Identity a -> f ()
check TrackedErrors (AnyCategory SourceContext)
parsed
where
check :: TrackedErrorsT Identity a -> m ()
check TrackedErrorsT Identity a
c
| forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrorsT Identity a
c = forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ String
"Parse " forall a. [a] -> [a] -> [a]
++ String
f forall a. [a] -> [a] -> [a]
++ String
": Expected failure but got\n" forall a. [a] -> [a] -> [a]
++
forall a. Show a => a -> String
show (forall a. TrackedErrors a -> a
getCompilerSuccess TrackedErrorsT Identity a
c) forall a. [a] -> [a] -> [a]
++ String
"\n"
checkShortParseSuccess :: String -> IO (TrackedErrors ())
checkShortParseSuccess :: String -> IO (TrackedErrors ())
checkShortParseSuccess String
s = do
let parsed :: TrackedErrors (AnyCategory SourceContext)
parsed = forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
s :: TrackedErrors (AnyCategory SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall {m :: * -> *} {a}.
ErrorContextM m =>
TrackedErrorsT Identity a -> m ()
check TrackedErrors (AnyCategory SourceContext)
parsed
where
check :: TrackedErrorsT Identity a -> m ()
check TrackedErrorsT Identity a
c
| forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrorsT Identity a
c = forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ String
"Parse '" forall a. [a] -> [a] -> [a]
++ String
s forall a. [a] -> [a] -> [a]
++ String
"':\n" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (forall a. TrackedErrors a -> CompilerMessage
getCompilerError TrackedErrorsT Identity a
c)
| Bool
otherwise = forall (m :: * -> *) a. Monad m => a -> m a
return ()
checkShortParseFail :: String -> IO (TrackedErrors ())
checkShortParseFail :: String -> IO (TrackedErrors ())
checkShortParseFail String
s = do
let parsed :: TrackedErrors (AnyCategory SourceContext)
parsed = forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
s :: TrackedErrors (AnyCategory SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall {f :: * -> *} {a}.
(ErrorContextM f, Show a) =>
TrackedErrorsT Identity a -> f ()
check TrackedErrors (AnyCategory SourceContext)
parsed
where
check :: TrackedErrorsT Identity a -> m ()
check TrackedErrorsT Identity a
c
| forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrorsT Identity a
c = forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ String
"Parse '" forall a. [a] -> [a] -> [a]
++ String
s forall a. [a] -> [a] -> [a]
++ String
"': Expected failure but got\n" forall a. [a] -> [a] -> [a]
++
forall a. Show a => a -> String
show (forall a. TrackedErrors a -> a
getCompilerSuccess TrackedErrorsT Identity a
c) forall a. [a] -> [a] -> [a]
++ String
"\n"
checkInferenceSuccess :: CategoryMap SourceContext -> [(String, [String])] ->
[String] -> [(String,String)] -> [(String,String)] -> TrackedErrors ()
checkInferenceSuccess :: CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm [(String, [String])]
pa [String]
is [(String, String)]
ts [(String, String)]
gs = (ParamValues -> TrackedErrors ParamValues -> TrackedErrors ())
-> CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceCommon forall {k} {a}.
(Ord k, Ord a, Show k, Show a) =>
Map k a -> TrackedErrorsT Identity (Map k a) -> TrackedErrors ()
check CategoryMap SourceContext
tm [(String, [String])]
pa [String]
is [(String, String)]
ts [(String, String)]
gs where
prefix :: String
prefix = forall a. Show a => a -> String
show [(String, String)]
ts forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ [(String, [String])] -> String
showFilters [(String, [String])]
pa
check :: Map k a -> TrackedErrorsT Identity (Map k a) -> TrackedErrors ()
check Map k a
gs2 TrackedErrorsT Identity (Map k a)
c
| forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrorsT Identity (Map k a)
c = forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ String
prefix forall a. [a] -> [a] -> [a]
++ String
":\n" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (forall a. TrackedErrors a -> CompilerMessage
getCompilerWarnings TrackedErrorsT Identity (Map k a)
c) forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (forall a. TrackedErrors a -> CompilerMessage
getCompilerError TrackedErrorsT Identity (Map k a)
c)
| Bool
otherwise = (forall k a. Map k a -> [(k, a)]
Map.toList forall a b. (a -> b) -> a -> b
$ forall a. TrackedErrors a -> a
getCompilerSuccess TrackedErrorsT Identity (Map k a)
c) forall a. (Ord a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsExactly` forall k a. Map k a -> [(k, a)]
Map.toList Map k a
gs2
checkInferenceFail :: CategoryMap SourceContext -> [(String, [String])] ->
[String] -> [(String,String)] -> TrackedErrors ()
checkInferenceFail :: CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceFail CategoryMap SourceContext
tm [(String, [String])]
pa [String]
is [(String, String)]
ts = (ParamValues -> TrackedErrors ParamValues -> TrackedErrors ())
-> CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceCommon forall {t :: (* -> *) -> * -> *} {m :: * -> *} {p} {a}.
(ErrorContextT t, ErrorContextM m, ErrorContextM (t Identity)) =>
p -> t Identity a -> m ()
check CategoryMap SourceContext
tm [(String, [String])]
pa [String]
is [(String, String)]
ts [] where
prefix :: String
prefix = forall a. Show a => a -> String
show [(String, String)]
ts forall a. [a] -> [a] -> [a]
++ String
" " forall a. [a] -> [a] -> [a]
++ [(String, [String])] -> String
showFilters [(String, [String])]
pa
check :: p -> t Identity a -> m ()
check p
_ t Identity a
c
| forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError t Identity a
c = forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM forall a b. (a -> b) -> a -> b
$ String
prefix forall a. [a] -> [a] -> [a]
++ String
": Expected failure\n"
checkInferenceCommon :: (ParamValues -> TrackedErrors ParamValues -> TrackedErrors ()) ->
CategoryMap SourceContext -> [(String,[String])] -> [String] ->
[(String,String)] -> [(String,String)] -> TrackedErrors ()
checkInferenceCommon :: (ParamValues -> TrackedErrors ParamValues -> TrackedErrors ())
-> CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceCommon ParamValues -> TrackedErrors ParamValues -> TrackedErrors ()
check CategoryMap SourceContext
tm [(String, [String])]
pa [String]
is [(String, String)]
ts [(String, String)]
gs = TrackedErrors ()
checked forall (m :: * -> *) a. ErrorContextM m => m a -> String -> m a
<!! String
context where
context :: String
context = String
"With params = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show [(String, [String])]
pa forall a. [a] -> [a] -> [a]
++ String
", pairs = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show [(String, String)]
ts
checked :: TrackedErrors ()
checked = do
let r :: CategoryResolver SourceContext
r = forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
tm
ParamFilters
pa2 <- [(String, [String])] -> TrackedErrors ParamFilters
parseFilterMap [(String, [String])]
pa
ParamValues
ia2 <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM String -> TrackedErrorsT Identity (ParamName, GeneralInstance)
readInferred [String]
is
[PatternMatch]
ts2 <- forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM (ParamValues
-> Variance
-> (String, String)
-> TrackedErrorsT Identity PatternMatch
parsePair ParamValues
ia2 Variance
Covariant) [(String, String)]
ts
let ka :: Set ParamName
ka = forall k a. Map k a -> Set k
Map.keysSet ParamValues
ia2
ParamValues
gs' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM forall {a} {b}.
(ParseFromSource a, ParseFromSource b) =>
(String, String) -> TrackedErrorsT Identity (a, b)
parseGuess [(String, String)]
gs
let f :: ParamFilters
f = forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey (\ParamName
k [TypeFilter]
_ -> Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ ParamName
k forall a. Ord a => a -> Set a -> Bool
`Set.member` Set ParamName
ka) ParamFilters
pa2
let ff :: ParamFilters
ff = forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey (\ParamName
k [TypeFilter]
_ -> ParamName
k forall a. Ord a => a -> Set a -> Bool
`Set.member` Set ParamName
ka) ParamFilters
pa2
MergeTree InferredTypeGuess
gs2 <- forall (m :: * -> *) r.
(CollectErrorsM m, TypeResolver r) =>
r
-> ParamFilters
-> ParamValues
-> [PatternMatch]
-> m (MergeTree InferredTypeGuess)
inferParamTypes CategoryResolver SourceContext
r ParamFilters
f ParamValues
ia2 [PatternMatch]
ts2
ParamValues -> TrackedErrors ParamValues -> TrackedErrors ()
check ParamValues
gs' forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) r.
(CollectErrorsM m, TypeResolver r) =>
r
-> ParamFilters
-> ParamFilters
-> ParamValues
-> MergeTree InferredTypeGuess
-> m ParamValues
mergeInferredTypes CategoryResolver SourceContext
r ParamFilters
f ParamFilters
ff ParamValues
ia2 MergeTree InferredTypeGuess
gs2
readInferred :: String -> TrackedErrorsT Identity (ParamName, GeneralInstance)
readInferred String
p = do
ParamName
p' <- forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
p
forall (m :: * -> *) a. Monad m => a -> m a
return (ParamName
p',forall a. (Eq a, Ord a) => a -> GeneralType a
singleType forall a b. (a -> b) -> a -> b
$ ParamName -> TypeInstanceOrParam
JustInferredType ParamName
p')
parseGuess :: (String, String) -> TrackedErrorsT Identity (a, b)
parseGuess (String
p,String
t) = do
a
p' <- forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
p
b
t' <- forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
t
forall (m :: * -> *) a. Monad m => a -> m a
return (a
p',b
t')
parsePair :: ParamValues
-> Variance
-> (String, String)
-> TrackedErrorsT Identity PatternMatch
parsePair ParamValues
im Variance
v (String
t1,String
t2) = do
ValueType
t1' <- forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
t1
ValueType
t2' <- forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
t2 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (m :: * -> *).
CollectErrorsM m =>
(ParamName -> m GeneralInstance) -> ValueType -> m ValueType
uncheckedSubValueType (forall {m :: * -> *}.
Monad m =>
ParamValues -> ParamName -> m GeneralInstance
weakLookup ParamValues
im)
forall (m :: * -> *) a. Monad m => a -> m a
return (Variance -> ValueType -> ValueType -> PatternMatch
TypePattern Variance
v ValueType
t1' ValueType
t2')
weakLookup :: ParamValues -> ParamName -> m GeneralInstance
weakLookup ParamValues
tm2 ParamName
n =
case ParamName
n forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` ParamValues
tm2 of
Just GeneralInstance
t -> forall (m :: * -> *) a. Monad m => a -> m a
return GeneralInstance
t
Maybe GeneralInstance
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. (Eq a, Ord a) => a -> GeneralType a
singleType forall a b. (a -> b) -> a -> b
$ Bool -> ParamName -> TypeInstanceOrParam
JustParamName Bool
True ParamName
n