Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Types.TypeCategory
Documentation
data AnyCategory c Source #
Constructors
ValueInterface | |
Fields
| |
InstanceInterface | |
Fields
| |
ValueConcrete | |
Fields
|
Instances
Show c => Show (AnyCategory c) Source # | |
Defined in Types.TypeCategory Methods showsPrec :: Int -> AnyCategory c -> ShowS # show :: AnyCategory c -> String # showList :: [AnyCategory c] -> ShowS # | |
ParseFromSource (AnyCategory SourcePos) Source # | |
Defined in Parser.TypeCategory Methods |
type CategoryMap c = Map CategoryName (AnyCategory c) Source #
newtype CategoryResolver c Source #
Constructors
CategoryResolver | |
Fields
|
Instances
Show c => TypeResolver (CategoryResolver c) Source # | |
Defined in Types.TypeCategory Methods trRefines :: (MergeableM m, CompileErrorM m) => CategoryResolver c -> TypeInstance -> CategoryName -> m InstanceParams Source # trDefines :: (MergeableM m, CompileErrorM m) => CategoryResolver c -> TypeInstance -> CategoryName -> m InstanceParams Source # trVariance :: (MergeableM m, CompileErrorM m) => CategoryResolver c -> CategoryName -> m InstanceVariances Source # trTypeFilters :: (MergeableM m, CompileErrorM m) => CategoryResolver c -> TypeInstance -> m InstanceFilters Source # trDefinesFilters :: (MergeableM m, CompileErrorM m) => CategoryResolver c -> DefinesInstance -> m InstanceFilters Source # trConcrete :: (MergeableM m, CompileErrorM m) => CategoryResolver c -> CategoryName -> m Bool Source # |
data FunctionName Source #
Instances
Eq FunctionName Source # | |
Defined in Types.TypeCategory | |
Ord FunctionName Source # | |
Defined in Types.TypeCategory Methods compare :: FunctionName -> FunctionName -> Ordering # (<) :: FunctionName -> FunctionName -> Bool # (<=) :: FunctionName -> FunctionName -> Bool # (>) :: FunctionName -> FunctionName -> Bool # (>=) :: FunctionName -> FunctionName -> Bool # max :: FunctionName -> FunctionName -> FunctionName # min :: FunctionName -> FunctionName -> FunctionName # | |
Show FunctionName Source # | |
Defined in Types.TypeCategory Methods showsPrec :: Int -> FunctionName -> ShowS # show :: FunctionName -> String # showList :: [FunctionName] -> ShowS # | |
ParseFromSource FunctionName Source # | |
Defined in Parser.TypeCategory Methods |
Constructors
StaticNamespace | |
NoNamespace | |
DynamicNamespace |
Instances
Eq Namespace Source # | |
Ord Namespace Source # | |
Show Namespace Source # | |
data ParamFilter c Source #
Constructors
ParamFilter | |
Fields
|
Instances
Show c => Show (ParamFilter c) Source # | |
Defined in Types.TypeCategory Methods showsPrec :: Int -> ParamFilter c -> ShowS # show :: ParamFilter c -> String # showList :: [ParamFilter c] -> ShowS # |
data PassedValue c Source #
Constructors
PassedValue | |
Instances
Show c => Show (PassedValue c) Source # | |
Defined in Types.TypeCategory Methods showsPrec :: Int -> PassedValue c -> ShowS # show :: PassedValue c -> String # showList :: [PassedValue c] -> ShowS # |
data ScopedFunction c Source #
Constructors
ScopedFunction | |
Fields
|
Instances
Show c => Show (ScopedFunction c) Source # | |
Defined in Types.TypeCategory Methods showsPrec :: Int -> ScopedFunction c -> ShowS # show :: ScopedFunction c -> String # showList :: [ScopedFunction c] -> ShowS # |
data SymbolScope Source #
Constructors
LocalScope | |
CategoryScope | |
TypeScope | |
ValueScope |
Instances
Eq SymbolScope Source # | |
Defined in Types.TypeCategory | |
Ord SymbolScope Source # | |
Defined in Types.TypeCategory Methods compare :: SymbolScope -> SymbolScope -> Ordering # (<) :: SymbolScope -> SymbolScope -> Bool # (<=) :: SymbolScope -> SymbolScope -> Bool # (>) :: SymbolScope -> SymbolScope -> Bool # (>=) :: SymbolScope -> SymbolScope -> Bool # max :: SymbolScope -> SymbolScope -> SymbolScope # min :: SymbolScope -> SymbolScope -> SymbolScope # | |
Show SymbolScope Source # | |
Defined in Types.TypeCategory Methods showsPrec :: Int -> SymbolScope -> ShowS # show :: SymbolScope -> String # showList :: [SymbolScope] -> ShowS # |
data ValueDefine c Source #
Constructors
ValueDefine | |
Fields
|
Instances
Show c => Show (ValueDefine c) Source # | |
Defined in Types.TypeCategory Methods showsPrec :: Int -> ValueDefine c -> ShowS # show :: ValueDefine c -> String # showList :: [ValueDefine c] -> ShowS # |
data ValueParam c Source #
Constructors
ValueParam | |
Fields
|
Instances
Show c => Show (ValueParam c) Source # | |
Defined in Types.TypeCategory Methods showsPrec :: Int -> ValueParam c -> ShowS # show :: ValueParam c -> String # showList :: [ValueParam c] -> ShowS # |
data ValueRefine c Source #
Constructors
ValueRefine | |
Fields
|
Instances
Show c => Show (ValueRefine c) Source # | |
Defined in Types.TypeCategory Methods showsPrec :: Int -> ValueRefine c -> ShowS # show :: ValueRefine c -> String # showList :: [ValueRefine c] -> ShowS # |
checkCategoryInstances :: (Show c, MergeableM m, CompileErrorM m) => CategoryMap c -> [AnyCategory c] -> m () Source #
checkConnectedTypes :: (Show c, MergeableM m, CompileErrorM m) => CategoryMap c -> [AnyCategory c] -> m () Source #
checkConnectionCycles :: (Show c, MergeableM m, CompileErrorM m) => CategoryMap c -> [AnyCategory c] -> m () Source #
checkParamVariances :: (Show c, MergeableM m, CompileErrorM m) => CategoryMap c -> [AnyCategory c] -> m () Source #
declareAllTypes :: (Show c, CompileErrorM m) => CategoryMap c -> [AnyCategory c] -> m (CategoryMap c) Source #
flattenAllConnections :: (Show c, MergeableM m, CompileErrorM m) => CategoryMap c -> [AnyCategory c] -> m [AnyCategory c] Source #
formatFullContext :: Show a => [a] -> String Source #
formatFullContextBrace :: Show a => [a] -> String Source #
getCategory :: (Show c, CompileErrorM m) => CategoryMap c -> ([c], CategoryName) -> m ([c], AnyCategory c) Source #
getCategoryContext :: AnyCategory c -> [c] Source #
getCategoryDefines :: AnyCategory c -> [ValueDefine c] Source #
getCategoryDeps :: AnyCategory c -> Set CategoryName Source #
getCategoryFilters :: AnyCategory c -> [ParamFilter c] Source #
getCategoryFunctions :: AnyCategory c -> [ScopedFunction c] Source #
getCategoryName :: AnyCategory c -> CategoryName Source #
getCategoryNamespace :: AnyCategory c -> Namespace Source #
getCategoryParamMap :: AnyCategory c -> ParamValues Source #
getCategoryParams :: AnyCategory c -> [ValueParam c] Source #
getCategoryRefines :: AnyCategory c -> [ValueRefine c] Source #
getConcreteCategory :: (Show c, CompileErrorM m) => CategoryMap c -> ([c], CategoryName) -> m ([c], AnyCategory c) Source #
getFilterMap :: [ValueParam c] -> [ParamFilter c] -> ParamFilters Source #
getInstanceCategory :: (Show c, CompileErrorM m) => CategoryMap c -> ([c], CategoryName) -> m ([c], AnyCategory c) Source #
getValueCategory :: (Show c, CompileErrorM m) => CategoryMap c -> ([c], CategoryName) -> m ([c], AnyCategory c) Source #
includeNewTypes :: (Show c, MergeableM m, CompileErrorM m) => CategoryMap c -> [AnyCategory c] -> m (CategoryMap c) Source #
inferParamTypes :: (MergeableM m, CompileErrorM m, TypeResolver r) => r -> ParamFilters -> ParamFilters -> ParamValues -> [(ValueType, ValueType)] -> m ParamValues Source #
isInstanceInterface :: AnyCategory c -> Bool Source #
isDynamicNamespace :: Namespace -> Bool Source #
isNoNamespace :: Namespace -> Bool Source #
isStaticNamespace :: Namespace -> Bool Source #
isValueConcrete :: AnyCategory c -> Bool Source #
isValueInterface :: AnyCategory c -> Bool Source #
mergeDefines :: (MergeableM m, CompileErrorM m, TypeResolver r) => r -> ParamFilters -> [ValueDefine c] -> m [ValueDefine c] Source #
mergeFunctions :: (Show c, MergeableM m, CompileErrorM m, TypeResolver r) => r -> CategoryMap c -> ParamValues -> ParamFilters -> [ValueRefine c] -> [ValueDefine c] -> [ScopedFunction c] -> m [ScopedFunction c] Source #
mergeInferredTypes :: (MergeableM m, CompileErrorM m, TypeResolver r) => r -> ParamFilters -> MergeTree InferredTypeGuess -> m [InferredTypeGuess] Source #
mergeRefines :: (MergeableM m, CompileErrorM m, TypeResolver r) => r -> ParamFilters -> [ValueRefine c] -> m [ValueRefine c] Source #
noDuplicateDefines :: (Show c, MergeableM m, CompileErrorM m) => [c] -> CategoryName -> [ValueDefine c] -> m () Source #
noDuplicateRefines :: (Show c, MergeableM m, CompileErrorM m) => [c] -> CategoryName -> [ValueRefine c] -> m () Source #
parsedToFunctionType :: (Show c, MergeableM m, CompileErrorM m) => ScopedFunction c -> m FunctionType Source #
partitionByScope :: (a -> SymbolScope) -> [a] -> ([a], [a], [a]) Source #
setCategoryNamespace :: Namespace -> AnyCategory c -> AnyCategory c Source #
topoSortCategories :: (Show c, MergeableM m, CompileErrorM m) => CategoryMap c -> [AnyCategory c] -> m [AnyCategory c] Source #
uncheckedSubFunction :: (Show c, MergeableM m, CompileErrorM m) => ParamValues -> ScopedFunction c -> m (ScopedFunction c) Source #
validateCategoryFunction :: (Show c, MergeableM m, CompileErrorM m, TypeResolver r) => r -> AnyCategory c -> ScopedFunction c -> m () Source #