module Test.TypeCategory (tests) where
import Control.Arrow
import Control.Monad ((>=>))
import System.FilePath
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.Builtin
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 ())
checkShortParseSuccess 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 ())
checkShortParseSuccess 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> () -> () }",
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"value_refines_value.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"value_refines_instance.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"value_refines_concrete.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"concrete_refines_instance.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"concrete_refines_concrete.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"concrete_defines_instance.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"concrete_defines_value.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"concrete_defines_concrete.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx")
(CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ())
-> CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrors ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourceContext)]
-> CategoryMap SourceContext
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent2",[SourceContext]
-> Namespace
-> CategoryName
-> [ValueParam SourceContext]
-> [ParamFilter SourceContext]
-> [ScopedFunction SourceContext]
-> AnyCategory SourceContext
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent2") [] [] [])
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx")
(CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ())
-> CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrors ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourceContext)]
-> CategoryMap SourceContext
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",[SourceContext]
-> Namespace
-> CategoryName
-> [ValueParam SourceContext]
-> [ParamFilter SourceContext]
-> [ScopedFunction SourceContext]
-> AnyCategory SourceContext
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [])
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"partial.0rx")
(CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ())
-> CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrors ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourceContext)]
-> CategoryMap SourceContext
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",[SourceContext]
-> Namespace
-> CategoryName
-> [ValueParam SourceContext]
-> [ValueRefine SourceContext]
-> [ParamFilter SourceContext]
-> [ScopedFunction SourceContext]
-> AnyCategory SourceContext
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ValueRefine c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [] [])
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"partial.0rx")
(CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ())
-> CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrors ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourceContext)]
-> CategoryMap SourceContext
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",[SourceContext]
-> Namespace
-> CategoryName
-> [ValueParam SourceContext]
-> [ParamFilter SourceContext]
-> [ScopedFunction SourceContext]
-> AnyCategory SourceContext
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [])
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"partial.0rx")
(CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ())
-> CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrors ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourceContext)]
-> CategoryMap SourceContext
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",[SourceContext]
-> Namespace
-> CategoryName
-> [ValueParam SourceContext]
-> [ValueRefine SourceContext]
-> [ValueDefine SourceContext]
-> [ParamFilter SourceContext]
-> [ScopedFunction SourceContext]
-> AnyCategory SourceContext
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ValueRefine c]
-> [ValueDefine c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
ValueConcrete [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [] [] [])
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"value_refines_value.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectionCycles CategoryMap SourceContext
forall k a. Map k a
Map.empty),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectionCycles CategoryMap SourceContext
forall k a. Map k a
Map.empty),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"concrete_defines_instance.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectionCycles CategoryMap SourceContext
forall k a. Map k a
Map.empty),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"value_cycle.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectionCycles CategoryMap SourceContext
forall k a. Map k a
Map.empty),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
(AnyCategory SourceContext -> String)
-> [AnyCategory SourceContext] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (CategoryName -> String
forall a. Show a => a -> String
show (CategoryName -> String)
-> (AnyCategory SourceContext -> CategoryName)
-> AnyCategory SourceContext
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnyCategory SourceContext -> CategoryName
forall c. AnyCategory c -> CategoryName
getCategoryName) [AnyCategory SourceContext]
ts2 [String] -> [String] -> TrackedErrors ()
forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [
String
"Object2",String
"Object3",String
"Object1",String
"Type",String
"Parent",String
"Child"
]),
String
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext])
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
[AnyCategory SourceContext] -> [(String, String)]
forall c. [AnyCategory c] -> [(String, String)]
scrapeAllRefines [AnyCategory SourceContext]
ts3 [(String, String)] -> [(String, String)] -> TrackedErrors ()
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")
]
[AnyCategory SourceContext] -> [(String, String)]
forall c. [AnyCategory c] -> [(String, String)]
scrapeAllDefines [AnyCategory SourceContext]
ts3 [(String, String)] -> [(String, String)] -> TrackedErrors ()
forall a. (Ord a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsExactly` [
(String
"Child",String
"Type<Child>")
]),
String
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext])
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (CategoryMap SourceContext
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> CategoryMap SourceContext
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourceContext)]
-> CategoryMap SourceContext
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent2",[SourceContext]
-> Namespace
-> CategoryName
-> [ValueParam SourceContext]
-> [ParamFilter SourceContext]
-> [ScopedFunction SourceContext]
-> AnyCategory SourceContext
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent2") [] [] [])
]
[AnyCategory SourceContext]
ts2 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
existing [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
existing [AnyCategory SourceContext]
ts2),
String
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext])
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (CategoryMap SourceContext
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> CategoryMap SourceContext
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourceContext)]
-> CategoryMap SourceContext
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",[SourceContext]
-> Namespace
-> CategoryName
-> [ValueParam SourceContext]
-> [ParamFilter SourceContext]
-> [ScopedFunction SourceContext]
-> AnyCategory SourceContext
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [])
]
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
existing [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a. Monad m => a -> m a
return (CategoryMap SourceContext
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> CategoryMap SourceContext
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourceContext)]
-> CategoryMap SourceContext
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",
[SourceContext]
-> Namespace
-> CategoryName
-> [ValueParam SourceContext]
-> [ValueRefine SourceContext]
-> [ParamFilter SourceContext]
-> [ScopedFunction SourceContext]
-> AnyCategory SourceContext
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ValueRefine c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") []
[[SourceContext] -> TypeInstance -> ValueRefine SourceContext
forall c. [c] -> TypeInstance -> ValueRefine c
ValueRefine [] (TypeInstance -> ValueRefine SourceContext)
-> TypeInstance -> ValueRefine SourceContext
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Object1") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
[SourceContext] -> TypeInstance -> ValueRefine SourceContext
forall c. [c] -> TypeInstance -> ValueRefine c
ValueRefine [] (TypeInstance -> ValueRefine SourceContext)
-> TypeInstance -> ValueRefine SourceContext
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Object2") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional [])] [] []),
(String -> CategoryName
CategoryName String
"Object2",
[SourceContext]
-> Namespace
-> CategoryName
-> [ValueParam SourceContext]
-> [ValueRefine SourceContext]
-> [ParamFilter SourceContext]
-> [ScopedFunction SourceContext]
-> AnyCategory SourceContext
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ValueRefine c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Object2") [] [] [] [])
]
[AnyCategory SourceContext]
ts2 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
existing [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
existing [AnyCategory SourceContext]
ts2
[AnyCategory SourceContext] -> [(String, String)]
forall c. [AnyCategory c] -> [(String, String)]
scrapeAllRefines [AnyCategory SourceContext]
ts3 [(String, String)] -> [(String, String)] -> TrackedErrors ()
forall a. (Ord a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsExactly` [
(String
"Child",String
"Parent"),
(String
"Child",String
"Object1"),
(String
"Child",String
"Object2")
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"valid_variances.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"contravariant_refines_covariant.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"contravariant_refines_invariant.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"covariant_refines_contravariant.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"covariant_refines_invariant.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"contravariant_defines_covariant.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"contravariant_defines_invariant.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"covariant_defines_contravariant.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"covariant_defines_invariant.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"concrete_duplicate_param.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"type_duplicate_param.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"value_duplicate_param.0rx") (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx")
(CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ())
-> CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrors ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourceContext)]
-> CategoryMap SourceContext
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent2",[SourceContext]
-> Namespace
-> CategoryName
-> [ValueParam SourceContext]
-> [ParamFilter SourceContext]
-> [ScopedFunction SourceContext]
-> AnyCategory SourceContext
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent2") [] [] [])
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx")
(CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ())
-> CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrors ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourceContext)]
-> CategoryMap SourceContext
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",[SourceContext]
-> Namespace
-> CategoryName
-> [ValueParam SourceContext]
-> [ParamFilter SourceContext]
-> [ScopedFunction SourceContext]
-> AnyCategory SourceContext
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [])
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"partial_params.0rx")
(CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ())
-> CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrors ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourceContext)]
-> CategoryMap SourceContext
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",
[SourceContext]
-> Namespace
-> CategoryName
-> [ValueParam SourceContext]
-> [ValueRefine SourceContext]
-> [ParamFilter SourceContext]
-> [ScopedFunction SourceContext]
-> AnyCategory SourceContext
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ValueRefine c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent")
[[SourceContext]
-> ParamName -> Variance -> ValueParam SourceContext
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#w") Variance
Contravariant,
[SourceContext]
-> ParamName -> Variance -> ValueParam SourceContext
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#z") Variance
Covariant] [] [] [])
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"partial_params.0rx")
(CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ())
-> CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrors ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourceContext)]
-> CategoryMap SourceContext
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",
[SourceContext]
-> Namespace
-> CategoryName
-> [ValueParam SourceContext]
-> [ValueRefine SourceContext]
-> [ParamFilter SourceContext]
-> [ScopedFunction SourceContext]
-> AnyCategory SourceContext
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ValueRefine c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent")
[[SourceContext]
-> ParamName -> Variance -> ValueParam SourceContext
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#w") Variance
Invariant,
[SourceContext]
-> ParamName -> Variance -> ValueParam SourceContext
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#z") Variance
Covariant] [] [] [])
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"partial_params.0rx")
(CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances (CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ())
-> CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrors ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourceContext)]
-> CategoryMap SourceContext
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",
[SourceContext]
-> Namespace
-> CategoryName
-> [ValueParam SourceContext]
-> [ValueRefine SourceContext]
-> [ParamFilter SourceContext]
-> [ScopedFunction SourceContext]
-> AnyCategory SourceContext
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ValueRefine c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent")
[[SourceContext]
-> ParamName -> Variance -> ValueParam SourceContext
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#w") Variance
Contravariant,
[SourceContext]
-> ParamName -> Variance -> ValueParam SourceContext
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#z") Variance
Invariant] [] [] [])
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete.0rx")
(\[AnyCategory SourceContext]
ts -> do
[String]
rs <- [AnyCategory SourceContext]
-> String -> String -> TrackedErrors [String]
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 [String] -> [String] -> TrackedErrors ()
forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [String
"#a",String
"#b",String
"#c",String
"#d",String
"#e",String
"#f"]
),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
[String]
rs <- [AnyCategory SourceContext]
-> String -> String -> TrackedErrors [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Object1<#a,#b>" String
"Object1"
[String]
rs [String] -> [String] -> TrackedErrors ()
forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [String
"#a",String
"#b"]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
[String]
rs <- [AnyCategory SourceContext]
-> String -> String -> TrackedErrors [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Object1<#a,#b>" String
"Object3"
[String]
rs [String] -> [String] -> TrackedErrors ()
forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [String
"#b"]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
[String]
rs <- [AnyCategory SourceContext]
-> String -> String -> TrackedErrors [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Undefined<#a,#b>" String
"Undefined"
[String]
rs [String] -> [String] -> TrackedErrors ()
forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [String
"#a",String
"#b"]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
[String]
rs <- [AnyCategory SourceContext]
-> String -> String -> TrackedErrors [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Object1<#a>" String
"Object1"
[String]
rs [String] -> [String] -> TrackedErrors ()
forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [String
"#a"]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
[String]
rs <- [AnyCategory SourceContext]
-> String -> String -> TrackedErrors [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Parent<#t>" String
"Object1"
[String]
rs [String] -> [String] -> TrackedErrors ()
forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [String
"#t",String
"Object3<Object2>"]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors [String])
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
[AnyCategory SourceContext]
-> String -> String -> TrackedErrors [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Parent<#t>" String
"Child"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors [String])
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
[AnyCategory SourceContext]
-> String -> String -> TrackedErrors [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Child" String
"Type"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors [String])
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
[AnyCategory SourceContext]
-> String -> String -> TrackedErrors [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory SourceContext]
ts3 String
"Child" String
"Missing"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[String]
rs <- [AnyCategory SourceContext]
-> String -> String -> TrackedErrors [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeDefines [AnyCategory SourceContext]
ts String
"Child" String
"Type"
[String]
rs [String] -> [String] -> TrackedErrors ()
forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [String
"Child"]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors [String])
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
-> String -> String -> TrackedErrors [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeDefines [AnyCategory SourceContext]
ts String
"Child" String
"Parent"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors [String])
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
-> String -> String -> TrackedErrors [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeDefines [AnyCategory SourceContext]
ts String
"Child" String
"Missing"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete.0rx")
(\[AnyCategory SourceContext]
ts -> do
[Variance]
vs <- [AnyCategory SourceContext] -> String -> TrackedErrors [Variance]
forall c.
Show c =>
[AnyCategory c] -> String -> TrackedErrors [Variance]
getTypeVariance [AnyCategory SourceContext]
ts String
"Type"
[Variance]
vs [Variance] -> [Variance] -> TrackedErrors ()
forall a. (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsPaired` [Variance
Contravariant,Variance
Contravariant,
Variance
Invariant,Variance
Invariant,
Variance
Covariant,Variance
Covariant]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors [Variance])
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext] -> String -> TrackedErrors [Variance]
forall c.
Show c =>
[AnyCategory c] -> String -> TrackedErrors [Variance]
getTypeVariance [AnyCategory SourceContext]
ts String
"Missing"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete.0rx")
(\[AnyCategory SourceContext]
ts -> do
[[String]]
rs <- [AnyCategory SourceContext] -> String -> TrackedErrors [[String]]
forall c.
Show c =>
[AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeFilters [AnyCategory SourceContext]
ts String
"Type<#a,#b,#c,#d,#e,#f>"
([String] -> [String] -> TrackedErrors ())
-> [[String]] -> [[String]] -> TrackedErrors ()
forall a.
Show a =>
(a -> a -> TrackedErrors ()) -> [a] -> [a] -> TrackedErrors ()
checkPaired [String] -> [String] -> TrackedErrors ()
forall a. (Ord a, Show a) => [a] -> [a] -> TrackedErrors ()
containsExactly [[String]]
rs [
[String
"allows Parent"],
[String
"requires Type2<#a>"],
[String
"defines Equals<#c>"],
[],
[],
[]
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete.0rx")
(\[AnyCategory SourceContext]
ts -> do
[[String]]
rs <- [AnyCategory SourceContext] -> String -> TrackedErrors [[String]]
forall c.
Show c =>
[AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeFilters [AnyCategory SourceContext]
ts String
"Type<Type<#t>,#b,Type3<#x>,#d,#e,#f>"
([String] -> [String] -> TrackedErrors ())
-> [[String]] -> [[String]] -> TrackedErrors ()
forall a.
Show a =>
(a -> a -> TrackedErrors ()) -> [a] -> [a] -> TrackedErrors ()
checkPaired [String] -> [String] -> TrackedErrors ()
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>>"],
[],
[],
[]
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"value_interface.0rx")
(\[AnyCategory SourceContext]
ts -> do
[[String]]
rs <- [AnyCategory SourceContext] -> String -> TrackedErrors [[String]]
forall c.
Show c =>
[AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeFilters [AnyCategory SourceContext]
ts String
"Type<#a,#b,#c,#d,#e,#f>"
([String] -> [String] -> TrackedErrors ())
-> [[String]] -> [[String]] -> TrackedErrors ()
forall a.
Show a =>
(a -> a -> TrackedErrors ()) -> [a] -> [a] -> TrackedErrors ()
checkPaired [String] -> [String] -> TrackedErrors ()
forall a. (Ord a, Show a) => [a] -> [a] -> TrackedErrors ()
containsExactly [[String]]
rs [
[String
"allows Parent"],
[String
"requires Type2<#a>"],
[String
"defines Equals<#c>"],
[],
[],
[]
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"value_interface.0rx")
(\[AnyCategory SourceContext]
ts -> do
[[String]]
rs <- [AnyCategory SourceContext] -> String -> TrackedErrors [[String]]
forall c.
Show c =>
[AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeFilters [AnyCategory SourceContext]
ts String
"Type<Type<#t>,#b,Type3<#x>,#d,#e,#f>"
([String] -> [String] -> TrackedErrors ())
-> [[String]] -> [[String]] -> TrackedErrors ()
forall a.
Show a =>
(a -> a -> TrackedErrors ()) -> [a] -> [a] -> TrackedErrors ()
checkPaired [String] -> [String] -> TrackedErrors ()
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>>"],
[],
[],
[]
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"type_interface.0rx")
(\[AnyCategory SourceContext]
ts -> do
[[String]]
rs <- [AnyCategory SourceContext] -> String -> TrackedErrors [[String]]
forall c.
Show c =>
[AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeDefinesFilters [AnyCategory SourceContext]
ts String
"Type<#a,#b,#c,#d,#e,#f>"
([String] -> [String] -> TrackedErrors ())
-> [[String]] -> [[String]] -> TrackedErrors ()
forall a.
Show a =>
(a -> a -> TrackedErrors ()) -> [a] -> [a] -> TrackedErrors ()
checkPaired [String] -> [String] -> TrackedErrors ()
forall a. (Ord a, Show a) => [a] -> [a] -> TrackedErrors ()
containsExactly [[String]]
rs [
[String
"allows Parent"],
[String
"requires Type2<#a>"],
[String
"defines Equals<#c>"],
[],
[],
[]
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"type_interface.0rx")
(\[AnyCategory SourceContext]
ts -> do
[[String]]
rs <- [AnyCategory SourceContext] -> String -> TrackedErrors [[String]]
forall c.
Show c =>
[AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeDefinesFilters [AnyCategory SourceContext]
ts String
"Type<Type<#t>,#b,Type3<#x>,#d,#e,#f>"
([String] -> [String] -> TrackedErrors ())
-> [[String]] -> [[String]] -> TrackedErrors ()
forall a.
Show a =>
(a -> a -> TrackedErrors ()) -> [a] -> [a] -> TrackedErrors ()
checkPaired [String] -> [String] -> TrackedErrors ()
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>>"],
[],
[],
[]
]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"Child"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"[Child|Child]"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"[Child&Child]"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"Object2"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"[Object2|Object2]"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"[Object2&Object2]"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeFail CategoryResolver SourceContext
r [] String
"Type<Child>"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeFail CategoryResolver SourceContext
r [] String
"[Type<Child>|Type<Child>]"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeFail CategoryResolver SourceContext
r [] String
"[Type<Child>&Type<Child>]"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall k a. Map k a
Map.empty [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall k a. Map k a
Map.empty [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall k a. Map k a
Map.empty
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"Value0<Value1,Value2>"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall k a. Map k a
Map.empty [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall k a. Map k a
Map.empty [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall k a. Map k a
Map.empty
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"Value0<Value1,Value1>"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall k a. Map k a
Map.empty [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall k a. Map k a
Map.empty [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall k a. Map k a
Map.empty
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r [] String
"Value0<Value3,Value2>"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall k a. Map k a
Map.empty [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall k a. Map k a
Map.empty [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall k a. Map k a
Map.empty
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r
[(String
"#x",[]),(String
"#y",[])]
String
"Value0<#x,#y>"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall k a. Map k a
Map.empty [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall k a. Map k a
Map.empty [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall k a. Map k a
Map.empty
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r
[(String
"#x",[String
"allows #y",String
"requires Function<#x,#y>"]),
(String
"#y",[String
"requires #x",String
"defines Equals<#y>"])]
String
"Value0<#x,#y>"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall k a. Map k a
Map.empty [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall k a. Map k a
Map.empty [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall k a. Map k a
Map.empty
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r
[(String
"#x",[String
"allows Value2",String
"requires Function<#x,Value2>"])]
String
"Value0<#x,Value2>"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall k a. Map k a
Map.empty [AnyCategory SourceContext]
ts
CategoryMap SourceContext
ta <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall k a. Map k a
Map.empty [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall k a. Map k a
Map.empty
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
ta
CategoryResolver SourceContext
-> [(String, [String])] -> String -> TrackedErrors ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> TrackedErrors ()
checkTypeSuccess CategoryResolver SourceContext
r
[(String
"#x",[String
"allows Value2",String
"requires Function<#x,Value2>"]),
(String
"#y",[String
"requires #x",String
"defines Equals<#y>"])]
String
"Value0<#x,#y>"),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete_instances.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts3),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"concrete_missing_define.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts3),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"concrete_missing_refine.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts3),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"value_instances.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts3),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"value_missing_define.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts3),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"value_missing_refine.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts3),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"type_instances.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts3),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"type_missing_define.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts3),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"type_missing_refine.0rx")
(\[AnyCategory SourceContext]
ts -> do
[AnyCategory SourceContext]
ts2 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts3),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts3),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
[AnyCategory SourceContext]
ts3 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2
CategoryMap SourceContext
tm <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts3
[String]
rs <- CategoryMap SourceContext -> String -> TrackedErrors [String]
forall c.
Map CategoryName (AnyCategory c)
-> String -> TrackedErrors [String]
getRefines CategoryMap SourceContext
tm String
"Test"
[String]
rs [String] -> [String] -> TrackedErrors ()
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"]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourceContext]
ts -> do
let tm0 :: Map CategoryName (AnyCategory c)
tm0 = [(CategoryName, AnyCategory c)] -> Map CategoryName (AnyCategory c)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent2",[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent2") [] [] [])
]
CategoryMap SourceContext
tm <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
tm0 [AnyCategory SourceContext]
ts
[String]
rs <- CategoryMap SourceContext -> String -> TrackedErrors [String]
forall c.
Map CategoryName (AnyCategory c)
-> String -> TrackedErrors [String]
getRefines CategoryMap SourceContext
tm String
"Child"
[String]
rs [String] -> [String] -> TrackedErrors ()
forall a. (Ord a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsExactly` [String
"Parent<Child>",String
"Object2",
String
"Object1<Child,Object3<Object2>>",
String
"Object3<Object3<Object2>>"]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"category_function_param_match.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_param_clash.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_duplicate_param.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_filter_param.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_allows_type.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_allows_variance.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_requires_type.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_requires_variance.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_defines_type.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_defines_variance.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_arg.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_return.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"weak_arg.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"weak_return.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"function_filters_satisfied.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_requires_missed.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_allows_missed.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_defines_missed.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"valid_function_variance.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_value_arg_variance.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_value_return_variance.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_type_arg_variance.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_type_return_variance.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"valid_filter_variance.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_allows_variance_right.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_defines_variance_right.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_requires_variance_right.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_allows_variance_left.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_defines_variance_left.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_requires_variance_left.0rx")
(\[AnyCategory SourceContext]
ts -> CategoryMap SourceContext
-> [AnyCategory SourceContext] -> TrackedErrors ()
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity [AnyCategory SourceContext]
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts2 TrackedErrorsT Identity [AnyCategory SourceContext]
-> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"valid_self.0rx")
(CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> (CategoryMap SourceContext -> TrackedErrors ())
-> [AnyCategory SourceContext]
-> TrackedErrors ()
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> TrackedErrors () -> CategoryMap SourceContext -> TrackedErrors ()
forall a b. a -> b -> a
const (() -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"filtered_self.0rx")
(CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> (CategoryMap SourceContext -> TrackedErrors ())
-> [AnyCategory SourceContext]
-> TrackedErrors ()
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> TrackedErrors () -> CategoryMap SourceContext -> TrackedErrors ()
forall a b. a -> b -> a
const (() -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_merge_self.0rx")
(CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> (CategoryMap SourceContext -> TrackedErrors ())
-> [AnyCategory SourceContext]
-> TrackedErrors ()
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> TrackedErrors () -> CategoryMap SourceContext -> TrackedErrors ()
forall a b. a -> b -> a
const (() -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"contravariant_self.0rx")
(CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> (CategoryMap SourceContext -> TrackedErrors ())
-> [AnyCategory SourceContext]
-> TrackedErrors ()
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> TrackedErrors () -> CategoryMap SourceContext -> TrackedErrors ()
forall a b. a -> b -> a
const (() -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
forall a.
String
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> IO (TrackedErrors ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"invariant_self.0rx")
(CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories ([AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext))
-> (CategoryMap SourceContext -> TrackedErrors ())
-> [AnyCategory SourceContext]
-> TrackedErrors ()
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> TrackedErrors () -> CategoryMap SourceContext -> TrackedErrors ()
forall a b. a -> b -> a
const (() -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceSuccess CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[]
[]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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>")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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>")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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>")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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>]")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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>")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [AnyCategory SourceContext]
ts
CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceFail CategoryMap SourceContext
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Type1",String
"#x"),
(String
"Interface1<Type2>",String
"Interface1<#x>"),
(String
"Interface2<Type0>",String
"Interface2<#x>")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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>]")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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]")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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>")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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]")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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>")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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]")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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]")]),
String
-> ([AnyCategory SourceContext] -> TrackedErrors ())
-> IO (TrackedErrors ())
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 <- CategoryMap SourceContext
-> [AnyCategory SourceContext]
-> TrackedErrorsT Identity (CategoryMap SourceContext)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourceContext
forall c. CategoryMap c
defaultCategories [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 :: Map CategoryName (AnyCategory c)
-> String -> TrackedErrors [String]
getRefines Map CategoryName (AnyCategory c)
tm String
n =
case (String -> CategoryName
CategoryName String
n) CategoryName
-> Map CategoryName (AnyCategory c) -> Maybe (AnyCategory c)
forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` Map CategoryName (AnyCategory c)
tm of
(Just AnyCategory c
t) -> [String] -> TrackedErrors [String]
forall (m :: * -> *) a. Monad m => a -> m a
return ([String] -> TrackedErrors [String])
-> [String] -> TrackedErrors [String]
forall a b. (a -> b) -> a -> b
$ (ValueRefine c -> String) -> [ValueRefine c] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (TypeInstance -> String
forall a. Show a => a -> String
show (TypeInstance -> String)
-> (ValueRefine c -> TypeInstance) -> ValueRefine c -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueRefine c -> TypeInstance
forall c. ValueRefine c -> TypeInstance
vrType) (AnyCategory c -> [ValueRefine c]
forall c. AnyCategory c -> [ValueRefine c]
getCategoryRefines AnyCategory c
t)
Maybe (AnyCategory c)
_ -> String -> TrackedErrors [String]
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> TrackedErrors [String])
-> String -> TrackedErrors [String]
forall a b. (a -> b) -> a -> b
$ String
"Type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" not found"
getDefines :: Map.Map CategoryName (AnyCategory c) -> String -> TrackedErrors [String]
getDefines :: Map CategoryName (AnyCategory c)
-> String -> TrackedErrors [String]
getDefines Map CategoryName (AnyCategory c)
tm String
n =
case (String -> CategoryName
CategoryName String
n) CategoryName
-> Map CategoryName (AnyCategory c) -> Maybe (AnyCategory c)
forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` Map CategoryName (AnyCategory c)
tm of
(Just AnyCategory c
t) -> [String] -> TrackedErrors [String]
forall (m :: * -> *) a. Monad m => a -> m a
return ([String] -> TrackedErrors [String])
-> [String] -> TrackedErrors [String]
forall a b. (a -> b) -> a -> b
$ (ValueDefine c -> String) -> [ValueDefine c] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (DefinesInstance -> String
forall a. Show a => a -> String
show (DefinesInstance -> String)
-> (ValueDefine c -> DefinesInstance) -> ValueDefine c -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueDefine c -> DefinesInstance
forall c. ValueDefine c -> DefinesInstance
vdType) (AnyCategory c -> [ValueDefine c]
forall c. AnyCategory c -> [ValueDefine c]
getCategoryDefines AnyCategory c
t)
Maybe (AnyCategory c)
_ -> String -> TrackedErrors [String]
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> TrackedErrors [String])
-> String -> TrackedErrors [String]
forall a b. (a -> b) -> a -> b
$ String
"Type " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" not found"
getTypeRefines :: Show c => [AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines :: [AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeRefines [AnyCategory c]
ts String
s String
n = do
CategoryMap c
ta <- CategoryMap c
-> [AnyCategory c] -> TrackedErrorsT Identity (CategoryMap c)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap c
forall c. CategoryMap c
defaultCategories [AnyCategory c]
ts
let r :: CategoryResolver c
r = CategoryMap c -> CategoryResolver c
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap c
ta
TypeInstance
t <- String -> String -> TrackedErrors TypeInstance
forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
s
Positional [GeneralInstance]
rs <- CategoryResolver c
-> TypeInstance
-> CategoryName
-> TrackedErrorsT Identity InstanceParams
forall r (m :: * -> *).
(TypeResolver r, CollectErrorsM m) =>
r -> TypeInstance -> CategoryName -> m InstanceParams
trRefines CategoryResolver c
r TypeInstance
t (String -> CategoryName
CategoryName String
n)
[String] -> TrackedErrors [String]
forall (m :: * -> *) a. Monad m => a -> m a
return ([String] -> TrackedErrors [String])
-> [String] -> TrackedErrors [String]
forall a b. (a -> b) -> a -> b
$ (GeneralInstance -> String) -> [GeneralInstance] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map GeneralInstance -> String
forall a. Show a => a -> String
show [GeneralInstance]
rs
getTypeDefines :: Show c => [AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeDefines :: [AnyCategory c] -> String -> String -> TrackedErrors [String]
getTypeDefines [AnyCategory c]
ts String
s String
n = do
CategoryMap c
ta <- CategoryMap c
-> [AnyCategory c] -> TrackedErrorsT Identity (CategoryMap c)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap c
forall c. CategoryMap c
defaultCategories [AnyCategory c]
ts
let r :: CategoryResolver c
r = CategoryMap c -> CategoryResolver c
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap c
ta
TypeInstance
t <- String -> String -> TrackedErrors TypeInstance
forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
s
Positional [GeneralInstance]
ds <- CategoryResolver c
-> TypeInstance
-> CategoryName
-> TrackedErrorsT Identity InstanceParams
forall r (m :: * -> *).
(TypeResolver r, CollectErrorsM m) =>
r -> TypeInstance -> CategoryName -> m InstanceParams
trDefines CategoryResolver c
r TypeInstance
t (String -> CategoryName
CategoryName String
n)
[String] -> TrackedErrors [String]
forall (m :: * -> *) a. Monad m => a -> m a
return ([String] -> TrackedErrors [String])
-> [String] -> TrackedErrors [String]
forall a b. (a -> b) -> a -> b
$ (GeneralInstance -> String) -> [GeneralInstance] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map GeneralInstance -> String
forall a. Show a => a -> String
show [GeneralInstance]
ds
getTypeVariance :: Show c => [AnyCategory c] -> String -> TrackedErrors [Variance]
getTypeVariance :: [AnyCategory c] -> String -> TrackedErrors [Variance]
getTypeVariance [AnyCategory c]
ts String
n = do
CategoryMap c
ta <- CategoryMap c
-> [AnyCategory c] -> TrackedErrorsT Identity (CategoryMap c)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap c
forall c. CategoryMap c
defaultCategories [AnyCategory c]
ts
let r :: CategoryResolver c
r = CategoryMap c -> CategoryResolver c
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap c
ta
(Positional [Variance]
vs) <- CategoryResolver c
-> CategoryName -> TrackedErrorsT Identity (Positional Variance)
forall r (m :: * -> *).
(TypeResolver r, CollectErrorsM m) =>
r -> CategoryName -> m (Positional Variance)
trVariance CategoryResolver c
r (String -> CategoryName
CategoryName String
n)
[Variance] -> TrackedErrors [Variance]
forall (m :: * -> *) a. Monad m => a -> m a
return [Variance]
vs
getTypeFilters :: Show c => [AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeFilters :: [AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeFilters [AnyCategory c]
ts String
s = do
CategoryMap c
ta <- CategoryMap c
-> [AnyCategory c] -> TrackedErrorsT Identity (CategoryMap c)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap c
forall c. CategoryMap c
defaultCategories [AnyCategory c]
ts
let r :: CategoryResolver c
r = CategoryMap c -> CategoryResolver c
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap c
ta
TypeInstance
t <- String -> String -> TrackedErrors TypeInstance
forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
s
Positional [[TypeFilter]]
vs <- CategoryResolver c
-> TypeInstance
-> TrackedErrorsT Identity (Positional [TypeFilter])
forall r (m :: * -> *).
(TypeResolver r, CollectErrorsM m) =>
r -> TypeInstance -> m (Positional [TypeFilter])
trTypeFilters CategoryResolver c
r TypeInstance
t
[[String]] -> TrackedErrors [[String]]
forall (m :: * -> *) a. Monad m => a -> m a
return ([[String]] -> TrackedErrors [[String]])
-> [[String]] -> TrackedErrors [[String]]
forall a b. (a -> b) -> a -> b
$ ([TypeFilter] -> [String]) -> [[TypeFilter]] -> [[String]]
forall a b. (a -> b) -> [a] -> [b]
map ((TypeFilter -> String) -> [TypeFilter] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map TypeFilter -> String
forall a. Show a => a -> String
show) [[TypeFilter]]
vs
getTypeDefinesFilters :: Show c => [AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeDefinesFilters :: [AnyCategory c] -> String -> TrackedErrors [[String]]
getTypeDefinesFilters [AnyCategory c]
ts String
s = do
CategoryMap c
ta <- CategoryMap c
-> [AnyCategory c] -> TrackedErrorsT Identity (CategoryMap c)
forall c (m :: * -> *).
(Show c, CollectErrorsM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap c
forall c. CategoryMap c
defaultCategories [AnyCategory c]
ts
let r :: CategoryResolver c
r = CategoryMap c -> CategoryResolver c
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap c
ta
DefinesInstance
t <- String -> String -> TrackedErrors DefinesInstance
forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
s
Positional [[TypeFilter]]
vs <- CategoryResolver c
-> DefinesInstance
-> TrackedErrorsT Identity (Positional [TypeFilter])
forall r (m :: * -> *).
(TypeResolver r, CollectErrorsM m) =>
r -> DefinesInstance -> m (Positional [TypeFilter])
trDefinesFilters CategoryResolver c
r DefinesInstance
t
[[String]] -> TrackedErrors [[String]]
forall (m :: * -> *) a. Monad m => a -> m a
return ([[String]] -> TrackedErrors [[String]])
-> [[String]] -> TrackedErrors [[String]]
forall a b. (a -> b) -> a -> b
$ ([TypeFilter] -> [String]) -> [[TypeFilter]] -> [[String]]
forall a b. (a -> b) -> [a] -> [b]
map ((TypeFilter -> String) -> [TypeFilter] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map TypeFilter -> String
forall a. Show a => a -> String
show) [[TypeFilter]]
vs
scrapeAllRefines :: [AnyCategory c] -> [(String, String)]
scrapeAllRefines :: [AnyCategory c] -> [(String, String)]
scrapeAllRefines = ((CategoryName, TypeInstance) -> (String, String))
-> [(CategoryName, TypeInstance)] -> [(String, String)]
forall a b. (a -> b) -> [a] -> [b]
map (CategoryName -> String
forall a. Show a => a -> String
show (CategoryName -> String)
-> (TypeInstance -> String)
-> (CategoryName, TypeInstance)
-> (String, String)
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** TypeInstance -> String
forall a. Show a => a -> String
show) ([(CategoryName, TypeInstance)] -> [(String, String)])
-> ([AnyCategory c] -> [(CategoryName, TypeInstance)])
-> [AnyCategory c]
-> [(String, String)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[(CategoryName, TypeInstance)]] -> [(CategoryName, TypeInstance)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[(CategoryName, TypeInstance)]]
-> [(CategoryName, TypeInstance)])
-> ([AnyCategory c] -> [[(CategoryName, TypeInstance)]])
-> [AnyCategory c]
-> [(CategoryName, TypeInstance)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AnyCategory c -> [(CategoryName, TypeInstance)])
-> [AnyCategory c] -> [[(CategoryName, TypeInstance)]]
forall a b. (a -> b) -> [a] -> [b]
map AnyCategory c -> [(CategoryName, TypeInstance)]
forall c. AnyCategory c -> [(CategoryName, TypeInstance)]
scrapeSingle where
scrapeSingle :: AnyCategory c -> [(CategoryName, TypeInstance)]
scrapeSingle (ValueInterface [c]
_ Namespace
_ CategoryName
n [ValueParam c]
_ [ValueRefine c]
rs [ParamFilter c]
_ [ScopedFunction c]
_) = (ValueRefine c -> (CategoryName, TypeInstance))
-> [ValueRefine c] -> [(CategoryName, TypeInstance)]
forall a b. (a -> b) -> [a] -> [b]
map ((,) CategoryName
n (TypeInstance -> (CategoryName, TypeInstance))
-> (ValueRefine c -> TypeInstance)
-> ValueRefine c
-> (CategoryName, TypeInstance)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueRefine c -> TypeInstance
forall c. ValueRefine c -> TypeInstance
vrType) [ValueRefine c]
rs
scrapeSingle (ValueConcrete [c]
_ Namespace
_ CategoryName
n [ValueParam c]
_ [ValueRefine c]
rs [ValueDefine c]
_ [ParamFilter c]
_ [ScopedFunction c]
_) = (ValueRefine c -> (CategoryName, TypeInstance))
-> [ValueRefine c] -> [(CategoryName, TypeInstance)]
forall a b. (a -> b) -> [a] -> [b]
map ((,) CategoryName
n (TypeInstance -> (CategoryName, TypeInstance))
-> (ValueRefine c -> TypeInstance)
-> ValueRefine c
-> (CategoryName, TypeInstance)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueRefine c -> TypeInstance
forall c. ValueRefine c -> TypeInstance
vrType) [ValueRefine c]
rs
scrapeSingle AnyCategory c
_ = []
scrapeAllDefines :: [AnyCategory c] -> [(String, String)]
scrapeAllDefines :: [AnyCategory c] -> [(String, String)]
scrapeAllDefines = ((CategoryName, DefinesInstance) -> (String, String))
-> [(CategoryName, DefinesInstance)] -> [(String, String)]
forall a b. (a -> b) -> [a] -> [b]
map (CategoryName -> String
forall a. Show a => a -> String
show (CategoryName -> String)
-> (DefinesInstance -> String)
-> (CategoryName, DefinesInstance)
-> (String, String)
forall (a :: * -> * -> *) b c b' c'.
Arrow a =>
a b c -> a b' c' -> a (b, b') (c, c')
*** DefinesInstance -> String
forall a. Show a => a -> String
show) ([(CategoryName, DefinesInstance)] -> [(String, String)])
-> ([AnyCategory c] -> [(CategoryName, DefinesInstance)])
-> [AnyCategory c]
-> [(String, String)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[(CategoryName, DefinesInstance)]]
-> [(CategoryName, DefinesInstance)]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[(CategoryName, DefinesInstance)]]
-> [(CategoryName, DefinesInstance)])
-> ([AnyCategory c] -> [[(CategoryName, DefinesInstance)]])
-> [AnyCategory c]
-> [(CategoryName, DefinesInstance)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AnyCategory c -> [(CategoryName, DefinesInstance)])
-> [AnyCategory c] -> [[(CategoryName, DefinesInstance)]]
forall a b. (a -> b) -> [a] -> [b]
map AnyCategory c -> [(CategoryName, DefinesInstance)]
forall c. AnyCategory c -> [(CategoryName, DefinesInstance)]
scrapeSingle where
scrapeSingle :: AnyCategory c -> [(CategoryName, DefinesInstance)]
scrapeSingle (ValueConcrete [c]
_ Namespace
_ CategoryName
n [ValueParam c]
_ [ValueRefine c]
_ [ValueDefine c]
ds [ParamFilter c]
_ [ScopedFunction c]
_) = (ValueDefine c -> (CategoryName, DefinesInstance))
-> [ValueDefine c] -> [(CategoryName, DefinesInstance)]
forall a b. (a -> b) -> [a] -> [b]
map ((,) CategoryName
n (DefinesInstance -> (CategoryName, DefinesInstance))
-> (ValueDefine c -> DefinesInstance)
-> ValueDefine c
-> (CategoryName, DefinesInstance)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValueDefine c -> DefinesInstance
forall c. ValueDefine c -> DefinesInstance
vdType) [ValueDefine c]
ds
scrapeSingle AnyCategory c
_ = []
checkPaired :: Show a => (a -> a -> TrackedErrors ()) -> [a] -> [a] -> TrackedErrors ()
checkPaired :: (a -> a -> TrackedErrors ()) -> [a] -> [a] -> TrackedErrors ()
checkPaired a -> a -> TrackedErrors ()
f [a]
actual [a]
expected
| [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
actual Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
expected =
String -> TrackedErrors ()
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> TrackedErrors ()) -> String -> TrackedErrors ()
forall a b. (a -> b) -> a -> b
$ String
"Different item counts: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [a] -> String
forall a. Show a => a -> String
show [a]
actual String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" (actual) vs. " String -> String -> String
forall a. [a] -> [a] -> [a]
++
[a] -> String
forall a. Show a => a -> String
show [a]
expected String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" (expected)"
| Bool
otherwise = ((a, a, Int) -> TrackedErrors ())
-> [(a, a, Int)] -> TrackedErrors ()
forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m ()
mapCompilerM_ (a, a, Int) -> TrackedErrors ()
forall a. Show a => (a, a, a) -> TrackedErrors ()
check ([a] -> [a] -> [Int] -> [(a, a, Int)]
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 TrackedErrors () -> String -> TrackedErrors ()
forall (m :: * -> *) a. ErrorContextM m => m a -> String -> m a
<!! String
"Item " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
n String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" mismatch"
containsPaired :: (Eq a, Show a) => [a] -> [a] -> TrackedErrors ()
containsPaired :: [a] -> [a] -> TrackedErrors ()
containsPaired = (a -> a -> TrackedErrors ()) -> [a] -> [a] -> TrackedErrors ()
forall a.
Show a =>
(a -> a -> TrackedErrors ()) -> [a] -> [a] -> TrackedErrors ()
checkPaired a -> a -> TrackedErrors ()
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 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
e = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = String -> m ()
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ a -> String
forall a. Show a => a -> String
show a
a String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" (actual) vs. " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
e String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" (expected)"
checkOperationSuccess :: String -> ([AnyCategory SourceContext] -> TrackedErrors a) -> IO (TrackedErrors ())
checkOperationSuccess :: 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 :: TrackedErrorsT Identity [AnyCategory SourceContext]
parsed = String
-> String -> TrackedErrorsT Identity [AnyCategory SourceContext]
forall a.
ParseFromSource a =>
String -> String -> TrackedErrors [a]
readMulti String
f String
contents :: TrackedErrors [AnyCategory SourceContext]
TrackedErrors () -> IO (TrackedErrors ())
forall (m :: * -> *) a. Monad m => a -> m a
return (TrackedErrors () -> IO (TrackedErrors ()))
-> TrackedErrors () -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a. ErrorContextM m => m a -> m a
check (TrackedErrorsT Identity [AnyCategory SourceContext]
parsed TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> TrackedErrors a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [AnyCategory SourceContext] -> TrackedErrors a
o TrackedErrors a -> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
where
check :: m a -> m a
check m a
x = m a
x m a -> String -> m a
forall (m :: * -> *) a. ErrorContextM m => m a -> String -> m a
<!! String
"Check " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
f String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":"
checkOperationFail :: String -> ([AnyCategory SourceContext] -> TrackedErrors a) -> IO (TrackedErrors ())
checkOperationFail :: 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 :: TrackedErrorsT Identity [AnyCategory SourceContext]
parsed = String
-> String -> TrackedErrorsT Identity [AnyCategory SourceContext]
forall a.
ParseFromSource a =>
String -> String -> TrackedErrors [a]
readMulti String
f String
contents :: TrackedErrors [AnyCategory SourceContext]
TrackedErrors () -> IO (TrackedErrors ())
forall (m :: * -> *) a. Monad m => a -> m a
return (TrackedErrors () -> IO (TrackedErrors ()))
-> TrackedErrors () -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a.
(ErrorContextM m, Show a) =>
TrackedErrorsT Identity a -> m ()
check (TrackedErrorsT Identity [AnyCategory SourceContext]
parsed TrackedErrorsT Identity [AnyCategory SourceContext]
-> ([AnyCategory SourceContext] -> TrackedErrors a)
-> TrackedErrors a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [AnyCategory SourceContext] -> TrackedErrors a
o TrackedErrors a -> TrackedErrors () -> TrackedErrors ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> TrackedErrors ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
where
check :: TrackedErrorsT Identity a -> m ()
check TrackedErrorsT Identity a
c
| TrackedErrorsT Identity a -> Bool
forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrorsT Identity a
c = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = String -> m ()
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"Check " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
f String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": Expected failure but got\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++
a -> String
forall a. Show a => a -> String
show (TrackedErrorsT Identity a -> a
forall a. TrackedErrors a -> a
getCompilerSuccess TrackedErrorsT Identity a
c) String -> String -> String
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 = String -> String -> TrackedErrors (AnyCategory SourceContext)
forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
f String
contents :: TrackedErrors (AnyCategory SourceContext)
TrackedErrors () -> IO (TrackedErrors ())
forall (m :: * -> *) a. Monad m => a -> m a
return (TrackedErrors () -> IO (TrackedErrors ()))
-> TrackedErrors () -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ TrackedErrors (AnyCategory SourceContext) -> TrackedErrors ()
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
| TrackedErrorsT Identity a -> Bool
forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrorsT Identity a
c = String -> m ()
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"Parse " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
f String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CompilerMessage -> String
forall a. Show a => a -> String
show (TrackedErrorsT Identity a -> CompilerMessage
forall a. TrackedErrors a -> CompilerMessage
getCompilerError TrackedErrorsT Identity a
c)
| Bool
otherwise = () -> m ()
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 = String -> String -> TrackedErrors (AnyCategory SourceContext)
forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
f String
contents :: TrackedErrors (AnyCategory SourceContext)
TrackedErrors () -> IO (TrackedErrors ())
forall (m :: * -> *) a. Monad m => a -> m a
return (TrackedErrors () -> IO (TrackedErrors ()))
-> TrackedErrors () -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ TrackedErrors (AnyCategory SourceContext) -> TrackedErrors ()
forall (m :: * -> *) a.
(ErrorContextM m, Show a) =>
TrackedErrorsT Identity a -> m ()
check TrackedErrors (AnyCategory SourceContext)
parsed
where
check :: TrackedErrorsT Identity a -> m ()
check TrackedErrorsT Identity a
c
| TrackedErrorsT Identity a -> Bool
forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrorsT Identity a
c = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = String -> m ()
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"Parse " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
f String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": Expected failure but got\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++
a -> String
forall a. Show a => a -> String
show (TrackedErrorsT Identity a -> a
forall a. TrackedErrors a -> a
getCompilerSuccess TrackedErrorsT Identity a
c) String -> String -> String
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 = String -> String -> TrackedErrors (AnyCategory SourceContext)
forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
s :: TrackedErrors (AnyCategory SourceContext)
TrackedErrors () -> IO (TrackedErrors ())
forall (m :: * -> *) a. Monad m => a -> m a
return (TrackedErrors () -> IO (TrackedErrors ()))
-> TrackedErrors () -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ TrackedErrors (AnyCategory SourceContext) -> TrackedErrors ()
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
| TrackedErrorsT Identity a -> Bool
forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrorsT Identity a
c = String -> m ()
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"Parse '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"':\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CompilerMessage -> String
forall a. Show a => a -> String
show (TrackedErrorsT Identity a -> CompilerMessage
forall a. TrackedErrors a -> CompilerMessage
getCompilerError TrackedErrorsT Identity a
c)
| Bool
otherwise = () -> m ()
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 = String -> String -> TrackedErrors (AnyCategory SourceContext)
forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
s :: TrackedErrors (AnyCategory SourceContext)
TrackedErrors () -> IO (TrackedErrors ())
forall (m :: * -> *) a. Monad m => a -> m a
return (TrackedErrors () -> IO (TrackedErrors ()))
-> TrackedErrors () -> IO (TrackedErrors ())
forall a b. (a -> b) -> a -> b
$ TrackedErrors (AnyCategory SourceContext) -> TrackedErrors ()
forall (m :: * -> *) a.
(ErrorContextM m, Show a) =>
TrackedErrorsT Identity a -> m ()
check TrackedErrors (AnyCategory SourceContext)
parsed
where
check :: TrackedErrorsT Identity a -> m ()
check TrackedErrorsT Identity a
c
| TrackedErrorsT Identity a -> Bool
forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrorsT Identity a
c = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = String -> m ()
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"Parse '" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"': Expected failure but got\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++
a -> String
forall a. Show a => a -> String
show (TrackedErrorsT Identity a -> a
forall a. TrackedErrors a -> a
getCompilerSuccess TrackedErrorsT Identity a
c) String -> String -> String
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 = ([InferredTypeGuess]
-> TrackedErrors [InferredTypeGuess] -> TrackedErrors ())
-> CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceCommon [InferredTypeGuess]
-> TrackedErrors [InferredTypeGuess] -> TrackedErrors ()
forall a.
(Ord a, Show a) =>
[a] -> TrackedErrorsT Identity [a] -> TrackedErrors ()
check CategoryMap SourceContext
tm [(String, [String])]
pa [String]
is [(String, String)]
ts [(String, String)]
gs where
prefix :: String
prefix = [(String, String)] -> String
forall a. Show a => a -> String
show [(String, String)]
ts String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, [String])] -> String
showParams [(String, [String])]
pa
check :: [a] -> TrackedErrorsT Identity [a] -> TrackedErrors ()
check [a]
gs2 TrackedErrorsT Identity [a]
c
| TrackedErrorsT Identity [a] -> Bool
forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError TrackedErrorsT Identity [a]
c = String -> TrackedErrors ()
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> TrackedErrors ()) -> String -> TrackedErrors ()
forall a b. (a -> b) -> a -> b
$ String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CompilerMessage -> String
forall a. Show a => a -> String
show (TrackedErrorsT Identity [a] -> CompilerMessage
forall a. TrackedErrors a -> CompilerMessage
getCompilerWarnings TrackedErrorsT Identity [a]
c) String -> String -> String
forall a. [a] -> [a] -> [a]
++ CompilerMessage -> String
forall a. Show a => a -> String
show (TrackedErrorsT Identity [a] -> CompilerMessage
forall a. TrackedErrors a -> CompilerMessage
getCompilerError TrackedErrorsT Identity [a]
c)
| Bool
otherwise = TrackedErrorsT Identity [a] -> [a]
forall a. TrackedErrors a -> a
getCompilerSuccess TrackedErrorsT Identity [a]
c [a] -> [a] -> TrackedErrors ()
forall a. (Ord a, Show a) => [a] -> [a] -> TrackedErrors ()
`containsExactly` [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 = ([InferredTypeGuess]
-> TrackedErrors [InferredTypeGuess] -> TrackedErrors ())
-> CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceCommon [InferredTypeGuess]
-> TrackedErrors [InferredTypeGuess] -> TrackedErrors ()
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 = [(String, String)] -> String
forall a. Show a => a -> String
show [(String, String)]
ts String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, [String])] -> String
showParams [(String, [String])]
pa
check :: p -> t Identity a -> m ()
check p
_ t Identity a
c
| t Identity a -> Bool
forall (t :: (* -> *) -> * -> *) a.
(ErrorContextT t, ErrorContextM (t Identity)) =>
t Identity a -> Bool
isCompilerError t Identity a
c = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = String -> m ()
forall (m :: * -> *) a. ErrorContextM m => String -> m a
compilerErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": Expected failure\n"
checkInferenceCommon :: ([InferredTypeGuess] -> TrackedErrors [InferredTypeGuess] -> TrackedErrors ()) ->
CategoryMap SourceContext -> [(String,[String])] -> [String] ->
[(String,String)] -> [(String,String)] -> TrackedErrors ()
checkInferenceCommon :: ([InferredTypeGuess]
-> TrackedErrors [InferredTypeGuess] -> TrackedErrors ())
-> CategoryMap SourceContext
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> TrackedErrors ()
checkInferenceCommon [InferredTypeGuess]
-> TrackedErrors [InferredTypeGuess] -> TrackedErrors ()
check CategoryMap SourceContext
tm [(String, [String])]
pa [String]
is [(String, String)]
ts [(String, String)]
gs = TrackedErrors ()
checked TrackedErrors () -> String -> TrackedErrors ()
forall (m :: * -> *) a. ErrorContextM m => m a -> String -> m a
<!! String
context where
context :: String
context = String
"With params = " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, [String])] -> String
forall a. Show a => a -> String
show [(String, [String])]
pa String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
", pairs = " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, String)] -> String
forall a. Show a => a -> String
show [(String, String)]
ts
checked :: TrackedErrors ()
checked = do
let r :: CategoryResolver SourceContext
r = CategoryMap SourceContext -> CategoryResolver SourceContext
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourceContext
tm
ParamFilters
pa2 <- [(String, [String])] -> TrackedErrors ParamFilters
parseFilterMap [(String, [String])]
pa
Map ParamName GeneralInstance
ia2 <- ([(ParamName, GeneralInstance)] -> Map ParamName GeneralInstance)
-> TrackedErrorsT Identity [(ParamName, GeneralInstance)]
-> TrackedErrorsT Identity (Map ParamName GeneralInstance)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [(ParamName, GeneralInstance)] -> Map ParamName GeneralInstance
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList (TrackedErrorsT Identity [(ParamName, GeneralInstance)]
-> TrackedErrorsT Identity (Map ParamName GeneralInstance))
-> TrackedErrorsT Identity [(ParamName, GeneralInstance)]
-> TrackedErrorsT Identity (Map ParamName GeneralInstance)
forall a b. (a -> b) -> a -> b
$ (String -> TrackedErrorsT Identity (ParamName, GeneralInstance))
-> [String]
-> TrackedErrorsT Identity [(ParamName, GeneralInstance)]
forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM String -> TrackedErrorsT Identity (ParamName, GeneralInstance)
readInferred [String]
is
[PatternMatch ValueType]
ts2 <- ((String, String)
-> TrackedErrorsT Identity (PatternMatch ValueType))
-> [(String, String)]
-> TrackedErrorsT Identity [PatternMatch ValueType]
forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM (Map ParamName GeneralInstance
-> Variance
-> (String, String)
-> TrackedErrorsT Identity (PatternMatch ValueType)
parsePair Map ParamName GeneralInstance
ia2 Variance
Covariant) [(String, String)]
ts
let ka :: Set ParamName
ka = Map ParamName GeneralInstance -> Set ParamName
forall k a. Map k a -> Set k
Map.keysSet Map ParamName GeneralInstance
ia2
[InferredTypeGuess]
gs' <- ((String, String) -> TrackedErrorsT Identity InferredTypeGuess)
-> [(String, String)] -> TrackedErrors [InferredTypeGuess]
forall (m :: * -> *) a b.
CollectErrorsM m =>
(a -> m b) -> [a] -> m [b]
mapCompilerM (String, String) -> TrackedErrorsT Identity InferredTypeGuess
parseGuess [(String, String)]
gs
let f :: ParamFilters
f = (ParamName -> [TypeFilter] -> Bool) -> ParamFilters -> ParamFilters
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey (\ParamName
k [TypeFilter]
_ -> Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ParamName
k ParamName -> Set ParamName -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set ParamName
ka) ParamFilters
pa2
let ff :: ParamFilters
ff = (ParamName -> [TypeFilter] -> Bool) -> ParamFilters -> ParamFilters
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey (\ParamName
k [TypeFilter]
_ -> ParamName
k ParamName -> Set ParamName -> Bool
forall a. Ord a => a -> Set a -> Bool
`Set.member` Set ParamName
ka) ParamFilters
pa2
MergeTree InferredTypeGuess
gs2 <- CategoryResolver SourceContext
-> ParamFilters
-> Map ParamName GeneralInstance
-> [PatternMatch ValueType]
-> TrackedErrorsT Identity (MergeTree InferredTypeGuess)
forall (m :: * -> *) r.
(CollectErrorsM m, TypeResolver r) =>
r
-> ParamFilters
-> Map ParamName GeneralInstance
-> [PatternMatch ValueType]
-> m (MergeTree InferredTypeGuess)
inferParamTypes CategoryResolver SourceContext
r ParamFilters
f Map ParamName GeneralInstance
ia2 [PatternMatch ValueType]
ts2
[InferredTypeGuess]
-> TrackedErrors [InferredTypeGuess] -> TrackedErrors ()
check [InferredTypeGuess]
gs' (TrackedErrors [InferredTypeGuess] -> TrackedErrors ())
-> TrackedErrors [InferredTypeGuess] -> TrackedErrors ()
forall a b. (a -> b) -> a -> b
$ CategoryResolver SourceContext
-> ParamFilters
-> ParamFilters
-> Map ParamName GeneralInstance
-> MergeTree InferredTypeGuess
-> TrackedErrors [InferredTypeGuess]
forall (m :: * -> *) r.
(CollectErrorsM m, TypeResolver r) =>
r
-> ParamFilters
-> ParamFilters
-> Map ParamName GeneralInstance
-> MergeTree InferredTypeGuess
-> m [InferredTypeGuess]
mergeInferredTypes CategoryResolver SourceContext
r ParamFilters
f ParamFilters
ff Map ParamName GeneralInstance
ia2 MergeTree InferredTypeGuess
gs2
readInferred :: String -> TrackedErrorsT Identity (ParamName, GeneralInstance)
readInferred String
p = do
ParamName
p' <- String -> String -> TrackedErrors ParamName
forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
p
(ParamName, GeneralInstance)
-> TrackedErrorsT Identity (ParamName, GeneralInstance)
forall (m :: * -> *) a. Monad m => a -> m a
return (ParamName
p',TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ ParamName -> TypeInstanceOrParam
JustInferredType ParamName
p')
parseGuess :: (String, String) -> TrackedErrorsT Identity InferredTypeGuess
parseGuess (String
p,String
t) = do
ParamName
p' <- String -> String -> TrackedErrors ParamName
forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
p
GeneralInstance
t' <- String -> String -> TrackedErrors GeneralInstance
forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
t
InferredTypeGuess -> TrackedErrorsT Identity InferredTypeGuess
forall (m :: * -> *) a. Monad m => a -> m a
return (InferredTypeGuess -> TrackedErrorsT Identity InferredTypeGuess)
-> InferredTypeGuess -> TrackedErrorsT Identity InferredTypeGuess
forall a b. (a -> b) -> a -> b
$ ParamName -> GeneralInstance -> Variance -> InferredTypeGuess
InferredTypeGuess ParamName
p' GeneralInstance
t' Variance
Invariant
parsePair :: Map ParamName GeneralInstance
-> Variance
-> (String, String)
-> TrackedErrorsT Identity (PatternMatch ValueType)
parsePair Map ParamName GeneralInstance
im Variance
v (String
t1,String
t2) = do
ValueType
t1' <- String -> String -> TrackedErrors ValueType
forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
t1
ValueType
t2' <- String -> String -> TrackedErrors ValueType
forall a. ParseFromSource a => String -> String -> TrackedErrors a
readSingle String
"(string)" String
t2 TrackedErrors ValueType
-> (ValueType -> TrackedErrors ValueType)
-> TrackedErrors ValueType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ParamName -> TrackedErrors GeneralInstance)
-> ValueType -> TrackedErrors ValueType
forall (m :: * -> *).
CollectErrorsM m =>
(ParamName -> m GeneralInstance) -> ValueType -> m ValueType
uncheckedSubValueType (Map ParamName GeneralInstance
-> ParamName -> TrackedErrors GeneralInstance
forall (m :: * -> *).
Monad m =>
Map ParamName GeneralInstance -> ParamName -> m GeneralInstance
weakLookup Map ParamName GeneralInstance
im)
PatternMatch ValueType
-> TrackedErrorsT Identity (PatternMatch ValueType)
forall (m :: * -> *) a. Monad m => a -> m a
return (Variance -> ValueType -> ValueType -> PatternMatch ValueType
forall a. Variance -> a -> a -> PatternMatch a
PatternMatch Variance
v ValueType
t1' ValueType
t2')
weakLookup :: Map ParamName GeneralInstance -> ParamName -> m GeneralInstance
weakLookup Map ParamName GeneralInstance
tm2 ParamName
n =
case ParamName
n ParamName -> Map ParamName GeneralInstance -> Maybe GeneralInstance
forall k a. Ord k => k -> Map k a -> Maybe a
`Map.lookup` Map ParamName GeneralInstance
tm2 of
Just GeneralInstance
t -> GeneralInstance -> m GeneralInstance
forall (m :: * -> *) a. Monad m => a -> m a
return GeneralInstance
t
Maybe GeneralInstance
Nothing -> GeneralInstance -> m GeneralInstance
forall (m :: * -> *) a. Monad m => a -> m a
return (GeneralInstance -> m GeneralInstance)
-> GeneralInstance -> m GeneralInstance
forall a b. (a -> b) -> a -> b
$ TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ Bool -> ParamName -> TypeInstanceOrParam
JustParamName Bool
True ParamName
n