{-# LANGUAGE Safe #-}
module Test.TypeCategory (tests) where
import Control.Arrow
import System.FilePath
import Text.Parsec
import qualified Data.Map as Map
import qualified Data.Set as Set
import Base.CompileError
import Base.CompileInfo
import Parser.TypeCategory ()
import Test.Common
import Types.Builtin
import Types.GeneralType
import Types.Positional
import Types.TypeCategory
import Types.TypeInstance
import Types.Variance
tests :: [IO (CompileInfo ())]
tests :: [IO (CompileInfo ())]
tests = [
String -> IO (CompileInfo ())
checkSingleParseSuccess (String
"testfiles" String -> String -> String
</> String
"value_interface.0rx"),
String -> IO (CompileInfo ())
checkSingleParseSuccess (String
"testfiles" String -> String -> String
</> String
"type_interface.0rx"),
String -> IO (CompileInfo ())
checkSingleParseSuccess (String
"testfiles" String -> String -> String
</> String
"concrete.0rx"),
String -> IO (CompileInfo ())
checkShortParseSuccess String
"concrete Type<#x> {}",
String -> IO (CompileInfo ())
checkShortParseSuccess String
"concrete Type {}",
String -> IO (CompileInfo ())
checkShortParseFail String
"concrete Type<T> {}",
String -> IO (CompileInfo ())
checkShortParseFail String
"concrete Type<optional> {}",
String -> IO (CompileInfo ())
checkShortParseFail String
"concrete Type<optional T> {}",
String -> IO (CompileInfo ())
checkShortParseFail String
"concrete Type<T<#x>> {}",
String -> IO (CompileInfo ())
checkShortParseSuccess String
"concrete Type { refines T }",
String -> IO (CompileInfo ())
checkShortParseFail String
"concrete Type { refines #x }",
String -> IO (CompileInfo ())
checkShortParseSuccess String
"concrete Type { defines T }",
String -> IO (CompileInfo ())
checkShortParseFail String
"concrete Type { defines #x }",
String -> IO (CompileInfo ())
checkShortParseFail String
"concrete Type { refines optional }",
String -> IO (CompileInfo ())
checkShortParseFail String
"concrete Type { refines optional T }",
String -> IO (CompileInfo ())
checkShortParseSuccess String
"concrete Type<#x|#y> { #x requires #y }",
String -> IO (CompileInfo ())
checkShortParseSuccess String
"concrete Type<#x|#y> { #x allows #y }",
String -> IO (CompileInfo ())
checkShortParseSuccess String
"concrete Type<#x|#y> { #x defines T }",
String -> IO (CompileInfo ())
checkShortParseFail String
"concrete Type<#x|#y> { #x defines #y }",
String -> IO (CompileInfo ())
checkShortParseSuccess String
"@type interface Type<#x> {}",
String -> IO (CompileInfo ())
checkShortParseSuccess String
"@type interface Type {}",
String -> IO (CompileInfo ())
checkShortParseFail String
"@type interface Type { refines T }",
String -> IO (CompileInfo ())
checkShortParseFail String
"@type interface Type { defines T }",
String -> IO (CompileInfo ())
checkShortParseSuccess String
"@type interface Type<#x> { #x allows T }",
String -> IO (CompileInfo ())
checkShortParseSuccess String
"@value interface Type<#x> {}",
String -> IO (CompileInfo ())
checkShortParseSuccess String
"@value interface Type {}",
String -> IO (CompileInfo ())
checkShortParseSuccess String
"@value interface Type { refines T }",
String -> IO (CompileInfo ())
checkShortParseFail String
"@value interface Type { defines T }",
String -> IO (CompileInfo ())
checkShortParseSuccess String
"@value interface Type<#x> { #x allows T }",
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"value_refines_value.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"value_refines_instance.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"value_refines_concrete.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"concrete_refines_instance.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"concrete_refines_concrete.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"concrete_defines_instance.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"concrete_defines_value.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"concrete_defines_concrete.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx")
(CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes (CategoryMap SourcePos
-> [AnyCategory SourcePos] -> CompileInfo ())
-> CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourcePos)] -> CategoryMap SourcePos
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent2",[SourcePos]
-> Namespace
-> CategoryName
-> [ValueParam SourcePos]
-> [ParamFilter SourcePos]
-> [ScopedFunction SourcePos]
-> AnyCategory SourcePos
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent2") [] [] [])
]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx")
(CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes (CategoryMap SourcePos
-> [AnyCategory SourcePos] -> CompileInfo ())
-> CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourcePos)] -> CategoryMap SourcePos
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",[SourcePos]
-> Namespace
-> CategoryName
-> [ValueParam SourcePos]
-> [ParamFilter SourcePos]
-> [ScopedFunction SourcePos]
-> AnyCategory SourcePos
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [])
]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"partial.0rx")
(CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes (CategoryMap SourcePos
-> [AnyCategory SourcePos] -> CompileInfo ())
-> CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourcePos)] -> CategoryMap SourcePos
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",[SourcePos]
-> Namespace
-> CategoryName
-> [ValueParam SourcePos]
-> [ValueRefine SourcePos]
-> [ParamFilter SourcePos]
-> [ScopedFunction SourcePos]
-> AnyCategory SourcePos
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 SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"partial.0rx")
(CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes (CategoryMap SourcePos
-> [AnyCategory SourcePos] -> CompileInfo ())
-> CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourcePos)] -> CategoryMap SourcePos
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",[SourcePos]
-> Namespace
-> CategoryName
-> [ValueParam SourcePos]
-> [ParamFilter SourcePos]
-> [ScopedFunction SourcePos]
-> AnyCategory SourcePos
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [])
]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"partial.0rx")
(CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectedTypes (CategoryMap SourcePos
-> [AnyCategory SourcePos] -> CompileInfo ())
-> CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourcePos)] -> CategoryMap SourcePos
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",[SourcePos]
-> Namespace
-> CategoryName
-> [ValueParam SourcePos]
-> [ValueRefine SourcePos]
-> [ValueDefine SourcePos]
-> [ParamFilter SourcePos]
-> [ScopedFunction SourcePos]
-> AnyCategory SourcePos
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 SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"value_refines_value.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectionCycles CategoryMap SourcePos
forall k a. Map k a
Map.empty),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectionCycles CategoryMap SourcePos
forall k a. Map k a
Map.empty),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"concrete_defines_instance.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectionCycles CategoryMap SourcePos
forall k a. Map k a
Map.empty),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"value_cycle.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkConnectionCycles CategoryMap SourcePos
forall k a. Map k a
Map.empty),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
(AnyCategory SourcePos -> String)
-> [AnyCategory SourcePos] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (CategoryName -> String
forall a. Show a => a -> String
show (CategoryName -> String)
-> (AnyCategory SourcePos -> CategoryName)
-> AnyCategory SourcePos
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AnyCategory SourcePos -> CategoryName
forall c. AnyCategory c -> CategoryName
getCategoryName) [AnyCategory SourcePos]
ts2 [String] -> [String] -> CompileInfo ()
forall a. (Eq a, Show a) => [a] -> [a] -> CompileInfo ()
`containsPaired` [
String
"Object2",String
"Object3",String
"Object1",String
"Type",String
"Parent",String
"Child"
]),
String
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos])
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
[AnyCategory SourcePos] -> [(String, String)]
forall c. [AnyCategory c] -> [(String, String)]
scrapeAllRefines [AnyCategory SourcePos]
ts3 [(String, String)] -> [(String, String)] -> CompileInfo ()
forall a. (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
`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 SourcePos] -> [(String, String)]
forall c. [AnyCategory c] -> [(String, String)]
scrapeAllDefines [AnyCategory SourcePos]
ts3 [(String, String)] -> [(String, String)] -> CompileInfo ()
forall a. (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
`containsExactly` [
(String
"Child",String
"Type<Child>")
]),
String
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos])
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
existing <- CategoryMap SourcePos
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a. Monad m => a -> m a
return (CategoryMap SourcePos
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CategoryMap SourcePos
-> CompileInfoT Identity (CategoryMap SourcePos)
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourcePos)] -> CategoryMap SourcePos
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent2",[SourcePos]
-> Namespace
-> CategoryName
-> [ValueParam SourcePos]
-> [ParamFilter SourcePos]
-> [ScopedFunction SourcePos]
-> AnyCategory SourcePos
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent2") [] [] [])
]
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
existing [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
existing [AnyCategory SourcePos]
ts2),
String
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos])
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
existing <- CategoryMap SourcePos
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a. Monad m => a -> m a
return (CategoryMap SourcePos
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CategoryMap SourcePos
-> CompileInfoT Identity (CategoryMap SourcePos)
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourcePos)] -> CategoryMap SourcePos
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",[SourcePos]
-> Namespace
-> CategoryName
-> [ValueParam SourcePos]
-> [ParamFilter SourcePos]
-> [ScopedFunction SourcePos]
-> AnyCategory SourcePos
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [])
]
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
existing [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"partial.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
existing <- CategoryMap SourcePos
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a. Monad m => a -> m a
return (CategoryMap SourcePos
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CategoryMap SourcePos
-> CompileInfoT Identity (CategoryMap SourcePos)
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourcePos)] -> CategoryMap SourcePos
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",
[SourcePos]
-> Namespace
-> CategoryName
-> [ValueParam SourcePos]
-> [ValueRefine SourcePos]
-> [ParamFilter SourcePos]
-> [ScopedFunction SourcePos]
-> AnyCategory SourcePos
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ValueRefine c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") []
[[SourcePos] -> TypeInstance -> ValueRefine SourcePos
forall c. [c] -> TypeInstance -> ValueRefine c
ValueRefine [] (TypeInstance -> ValueRefine SourcePos)
-> TypeInstance -> ValueRefine SourcePos
forall a b. (a -> b) -> a -> b
$ CategoryName -> InstanceParams -> TypeInstance
TypeInstance (String -> CategoryName
CategoryName String
"Object1") ([GeneralInstance] -> InstanceParams
forall a. [a] -> Positional a
Positional []),
[SourcePos] -> TypeInstance -> ValueRefine SourcePos
forall c. [c] -> TypeInstance -> ValueRefine c
ValueRefine [] (TypeInstance -> ValueRefine SourcePos)
-> TypeInstance -> ValueRefine SourcePos
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",
[SourcePos]
-> Namespace
-> CategoryName
-> [ValueParam SourcePos]
-> [ValueRefine SourcePos]
-> [ParamFilter SourcePos]
-> [ScopedFunction SourcePos]
-> AnyCategory SourcePos
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ValueRefine c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Object2") [] [] [] [])
]
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
existing [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
existing [AnyCategory SourcePos]
ts2
[AnyCategory SourcePos] -> [(String, String)]
forall c. [AnyCategory c] -> [(String, String)]
scrapeAllRefines [AnyCategory SourcePos]
ts3 [(String, String)] -> [(String, String)] -> CompileInfo ()
forall a. (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
`containsExactly` [
(String
"Child",String
"Parent"),
(String
"Child",String
"Object1"),
(String
"Child",String
"Object2")
]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess (String
"testfiles" String -> String -> String
</> String
"valid_variances.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"contravariant_refines_covariant.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"contravariant_refines_invariant.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"covariant_refines_contravariant.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"covariant_refines_invariant.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"contravariant_defines_covariant.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"contravariant_defines_invariant.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"covariant_defines_contravariant.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"covariant_defines_invariant.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"concrete_duplicate_param.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"type_duplicate_param.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail (String
"testfiles" String -> String -> String
</> String
"value_duplicate_param.0rx") (CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx")
(CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances (CategoryMap SourcePos
-> [AnyCategory SourcePos] -> CompileInfo ())
-> CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourcePos)] -> CategoryMap SourcePos
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent2",[SourcePos]
-> Namespace
-> CategoryName
-> [ValueParam SourcePos]
-> [ParamFilter SourcePos]
-> [ScopedFunction SourcePos]
-> AnyCategory SourcePos
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent2") [] [] [])
]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"concrete_refines_value.0rx")
(CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances (CategoryMap SourcePos
-> [AnyCategory SourcePos] -> CompileInfo ())
-> CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourcePos)] -> CategoryMap SourcePos
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",[SourcePos]
-> Namespace
-> CategoryName
-> [ValueParam SourcePos]
-> [ParamFilter SourcePos]
-> [ScopedFunction SourcePos]
-> AnyCategory SourcePos
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
InstanceInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent") [] [] [])
]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"partial_params.0rx")
(CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances (CategoryMap SourcePos
-> [AnyCategory SourcePos] -> CompileInfo ())
-> CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourcePos)] -> CategoryMap SourcePos
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",
[SourcePos]
-> Namespace
-> CategoryName
-> [ValueParam SourcePos]
-> [ValueRefine SourcePos]
-> [ParamFilter SourcePos]
-> [ScopedFunction SourcePos]
-> AnyCategory SourcePos
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ValueRefine c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent")
[[SourcePos] -> ParamName -> Variance -> ValueParam SourcePos
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#w") Variance
Contravariant,
[SourcePos] -> ParamName -> Variance -> ValueParam SourcePos
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#z") Variance
Covariant] [] [] [])
]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"partial_params.0rx")
(CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances (CategoryMap SourcePos
-> [AnyCategory SourcePos] -> CompileInfo ())
-> CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourcePos)] -> CategoryMap SourcePos
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",
[SourcePos]
-> Namespace
-> CategoryName
-> [ValueParam SourcePos]
-> [ValueRefine SourcePos]
-> [ParamFilter SourcePos]
-> [ScopedFunction SourcePos]
-> AnyCategory SourcePos
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ValueRefine c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent")
[[SourcePos] -> ParamName -> Variance -> ValueParam SourcePos
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#w") Variance
Invariant,
[SourcePos] -> ParamName -> Variance -> ValueParam SourcePos
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#z") Variance
Covariant] [] [] [])
]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"partial_params.0rx")
(CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances (CategoryMap SourcePos
-> [AnyCategory SourcePos] -> CompileInfo ())
-> CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ [(CategoryName, AnyCategory SourcePos)] -> CategoryMap SourcePos
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [
(String -> CategoryName
CategoryName String
"Parent",
[SourcePos]
-> Namespace
-> CategoryName
-> [ValueParam SourcePos]
-> [ValueRefine SourcePos]
-> [ParamFilter SourcePos]
-> [ScopedFunction SourcePos]
-> AnyCategory SourcePos
forall c.
[c]
-> Namespace
-> CategoryName
-> [ValueParam c]
-> [ValueRefine c]
-> [ParamFilter c]
-> [ScopedFunction c]
-> AnyCategory c
ValueInterface [] Namespace
NoNamespace (String -> CategoryName
CategoryName String
"Parent")
[[SourcePos] -> ParamName -> Variance -> ValueParam SourcePos
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#w") Variance
Contravariant,
[SourcePos] -> ParamName -> Variance -> ValueParam SourcePos
forall c. [c] -> ParamName -> Variance -> ValueParam c
ValueParam [] (String -> ParamName
ParamName String
"#z") Variance
Invariant] [] [] [])
]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete.0rx")
(\[AnyCategory SourcePos]
ts -> do
[String]
rs <- [AnyCategory SourcePos] -> String -> String -> CompileInfo [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> CompileInfo [String]
getTypeRefines [AnyCategory SourcePos]
ts String
"Type<#a,#b,#c,#d,#e,#f>" String
"Type"
[String]
rs [String] -> [String] -> CompileInfo ()
forall a. (Eq a, Show a) => [a] -> [a] -> CompileInfo ()
`containsPaired` [String
"#a",String
"#b",String
"#c",String
"#d",String
"#e",String
"#f"]
),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
[String]
rs <- [AnyCategory SourcePos] -> String -> String -> CompileInfo [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> CompileInfo [String]
getTypeRefines [AnyCategory SourcePos]
ts3 String
"Object1<#a,#b>" String
"Object1"
[String]
rs [String] -> [String] -> CompileInfo ()
forall a. (Eq a, Show a) => [a] -> [a] -> CompileInfo ()
`containsPaired` [String
"#a",String
"#b"]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
[String]
rs <- [AnyCategory SourcePos] -> String -> String -> CompileInfo [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> CompileInfo [String]
getTypeRefines [AnyCategory SourcePos]
ts3 String
"Object1<#a,#b>" String
"Object3"
[String]
rs [String] -> [String] -> CompileInfo ()
forall a. (Eq a, Show a) => [a] -> [a] -> CompileInfo ()
`containsPaired` [String
"#b"]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
[String]
rs <- [AnyCategory SourcePos] -> String -> String -> CompileInfo [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> CompileInfo [String]
getTypeRefines [AnyCategory SourcePos]
ts3 String
"Undefined<#a,#b>" String
"Undefined"
[String]
rs [String] -> [String] -> CompileInfo ()
forall a. (Eq a, Show a) => [a] -> [a] -> CompileInfo ()
`containsPaired` [String
"#a",String
"#b"]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
[String]
rs <- [AnyCategory SourcePos] -> String -> String -> CompileInfo [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> CompileInfo [String]
getTypeRefines [AnyCategory SourcePos]
ts3 String
"Object1<#a>" String
"Object1"
[String]
rs [String] -> [String] -> CompileInfo ()
forall a. (Eq a, Show a) => [a] -> [a] -> CompileInfo ()
`containsPaired` [String
"#a"]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
[String]
rs <- [AnyCategory SourcePos] -> String -> String -> CompileInfo [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> CompileInfo [String]
getTypeRefines [AnyCategory SourcePos]
ts3 String
"Parent<#t>" String
"Object1"
[String]
rs [String] -> [String] -> CompileInfo ()
forall a. (Eq a, Show a) => [a] -> [a] -> CompileInfo ()
`containsPaired` [String
"#t",String
"Object3<Object2>"]),
String
-> ([AnyCategory SourcePos] -> CompileInfo [String])
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
[AnyCategory SourcePos] -> String -> String -> CompileInfo [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> CompileInfo [String]
getTypeRefines [AnyCategory SourcePos]
ts3 String
"Parent<#t>" String
"Child"),
String
-> ([AnyCategory SourcePos] -> CompileInfo [String])
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
[AnyCategory SourcePos] -> String -> String -> CompileInfo [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> CompileInfo [String]
getTypeRefines [AnyCategory SourcePos]
ts3 String
"Child" String
"Type"),
String
-> ([AnyCategory SourcePos] -> CompileInfo [String])
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
[AnyCategory SourcePos] -> String -> String -> CompileInfo [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> CompileInfo [String]
getTypeRefines [AnyCategory SourcePos]
ts3 String
"Child" String
"Missing"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[String]
rs <- [AnyCategory SourcePos] -> String -> String -> CompileInfo [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> CompileInfo [String]
getTypeDefines [AnyCategory SourcePos]
ts String
"Child" String
"Type"
[String]
rs [String] -> [String] -> CompileInfo ()
forall a. (Eq a, Show a) => [a] -> [a] -> CompileInfo ()
`containsPaired` [String
"Child"]),
String
-> ([AnyCategory SourcePos] -> CompileInfo [String])
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos] -> String -> String -> CompileInfo [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> CompileInfo [String]
getTypeDefines [AnyCategory SourcePos]
ts String
"Child" String
"Parent"),
String
-> ([AnyCategory SourcePos] -> CompileInfo [String])
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos] -> String -> String -> CompileInfo [String]
forall c.
Show c =>
[AnyCategory c] -> String -> String -> CompileInfo [String]
getTypeDefines [AnyCategory SourcePos]
ts String
"Child" String
"Missing"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete.0rx")
(\[AnyCategory SourcePos]
ts -> do
[Variance]
vs <- [AnyCategory SourcePos] -> String -> CompileInfo [Variance]
forall c.
Show c =>
[AnyCategory c] -> String -> CompileInfo [Variance]
getTypeVariance [AnyCategory SourcePos]
ts String
"Type"
[Variance]
vs [Variance] -> [Variance] -> CompileInfo ()
forall a. (Eq a, Show a) => [a] -> [a] -> CompileInfo ()
`containsPaired` [Variance
Contravariant,Variance
Contravariant,
Variance
Invariant,Variance
Invariant,
Variance
Covariant,Variance
Covariant]),
String
-> ([AnyCategory SourcePos] -> CompileInfo [Variance])
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos] -> String -> CompileInfo [Variance]
forall c.
Show c =>
[AnyCategory c] -> String -> CompileInfo [Variance]
getTypeVariance [AnyCategory SourcePos]
ts String
"Missing"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete.0rx")
(\[AnyCategory SourcePos]
ts -> do
[[String]]
rs <- [AnyCategory SourcePos] -> String -> CompileInfo [[String]]
forall c.
Show c =>
[AnyCategory c] -> String -> CompileInfo [[String]]
getTypeFilters [AnyCategory SourcePos]
ts String
"Type<#a,#b,#c,#d,#e,#f>"
([String] -> [String] -> CompileInfo ())
-> [[String]] -> [[String]] -> CompileInfo ()
forall a.
Show a =>
(a -> a -> CompileInfo ()) -> [a] -> [a] -> CompileInfo ()
checkPaired [String] -> [String] -> CompileInfo ()
forall a. (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
containsExactly [[String]]
rs [
[String
"allows Parent"],
[String
"requires Type2<#a>"],
[String
"defines Equals<#c>"],
[],
[],
[]
]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete.0rx")
(\[AnyCategory SourcePos]
ts -> do
[[String]]
rs <- [AnyCategory SourcePos] -> String -> CompileInfo [[String]]
forall c.
Show c =>
[AnyCategory c] -> String -> CompileInfo [[String]]
getTypeFilters [AnyCategory SourcePos]
ts String
"Type<Type<#t>,#b,Type3<#x>,#d,#e,#f>"
([String] -> [String] -> CompileInfo ())
-> [[String]] -> [[String]] -> CompileInfo ()
forall a.
Show a =>
(a -> a -> CompileInfo ()) -> [a] -> [a] -> CompileInfo ()
checkPaired [String] -> [String] -> CompileInfo ()
forall a. (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
containsExactly [[String]]
rs [
[String
"allows Parent"],
[String
"requires Type2<Type<#t>>"],
[String
"defines Equals<Type3<#x>>"],
[],
[],
[]
]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"value_interface.0rx")
(\[AnyCategory SourcePos]
ts -> do
[[String]]
rs <- [AnyCategory SourcePos] -> String -> CompileInfo [[String]]
forall c.
Show c =>
[AnyCategory c] -> String -> CompileInfo [[String]]
getTypeFilters [AnyCategory SourcePos]
ts String
"Type<#a,#b,#c,#d,#e,#f>"
([String] -> [String] -> CompileInfo ())
-> [[String]] -> [[String]] -> CompileInfo ()
forall a.
Show a =>
(a -> a -> CompileInfo ()) -> [a] -> [a] -> CompileInfo ()
checkPaired [String] -> [String] -> CompileInfo ()
forall a. (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
containsExactly [[String]]
rs [
[String
"allows Parent"],
[String
"requires Type2<#a>"],
[String
"defines Equals<#c>"],
[],
[],
[]
]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"value_interface.0rx")
(\[AnyCategory SourcePos]
ts -> do
[[String]]
rs <- [AnyCategory SourcePos] -> String -> CompileInfo [[String]]
forall c.
Show c =>
[AnyCategory c] -> String -> CompileInfo [[String]]
getTypeFilters [AnyCategory SourcePos]
ts String
"Type<Type<#t>,#b,Type3<#x>,#d,#e,#f>"
([String] -> [String] -> CompileInfo ())
-> [[String]] -> [[String]] -> CompileInfo ()
forall a.
Show a =>
(a -> a -> CompileInfo ()) -> [a] -> [a] -> CompileInfo ()
checkPaired [String] -> [String] -> CompileInfo ()
forall a. (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
containsExactly [[String]]
rs [
[String
"allows Parent"],
[String
"requires Type2<Type<#t>>"],
[String
"defines Equals<Type3<#x>>"],
[],
[],
[]
]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"type_interface.0rx")
(\[AnyCategory SourcePos]
ts -> do
[[String]]
rs <- [AnyCategory SourcePos] -> String -> CompileInfo [[String]]
forall c.
Show c =>
[AnyCategory c] -> String -> CompileInfo [[String]]
getTypeDefinesFilters [AnyCategory SourcePos]
ts String
"Type<#a,#b,#c,#d,#e,#f>"
([String] -> [String] -> CompileInfo ())
-> [[String]] -> [[String]] -> CompileInfo ()
forall a.
Show a =>
(a -> a -> CompileInfo ()) -> [a] -> [a] -> CompileInfo ()
checkPaired [String] -> [String] -> CompileInfo ()
forall a. (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
containsExactly [[String]]
rs [
[String
"allows Parent"],
[String
"requires Type2<#a>"],
[String
"defines Equals<#c>"],
[],
[],
[]
]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"type_interface.0rx")
(\[AnyCategory SourcePos]
ts -> do
[[String]]
rs <- [AnyCategory SourcePos] -> String -> CompileInfo [[String]]
forall c.
Show c =>
[AnyCategory c] -> String -> CompileInfo [[String]]
getTypeDefinesFilters [AnyCategory SourcePos]
ts String
"Type<Type<#t>,#b,Type3<#x>,#d,#e,#f>"
([String] -> [String] -> CompileInfo ())
-> [[String]] -> [[String]] -> CompileInfo ()
forall a.
Show a =>
(a -> a -> CompileInfo ()) -> [a] -> [a] -> CompileInfo ()
checkPaired [String] -> [String] -> CompileInfo ()
forall a. (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
containsExactly [[String]]
rs [
[String
"allows Parent"],
[String
"requires Type2<Type<#t>>"],
[String
"defines Equals<Type3<#x>>"],
[],
[],
[]
]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess CategoryResolver SourcePos
r [] String
"Child"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess CategoryResolver SourcePos
r [] String
"[Child|Child]"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess CategoryResolver SourcePos
r [] String
"[Child&Child]"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess CategoryResolver SourcePos
r [] String
"Object2"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess CategoryResolver SourcePos
r [] String
"[Object2|Object2]"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess CategoryResolver SourcePos
r [] String
"[Object2&Object2]"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail CategoryResolver SourcePos
r [] String
"Type<Child>"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail CategoryResolver SourcePos
r [] String
"[Type<Child>|Type<Child>]"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeFail CategoryResolver SourcePos
r [] String
"[Type<Child>&Type<Child>]"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall k a. Map k a
Map.empty [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall k a. Map k a
Map.empty [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall k a. Map k a
Map.empty
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess CategoryResolver SourcePos
r [] String
"Value0<Value1,Value2>"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall k a. Map k a
Map.empty [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall k a. Map k a
Map.empty [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall k a. Map k a
Map.empty
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess CategoryResolver SourcePos
r [] String
"Value0<Value1,Value1>"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall k a. Map k a
Map.empty [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall k a. Map k a
Map.empty [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall k a. Map k a
Map.empty
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess CategoryResolver SourcePos
r [] String
"Value0<Value3,Value2>"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall k a. Map k a
Map.empty [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall k a. Map k a
Map.empty [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall k a. Map k a
Map.empty
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess CategoryResolver SourcePos
r
[(String
"#x",[]),(String
"#y",[])]
String
"Value0<#x,#y>"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall k a. Map k a
Map.empty [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall k a. Map k a
Map.empty [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall k a. Map k a
Map.empty
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess CategoryResolver SourcePos
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 SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall k a. Map k a
Map.empty [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall k a. Map k a
Map.empty [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall k a. Map k a
Map.empty
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess CategoryResolver SourcePos
r
[(String
"#x",[String
"allows Value2",String
"requires Function<#x,Value2>"])]
String
"Value0<#x,Value2>"),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"filters.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall k a. Map k a
Map.empty [AnyCategory SourcePos]
ts
CategoryMap SourcePos
ta <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall k a. Map k a
Map.empty [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos))
-> CompileInfoT Identity (CategoryMap SourcePos)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall k a. Map k a
Map.empty
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
ta
CategoryResolver SourcePos
-> [(String, [String])] -> String -> CompileInfo ()
forall r.
TypeResolver r =>
r -> [(String, [String])] -> String -> CompileInfo ()
checkTypeSuccess CategoryResolver SourcePos
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 SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"concrete_instances.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts3),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"concrete_missing_define.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts3),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"concrete_missing_refine.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts3),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"value_instances.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts3),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"value_missing_define.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts3),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"value_missing_refine.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts3),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"type_instances.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts3),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"type_missing_define.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts3),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"type_missing_refine.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts3),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"requires_concrete.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts3),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"merged.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
[AnyCategory SourcePos]
ts3 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
declareAllTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts3
[String]
rs <- CategoryMap SourcePos -> String -> CompileInfo [String]
forall c.
Map CategoryName (AnyCategory c) -> String -> CompileInfo [String]
getRefines CategoryMap SourcePos
tm String
"Test"
[String]
rs [String] -> [String] -> CompileInfo ()
forall a. (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
`containsExactly` [String
"Value0",String
"Value1",String
"Value2",String
"Value3",
String
"Value4<Value1,Value1>",String
"Inherit1",String
"Inherit2"]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"merged.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"duplicate_refine.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"duplicate_define.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"refine_wrong_direction.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"inherit_incompatible.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"merge_incompatible.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"flatten.0rx")
(\[AnyCategory SourcePos]
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 SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
tm0 [AnyCategory SourcePos]
ts
[String]
rs <- CategoryMap SourcePos -> String -> CompileInfo [String]
forall c.
Map CategoryName (AnyCategory c) -> String -> CompileInfo [String]
getRefines CategoryMap SourcePos
tm String
"Child"
[String]
rs [String] -> [String] -> CompileInfo ()
forall a. (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
`containsExactly` [String
"Parent<Child>",String
"Object2",
String
"Object1<Child,Object3<Object2>>",
String
"Object3<Object3<Object2>>"]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"category_function_param_match.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_param_clash.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_duplicate_param.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_filter_param.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_allows_type.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_allows_variance.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_requires_type.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_requires_variance.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_defines_type.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_defines_variance.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_arg.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_bad_return.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"weak_arg.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"weak_return.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"function_filters_satisfied.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_requires_missed.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_allows_missed.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"function_defines_missed.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"valid_function_variance.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_value_arg_variance.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_value_return_variance.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_type_arg_variance.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_type_return_variance.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkCategoryInstances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"valid_filter_variance.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_allows_variance_right.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_defines_variance_right.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_requires_variance_right.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_allows_variance_left.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_defines_variance_left.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"bad_requires_variance_left.0rx")
(\[AnyCategory SourcePos]
ts -> CategoryMap SourcePos -> [AnyCategory SourcePos] -> CompileInfo ()
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m ()
checkParamVariances CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"conflicting_declaration.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"conflicting_inherited.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"successful_merge.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"merge_with_refine.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"failed_merge.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"ambiguous_merge_inherit.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"merge_different_scopes.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"successful_merge_params.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"failed_merge_params.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"preserve_merged.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail
(String
"testfiles" String -> String -> String
</> String
"conflict_in_preserved.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"resolved_in_preserved.0rx")
(\[AnyCategory SourcePos]
ts -> do
[AnyCategory SourcePos]
ts2 <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
topoSortCategories CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity [AnyCategory SourcePos]
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m [AnyCategory c]
flattenAllConnections CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts2 CompileInfoT Identity [AnyCategory SourcePos]
-> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Type1",String
"#x")]
[(String
"#x",String
"Type1")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Type2",String
"#x"),(String
"Type1",String
"#x")]
[(String
"#x",String
"Type1")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[]
[]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface1<Type2>",String
"#x"),(String
"Interface1<Type1>",String
"#x")]
[(String
"#x",String
"Interface1<Type1>")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface2<Type2>",String
"#x"),(String
"Interface2<Type1>",String
"#x")]
[(String
"#x",String
"Interface2<Type2>")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface2<Type2>",String
"Interface2<#x>"),
(String
"Interface2<Type1>",String
"Interface2<#x>")]
[(String
"#x",String
"Type2")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface3<Type1>",String
"#x"),(String
"Interface3<Type1>",String
"#x")]
[(String
"#x",String
"Interface3<Type1>")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface3<Type1>",String
"#x"),(String
"Interface3<Type2>",String
"#x")]
[(String
"#x",String
"[Interface3<Type2>|Interface3<Type1>]")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface3<Type1>",String
"Interface3<#x>"),
(String
"Interface3<Type1>",String
"Interface3<#x>")]
[(String
"#x",String
"Type1")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> CompileInfo ()
checkInferenceFail CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface3<Type1>",String
"Interface3<#x>"),
(String
"Interface3<Type2>",String
"Interface3<#x>")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> CompileInfo ()
checkInferenceFail CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Type1",String
"#x"),
(String
"Interface1<Type2>",String
"Interface1<#x>"),
(String
"Interface2<Type0>",String
"Interface2<#x>")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
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 SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface1<Type1>",String
"Interface1<[#x|Interface2<#x>]>")]
[(String
"#x",String
"Type1")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface1<Type2>",String
"Interface1<[#x&Type1]>")]
[(String
"#x",String
"Type2")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface2<Type1>",String
"Interface2<[#x&Interface2<#x>]>")]
[(String
"#x",String
"Type1")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface2<Type0>",String
"Interface2<[#x|Type1]>")]
[(String
"#x",String
"Type0")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface3<Type0>",String
"[Interface1<#x>&Interface3<#x>]")]
[(String
"#x",String
"Type0")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Type1",String
"#x"),(String
"Type2",String
"[Type2|Type0]")]
[(String
"#x",String
"Type1")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
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 SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface1<any>",String
"Interface1<#x>")]
[(String
"#x",String
"any")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"inference.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Interface2<all>",String
"Interface2<#x>")]
[(String
"#x",String
"all")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"delayed_merging.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> CompileInfo ()
checkInferenceFail CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Type",String
"[Interface1<#x>|Interface2<#x>]")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"delayed_merging.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"Base",String
"#x"),
(String
"Type",String
"[Interface1<#x>|Interface2<#x>]")]
[(String
"#x",String
"Base")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type1>|Interface3<Type2>]",String
"Interface0<#x>")]
[(String
"#x",String
"Type1")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type0>|Interface3<Type4>]",String
"Interface0<#x>")]
[(String
"#x",String
"[Type4|Type0]")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type1>&Interface3<Type2>]",String
"Interface0<#x>")]
[(String
"#x",String
"Type2")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> CompileInfo ()
checkInferenceFail CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type0>&Interface3<Type4>]",String
"Interface0<#x>")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type1>|Interface3<Type2>]",String
"Interface1<#x>")]
[(String
"#x",String
"Type2")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type0>|Interface3<Type4>]",String
"Interface1<#x>")]
[(String
"#x",String
"[Type4&Type0]")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type1>&Interface3<Type2>]",String
"Interface1<#x>")]
[(String
"#x",String
"Type1")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> CompileInfo ()
checkInferenceFail CategoryMap SourcePos
tm
[(String
"#x",[])] [String
"#x"]
[(String
"[Interface2<Type0>&Interface3<Type4>]",String
"Interface1<#x>")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[String
"requires Type0"])] [String
"#x"]
[(String
"[Interface2<Type1>&Interface3<Type4>]",String
"Interface0<#x>")]
[(String
"#x",String
"Type1")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[String
"allows Type2"])] [String
"#x"]
[(String
"[Interface2<Type1>&Interface3<Type4>]",String
"Interface0<#x>")]
[(String
"#x",String
"Type1")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[String
"defines Defined<#x>"])] [String
"#x"]
[(String
"[Interface2<Type1>&Interface3<Type4>]",String
"Interface0<#x>")]
[(String
"#x",String
"Type4")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[String
"requires Type0"])] [String
"#x"]
[(String
"[Type1|Type2]",String
"#x")]
[(String
"#x",String
"[Type1|Type2]")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm
[(String
"#x",[String
"requires #x"])] [String
"#x"]
[(String
"[Type1|Type2]",String
"#x")]
[(String
"#x",String
"[Type1|Type2]")]),
String
-> ([AnyCategory SourcePos] -> CompileInfo ())
-> IO (CompileInfo ())
forall a.
String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess
(String
"testfiles" String -> String -> String
</> String
"infer_meta.0rx")
(\[AnyCategory SourcePos]
ts -> do
CategoryMap SourcePos
tm <- CategoryMap SourcePos
-> [AnyCategory SourcePos]
-> CompileInfoT Identity (CategoryMap SourcePos)
forall c (m :: * -> *).
(Show c, CompileErrorM m) =>
CategoryMap c -> [AnyCategory c] -> m (CategoryMap c)
includeNewTypes CategoryMap SourcePos
forall c. CategoryMap c
defaultCategories [AnyCategory SourcePos]
ts
CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> CompileInfo ()
checkInferenceFail CategoryMap SourcePos
tm
[(String
"#x",[String
"requires Type0"])] [String
"#x"]
[(String
"[Type1|Type4]",String
"#x")])
]
getRefines :: Map.Map CategoryName (AnyCategory c) -> String -> CompileInfo [String]
getRefines :: Map CategoryName (AnyCategory c) -> String -> CompileInfo [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] -> CompileInfo [String]
forall (m :: * -> *) a. Monad m => a -> m a
return ([String] -> CompileInfo [String])
-> [String] -> CompileInfo [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 -> CompileInfo [String]
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> CompileInfo [String]) -> String -> CompileInfo [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 -> CompileInfo [String]
getDefines :: Map CategoryName (AnyCategory c) -> String -> CompileInfo [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] -> CompileInfo [String]
forall (m :: * -> *) a. Monad m => a -> m a
return ([String] -> CompileInfo [String])
-> [String] -> CompileInfo [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 -> CompileInfo [String]
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> CompileInfo [String]) -> String -> CompileInfo [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 -> CompileInfo [String]
getTypeRefines :: [AnyCategory c] -> String -> String -> CompileInfo [String]
getTypeRefines [AnyCategory c]
ts String
s String
n = do
CategoryMap c
ta <- CategoryMap c
-> [AnyCategory c] -> CompileInfoT Identity (CategoryMap c)
forall c (m :: * -> *).
(Show c, CompileErrorM 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 -> CompileInfo TypeInstance
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
s
Positional [GeneralInstance]
rs <- CategoryResolver c
-> TypeInstance
-> CategoryName
-> CompileInfoT Identity InstanceParams
forall r (m :: * -> *).
(TypeResolver r, CompileErrorM m) =>
r -> TypeInstance -> CategoryName -> m InstanceParams
trRefines CategoryResolver c
r TypeInstance
t (String -> CategoryName
CategoryName String
n)
[String] -> CompileInfo [String]
forall (m :: * -> *) a. Monad m => a -> m a
return ([String] -> CompileInfo [String])
-> [String] -> CompileInfo [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 -> CompileInfo [String]
getTypeDefines :: [AnyCategory c] -> String -> String -> CompileInfo [String]
getTypeDefines [AnyCategory c]
ts String
s String
n = do
CategoryMap c
ta <- CategoryMap c
-> [AnyCategory c] -> CompileInfoT Identity (CategoryMap c)
forall c (m :: * -> *).
(Show c, CompileErrorM 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 -> CompileInfo TypeInstance
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
s
Positional [GeneralInstance]
ds <- CategoryResolver c
-> TypeInstance
-> CategoryName
-> CompileInfoT Identity InstanceParams
forall r (m :: * -> *).
(TypeResolver r, CompileErrorM m) =>
r -> TypeInstance -> CategoryName -> m InstanceParams
trDefines CategoryResolver c
r TypeInstance
t (String -> CategoryName
CategoryName String
n)
[String] -> CompileInfo [String]
forall (m :: * -> *) a. Monad m => a -> m a
return ([String] -> CompileInfo [String])
-> [String] -> CompileInfo [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 -> CompileInfo [Variance]
getTypeVariance :: [AnyCategory c] -> String -> CompileInfo [Variance]
getTypeVariance [AnyCategory c]
ts String
n = do
CategoryMap c
ta <- CategoryMap c
-> [AnyCategory c] -> CompileInfoT Identity (CategoryMap c)
forall c (m :: * -> *).
(Show c, CompileErrorM 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 -> CompileInfoT Identity (Positional Variance)
forall r (m :: * -> *).
(TypeResolver r, CompileErrorM m) =>
r -> CategoryName -> m (Positional Variance)
trVariance CategoryResolver c
r (String -> CategoryName
CategoryName String
n)
[Variance] -> CompileInfo [Variance]
forall (m :: * -> *) a. Monad m => a -> m a
return [Variance]
vs
getTypeFilters :: Show c => [AnyCategory c] -> String -> CompileInfo [[String]]
getTypeFilters :: [AnyCategory c] -> String -> CompileInfo [[String]]
getTypeFilters [AnyCategory c]
ts String
s = do
CategoryMap c
ta <- CategoryMap c
-> [AnyCategory c] -> CompileInfoT Identity (CategoryMap c)
forall c (m :: * -> *).
(Show c, CompileErrorM 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 -> CompileInfo TypeInstance
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
s
Positional [[TypeFilter]]
vs <- CategoryResolver c
-> TypeInstance -> CompileInfoT Identity (Positional [TypeFilter])
forall r (m :: * -> *).
(TypeResolver r, CompileErrorM m) =>
r -> TypeInstance -> m (Positional [TypeFilter])
trTypeFilters CategoryResolver c
r TypeInstance
t
[[String]] -> CompileInfo [[String]]
forall (m :: * -> *) a. Monad m => a -> m a
return ([[String]] -> CompileInfo [[String]])
-> [[String]] -> CompileInfo [[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 -> CompileInfo [[String]]
getTypeDefinesFilters :: [AnyCategory c] -> String -> CompileInfo [[String]]
getTypeDefinesFilters [AnyCategory c]
ts String
s = do
CategoryMap c
ta <- CategoryMap c
-> [AnyCategory c] -> CompileInfoT Identity (CategoryMap c)
forall c (m :: * -> *).
(Show c, CompileErrorM 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 -> CompileInfo DefinesInstance
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
s
Positional [[TypeFilter]]
vs <- CategoryResolver c
-> DefinesInstance
-> CompileInfoT Identity (Positional [TypeFilter])
forall r (m :: * -> *).
(TypeResolver r, CompileErrorM m) =>
r -> DefinesInstance -> m (Positional [TypeFilter])
trDefinesFilters CategoryResolver c
r DefinesInstance
t
[[String]] -> CompileInfo [[String]]
forall (m :: * -> *) a. Monad m => a -> m a
return ([[String]] -> CompileInfo [[String]])
-> [[String]] -> CompileInfo [[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 -> CompileInfo ()) -> [a] -> [a] -> CompileInfo ()
checkPaired :: (a -> a -> CompileInfo ()) -> [a] -> [a] -> CompileInfo ()
checkPaired a -> a -> CompileInfo ()
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 -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> CompileInfo ()) -> String -> CompileInfo ()
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) -> CompileInfo ()) -> [(a, a, Int)] -> CompileInfo ()
forall (m :: * -> *) a b.
CompileErrorM m =>
(a -> m b) -> [a] -> m ()
mapErrorsM_ (a, a, Int) -> CompileInfo ()
forall a. Show a => (a, a, a) -> CompileInfo ()
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) -> CompileInfo ()
check (a
a,a
e,a
n) = a -> a -> CompileInfo ()
f a
a a
e CompileInfo () -> String -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM 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] -> CompileInfo ()
containsPaired :: [a] -> [a] -> CompileInfo ()
containsPaired = (a -> a -> CompileInfo ()) -> [a] -> [a] -> CompileInfo ()
forall a.
Show a =>
(a -> a -> CompileInfo ()) -> [a] -> [a] -> CompileInfo ()
checkPaired a -> a -> CompileInfo ()
forall a (m :: * -> *).
(Eq a, CompileErrorM 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. CompileErrorM m => String -> m a
compileErrorM (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 SourcePos] -> CompileInfo a) -> IO (CompileInfo ())
checkOperationSuccess :: String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationSuccess String
f [AnyCategory SourcePos] -> CompileInfo a
o = do
String
contents <- String -> IO String
loadFile String
f
let parsed :: CompileInfoT Identity [AnyCategory SourcePos]
parsed = String -> String -> CompileInfoT Identity [AnyCategory SourcePos]
forall a. ParseFromSource a => String -> String -> CompileInfo [a]
readMulti String
f String
contents :: CompileInfo [AnyCategory SourcePos]
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => m a -> m a
check (CompileInfoT Identity [AnyCategory SourcePos]
parsed CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos] -> CompileInfo a) -> CompileInfo a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [AnyCategory SourcePos] -> CompileInfo a
o CompileInfo a -> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
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. CompileErrorM 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 SourcePos] -> CompileInfo a) -> IO (CompileInfo ())
checkOperationFail :: String
-> ([AnyCategory SourcePos] -> CompileInfo a)
-> IO (CompileInfo ())
checkOperationFail String
f [AnyCategory SourcePos] -> CompileInfo a
o = do
String
contents <- String -> IO String
loadFile String
f
let parsed :: CompileInfoT Identity [AnyCategory SourcePos]
parsed = String -> String -> CompileInfoT Identity [AnyCategory SourcePos]
forall a. ParseFromSource a => String -> String -> CompileInfo [a]
readMulti String
f String
contents :: CompileInfo [AnyCategory SourcePos]
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a.
(CompileErrorM m, Show a) =>
CompileInfo a -> m ()
check (CompileInfoT Identity [AnyCategory SourcePos]
parsed CompileInfoT Identity [AnyCategory SourcePos]
-> ([AnyCategory SourcePos] -> CompileInfo a) -> CompileInfo a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [AnyCategory SourcePos] -> CompileInfo a
o CompileInfo a -> CompileInfo () -> CompileInfo ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> CompileInfo ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())
where
check :: CompileInfo a -> m ()
check CompileInfo a
c
| CompileInfo a -> Bool
forall a. CompileInfo a -> Bool
isCompileError CompileInfo a
c = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = String -> m ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"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 (CompileInfo a -> a
forall a. CompileInfo a -> a
getCompileSuccess CompileInfo a
c) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
checkSingleParseSuccess :: String -> IO (CompileInfo ())
checkSingleParseSuccess :: String -> IO (CompileInfo ())
checkSingleParseSuccess String
f = do
String
contents <- String -> IO String
loadFile String
f
let parsed :: CompileInfo (AnyCategory SourcePos)
parsed = String -> String -> CompileInfo (AnyCategory SourcePos)
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
f String
contents :: CompileInfo (AnyCategory SourcePos)
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ CompileInfo (AnyCategory SourcePos) -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => CompileInfo a -> m ()
check CompileInfo (AnyCategory SourcePos)
parsed
where
check :: CompileInfo a -> m ()
check CompileInfo a
c
| CompileInfo a -> Bool
forall a. CompileInfo a -> Bool
isCompileError CompileInfo a
c = String -> m ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"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]
++ CompileMessage -> String
forall a. Show a => a -> String
show (CompileInfo a -> CompileMessage
forall a. CompileInfo a -> CompileMessage
getCompileError CompileInfo a
c)
| Bool
otherwise = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
checkSingleParseFail :: String -> IO (CompileInfo ())
checkSingleParseFail :: String -> IO (CompileInfo ())
checkSingleParseFail String
f = do
String
contents <- String -> IO String
loadFile String
f
let parsed :: CompileInfo (AnyCategory SourcePos)
parsed = String -> String -> CompileInfo (AnyCategory SourcePos)
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
f String
contents :: CompileInfo (AnyCategory SourcePos)
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ CompileInfo (AnyCategory SourcePos) -> CompileInfo ()
forall (m :: * -> *) a.
(CompileErrorM m, Show a) =>
CompileInfo a -> m ()
check CompileInfo (AnyCategory SourcePos)
parsed
where
check :: CompileInfo a -> m ()
check CompileInfo a
c
| CompileInfo a -> Bool
forall a. CompileInfo a -> Bool
isCompileError CompileInfo a
c = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = String -> m ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"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 (CompileInfo a -> a
forall a. CompileInfo a -> a
getCompileSuccess CompileInfo a
c) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
checkShortParseSuccess :: String -> IO (CompileInfo ())
checkShortParseSuccess :: String -> IO (CompileInfo ())
checkShortParseSuccess String
s = do
let parsed :: CompileInfo (AnyCategory SourcePos)
parsed = String -> String -> CompileInfo (AnyCategory SourcePos)
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
s :: CompileInfo (AnyCategory SourcePos)
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ CompileInfo (AnyCategory SourcePos) -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => CompileInfo a -> m ()
check CompileInfo (AnyCategory SourcePos)
parsed
where
check :: CompileInfo a -> m ()
check CompileInfo a
c
| CompileInfo a -> Bool
forall a. CompileInfo a -> Bool
isCompileError CompileInfo a
c = String -> m ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"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]
++ CompileMessage -> String
forall a. Show a => a -> String
show (CompileInfo a -> CompileMessage
forall a. CompileInfo a -> CompileMessage
getCompileError CompileInfo a
c)
| Bool
otherwise = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
checkShortParseFail :: String -> IO (CompileInfo ())
checkShortParseFail :: String -> IO (CompileInfo ())
checkShortParseFail String
s = do
let parsed :: CompileInfo (AnyCategory SourcePos)
parsed = String -> String -> CompileInfo (AnyCategory SourcePos)
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
s :: CompileInfo (AnyCategory SourcePos)
CompileInfo () -> IO (CompileInfo ())
forall (m :: * -> *) a. Monad m => a -> m a
return (CompileInfo () -> IO (CompileInfo ()))
-> CompileInfo () -> IO (CompileInfo ())
forall a b. (a -> b) -> a -> b
$ CompileInfo (AnyCategory SourcePos) -> CompileInfo ()
forall (m :: * -> *) a.
(CompileErrorM m, Show a) =>
CompileInfo a -> m ()
check CompileInfo (AnyCategory SourcePos)
parsed
where
check :: CompileInfo a -> m ()
check CompileInfo a
c
| CompileInfo a -> Bool
forall a. CompileInfo a -> Bool
isCompileError CompileInfo a
c = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = String -> m ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
"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 (CompileInfo a -> a
forall a. CompileInfo a -> a
getCompileSuccess CompileInfo a
c) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
checkInferenceSuccess :: CategoryMap SourcePos -> [(String, [String])] ->
[String] -> [(String,String)] -> [(String,String)] -> CompileInfo ()
checkInferenceSuccess :: CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceSuccess CategoryMap SourcePos
tm [(String, [String])]
pa [String]
is [(String, String)]
ts [(String, String)]
gs = ([InferredTypeGuess]
-> CompileInfo [InferredTypeGuess] -> CompileInfo ())
-> CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceCommon [InferredTypeGuess]
-> CompileInfo [InferredTypeGuess] -> CompileInfo ()
forall a.
(Ord a, Show a) =>
[a] -> CompileInfo [a] -> CompileInfo ()
check CategoryMap SourcePos
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] -> CompileInfo [a] -> CompileInfo ()
check [a]
gs2 CompileInfo [a]
c
| CompileInfo [a] -> Bool
forall a. CompileInfo a -> Bool
isCompileError CompileInfo [a]
c = String -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> CompileInfo ()) -> String -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CompileMessage -> String
forall a. Show a => a -> String
show (CompileInfo [a] -> CompileMessage
forall a. CompileInfo a -> CompileMessage
getCompileWarnings CompileInfo [a]
c) String -> String -> String
forall a. [a] -> [a] -> [a]
++ CompileMessage -> String
forall a. Show a => a -> String
show (CompileInfo [a] -> CompileMessage
forall a. CompileInfo a -> CompileMessage
getCompileError CompileInfo [a]
c)
| Bool
otherwise = CompileInfo [a] -> [a]
forall a. CompileInfo a -> a
getCompileSuccess CompileInfo [a]
c [a] -> [a] -> CompileInfo ()
forall a. (Ord a, Show a) => [a] -> [a] -> CompileInfo ()
`containsExactly` [a]
gs2
checkInferenceFail :: CategoryMap SourcePos -> [(String, [String])] ->
[String] -> [(String,String)] -> CompileInfo ()
checkInferenceFail :: CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> CompileInfo ()
checkInferenceFail CategoryMap SourcePos
tm [(String, [String])]
pa [String]
is [(String, String)]
ts = ([InferredTypeGuess]
-> CompileInfo [InferredTypeGuess] -> CompileInfo ())
-> CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceCommon [InferredTypeGuess]
-> CompileInfo [InferredTypeGuess] -> CompileInfo ()
forall (m :: * -> *) p a.
CompileErrorM m =>
p -> CompileInfo a -> m ()
check CategoryMap SourcePos
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 -> CompileInfo a -> m ()
check p
_ CompileInfo a
c
| CompileInfo a -> Bool
forall a. CompileInfo a -> Bool
isCompileError CompileInfo a
c = () -> m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
| Bool
otherwise = String -> m ()
forall (m :: * -> *) a. CompileErrorM m => String -> m a
compileErrorM (String -> m ()) -> String -> m ()
forall a b. (a -> b) -> a -> b
$ String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": Expected failure\n"
checkInferenceCommon :: ([InferredTypeGuess] -> CompileInfo [InferredTypeGuess] -> CompileInfo ()) ->
CategoryMap SourcePos -> [(String,[String])] -> [String] ->
[(String,String)] -> [(String,String)] -> CompileInfo ()
checkInferenceCommon :: ([InferredTypeGuess]
-> CompileInfo [InferredTypeGuess] -> CompileInfo ())
-> CategoryMap SourcePos
-> [(String, [String])]
-> [String]
-> [(String, String)]
-> [(String, String)]
-> CompileInfo ()
checkInferenceCommon [InferredTypeGuess]
-> CompileInfo [InferredTypeGuess] -> CompileInfo ()
check CategoryMap SourcePos
tm [(String, [String])]
pa [String]
is [(String, String)]
ts [(String, String)]
gs = CompileInfo ()
checked CompileInfo () -> String -> CompileInfo ()
forall (m :: * -> *) a. CompileErrorM m => m a -> String -> m a
<!! String
context where
context :: String
context = String
"With params = " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, [String])] -> String
forall a. Show a => a -> String
show [(String, [String])]
pa String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
", pairs = " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [(String, String)] -> String
forall a. Show a => a -> String
show [(String, String)]
ts
checked :: CompileInfo ()
checked = do
let r :: CategoryResolver SourcePos
r = CategoryMap SourcePos -> CategoryResolver SourcePos
forall c. CategoryMap c -> CategoryResolver c
CategoryResolver CategoryMap SourcePos
tm
ParamFilters
pa2 <- [(String, [String])] -> CompileInfo ParamFilters
parseFilterMap [(String, [String])]
pa
Map ParamName GeneralInstance
ia2 <- ([(ParamName, GeneralInstance)] -> Map ParamName GeneralInstance)
-> CompileInfoT Identity [(ParamName, GeneralInstance)]
-> CompileInfoT 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 (CompileInfoT Identity [(ParamName, GeneralInstance)]
-> CompileInfoT Identity (Map ParamName GeneralInstance))
-> CompileInfoT Identity [(ParamName, GeneralInstance)]
-> CompileInfoT Identity (Map ParamName GeneralInstance)
forall a b. (a -> b) -> a -> b
$ (String -> CompileInfoT Identity (ParamName, GeneralInstance))
-> [String] -> CompileInfoT Identity [(ParamName, GeneralInstance)]
forall (m :: * -> *) a b.
CompileErrorM m =>
(a -> m b) -> [a] -> m [b]
mapErrorsM String -> CompileInfoT Identity (ParamName, GeneralInstance)
readInferred [String]
is
[PatternMatch ValueType]
ts2 <- ((String, String)
-> CompileInfoT Identity (PatternMatch ValueType))
-> [(String, String)]
-> CompileInfoT Identity [PatternMatch ValueType]
forall (m :: * -> *) a b.
CompileErrorM m =>
(a -> m b) -> [a] -> m [b]
mapErrorsM (Map ParamName GeneralInstance
-> Variance
-> (String, String)
-> CompileInfoT 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) -> CompileInfoT Identity InferredTypeGuess)
-> [(String, String)] -> CompileInfo [InferredTypeGuess]
forall (m :: * -> *) a b.
CompileErrorM m =>
(a -> m b) -> [a] -> m [b]
mapErrorsM (String, String) -> CompileInfoT 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 SourcePos
-> ParamFilters
-> Map ParamName GeneralInstance
-> [PatternMatch ValueType]
-> CompileInfoT Identity (MergeTree InferredTypeGuess)
forall (m :: * -> *) r.
(CompileErrorM m, TypeResolver r) =>
r
-> ParamFilters
-> Map ParamName GeneralInstance
-> [PatternMatch ValueType]
-> m (MergeTree InferredTypeGuess)
inferParamTypes CategoryResolver SourcePos
r ParamFilters
f Map ParamName GeneralInstance
ia2 [PatternMatch ValueType]
ts2
[InferredTypeGuess]
-> CompileInfo [InferredTypeGuess] -> CompileInfo ()
check [InferredTypeGuess]
gs' (CompileInfo [InferredTypeGuess] -> CompileInfo ())
-> CompileInfo [InferredTypeGuess] -> CompileInfo ()
forall a b. (a -> b) -> a -> b
$ CategoryResolver SourcePos
-> ParamFilters
-> ParamFilters
-> Map ParamName GeneralInstance
-> MergeTree InferredTypeGuess
-> CompileInfo [InferredTypeGuess]
forall (m :: * -> *) r.
(CompileErrorM m, TypeResolver r) =>
r
-> ParamFilters
-> ParamFilters
-> Map ParamName GeneralInstance
-> MergeTree InferredTypeGuess
-> m [InferredTypeGuess]
mergeInferredTypes CategoryResolver SourcePos
r ParamFilters
f ParamFilters
ff Map ParamName GeneralInstance
ia2 MergeTree InferredTypeGuess
gs2
readInferred :: String -> CompileInfoT Identity (ParamName, GeneralInstance)
readInferred String
p = do
ParamName
p' <- String -> String -> CompileInfo ParamName
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
p
(ParamName, GeneralInstance)
-> CompileInfoT Identity (ParamName, GeneralInstance)
forall (m :: * -> *) a. Monad m => a -> m a
return (ParamName
p',TypeInstanceOrParam -> GeneralInstance
forall a. (Eq a, Ord a) => a -> GeneralType a
singleType (TypeInstanceOrParam -> GeneralInstance)
-> TypeInstanceOrParam -> GeneralInstance
forall a b. (a -> b) -> a -> b
$ ParamName -> TypeInstanceOrParam
JustInferredType ParamName
p')
parseGuess :: (String, String) -> CompileInfoT Identity InferredTypeGuess
parseGuess (String
p,String
t) = do
ParamName
p' <- String -> String -> CompileInfo ParamName
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
p
GeneralInstance
t' <- String -> String -> CompileInfo GeneralInstance
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
t
InferredTypeGuess -> CompileInfoT Identity InferredTypeGuess
forall (m :: * -> *) a. Monad m => a -> m a
return (InferredTypeGuess -> CompileInfoT Identity InferredTypeGuess)
-> InferredTypeGuess -> CompileInfoT Identity InferredTypeGuess
forall a b. (a -> b) -> a -> b
$ ParamName -> GeneralInstance -> Variance -> InferredTypeGuess
InferredTypeGuess ParamName
p' GeneralInstance
t' Variance
Invariant
parsePair :: Map ParamName GeneralInstance
-> Variance
-> (String, String)
-> CompileInfoT Identity (PatternMatch ValueType)
parsePair Map ParamName GeneralInstance
im Variance
v (String
t1,String
t2) = do
ValueType
t1' <- String -> String -> CompileInfo ValueType
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
t1
ValueType
t2' <- String -> String -> CompileInfo ValueType
forall a. ParseFromSource a => String -> String -> CompileInfo a
readSingle String
"(string)" String
t2 CompileInfo ValueType
-> (ValueType -> CompileInfo ValueType) -> CompileInfo ValueType
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ParamName -> CompileInfo GeneralInstance)
-> ValueType -> CompileInfo ValueType
forall (m :: * -> *).
CompileErrorM m =>
(ParamName -> m GeneralInstance) -> ValueType -> m ValueType
uncheckedSubValueType (Map ParamName GeneralInstance
-> ParamName -> CompileInfo GeneralInstance
forall (m :: * -> *).
Monad m =>
Map ParamName GeneralInstance -> ParamName -> m GeneralInstance
weakLookup Map ParamName GeneralInstance
im)
PatternMatch ValueType
-> CompileInfoT 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