Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Types.TypeInstance
Documentation
data AnyTypeResolver Source #
Constructors
TypeResolver r => AnyTypeResolver r |
Instances
TypeResolver AnyTypeResolver Source # | |
Defined in Types.TypeInstance Methods trRefines :: (MergeableM m, CompileErrorM m) => AnyTypeResolver -> TypeInstance -> CategoryName -> m InstanceParams Source # trDefines :: (MergeableM m, CompileErrorM m) => AnyTypeResolver -> TypeInstance -> CategoryName -> m InstanceParams Source # trVariance :: (MergeableM m, CompileErrorM m) => AnyTypeResolver -> CategoryName -> m InstanceVariances Source # trTypeFilters :: (MergeableM m, CompileErrorM m) => AnyTypeResolver -> TypeInstance -> m InstanceFilters Source # trDefinesFilters :: (MergeableM m, CompileErrorM m) => AnyTypeResolver -> DefinesInstance -> m InstanceFilters Source # trConcrete :: (MergeableM m, CompileErrorM m) => AnyTypeResolver -> CategoryName -> m Bool Source # |
data CategoryName Source #
Constructors
CategoryName | |
BuiltinBool | |
BuiltinChar | |
BuiltinInt | |
BuiltinFloat | |
BuiltinString | |
BuiltinFormatted | |
CategoryNone |
Instances
Eq CategoryName Source # | |
Defined in Types.TypeInstance | |
Ord CategoryName Source # | |
Defined in Types.TypeInstance Methods compare :: CategoryName -> CategoryName -> Ordering # (<) :: CategoryName -> CategoryName -> Bool # (<=) :: CategoryName -> CategoryName -> Bool # (>) :: CategoryName -> CategoryName -> Bool # (>=) :: CategoryName -> CategoryName -> Bool # max :: CategoryName -> CategoryName -> CategoryName # min :: CategoryName -> CategoryName -> CategoryName # | |
Show CategoryName Source # | |
Defined in Types.TypeInstance Methods showsPrec :: Int -> CategoryName -> ShowS # show :: CategoryName -> String # showList :: [CategoryName] -> ShowS # | |
ParseFromSource CategoryName Source # | |
Defined in Parser.TypeInstance Methods |
data DefinesInstance Source #
Constructors
DefinesInstance | |
Fields |
Instances
Eq DefinesInstance Source # | |
Defined in Types.TypeInstance Methods (==) :: DefinesInstance -> DefinesInstance -> Bool # (/=) :: DefinesInstance -> DefinesInstance -> Bool # | |
Ord DefinesInstance Source # | |
Defined in Types.TypeInstance Methods compare :: DefinesInstance -> DefinesInstance -> Ordering # (<) :: DefinesInstance -> DefinesInstance -> Bool # (<=) :: DefinesInstance -> DefinesInstance -> Bool # (>) :: DefinesInstance -> DefinesInstance -> Bool # (>=) :: DefinesInstance -> DefinesInstance -> Bool # max :: DefinesInstance -> DefinesInstance -> DefinesInstance # min :: DefinesInstance -> DefinesInstance -> DefinesInstance # | |
Show DefinesInstance Source # | |
Defined in Types.TypeInstance Methods showsPrec :: Int -> DefinesInstance -> ShowS # show :: DefinesInstance -> String # showList :: [DefinesInstance] -> ShowS # | |
ParseFromSource DefinesInstance Source # | |
Defined in Parser.TypeInstance Methods |
data FilterDirection Source #
Constructors
FilterRequires | |
FilterAllows |
Instances
Eq FilterDirection Source # | |
Defined in Types.TypeInstance Methods (==) :: FilterDirection -> FilterDirection -> Bool # (/=) :: FilterDirection -> FilterDirection -> Bool # | |
Ord FilterDirection Source # | |
Defined in Types.TypeInstance Methods compare :: FilterDirection -> FilterDirection -> Ordering # (<) :: FilterDirection -> FilterDirection -> Bool # (<=) :: FilterDirection -> FilterDirection -> Bool # (>) :: FilterDirection -> FilterDirection -> Bool # (>=) :: FilterDirection -> FilterDirection -> Bool # max :: FilterDirection -> FilterDirection -> FilterDirection # min :: FilterDirection -> FilterDirection -> FilterDirection # |
data InferredTypeGuess Source #
Constructors
InferredTypeGuess | |
Fields |
Instances
Eq InferredTypeGuess Source # | |
Defined in Types.TypeInstance Methods (==) :: InferredTypeGuess -> InferredTypeGuess -> Bool # (/=) :: InferredTypeGuess -> InferredTypeGuess -> Bool # | |
Ord InferredTypeGuess Source # | |
Defined in Types.TypeInstance Methods compare :: InferredTypeGuess -> InferredTypeGuess -> Ordering # (<) :: InferredTypeGuess -> InferredTypeGuess -> Bool # (<=) :: InferredTypeGuess -> InferredTypeGuess -> Bool # (>) :: InferredTypeGuess -> InferredTypeGuess -> Bool # (>=) :: InferredTypeGuess -> InferredTypeGuess -> Bool # max :: InferredTypeGuess -> InferredTypeGuess -> InferredTypeGuess # min :: InferredTypeGuess -> InferredTypeGuess -> InferredTypeGuess # | |
Show InferredTypeGuess Source # | |
Defined in Types.TypeInstance Methods showsPrec :: Int -> InferredTypeGuess -> ShowS # show :: InferredTypeGuess -> String # showList :: [InferredTypeGuess] -> ShowS # |
type InstanceFilters = Positional [TypeFilter] Source #
type InstanceVariances = Positional Variance Source #
type ParamFilters = Map ParamName [TypeFilter] Source #
type ParamValues = Map ParamName GeneralInstance Source #
Instances
Eq ParamName Source # | |
Ord ParamName Source # | |
Show ParamName Source # | |
ParseFromSource ParamName Source # | |
Defined in Parser.TypeInstance Methods |
data StorageType Source #
Constructors
WeakValue | |
OptionalValue | |
RequiredValue |
Instances
Eq StorageType Source # | |
Defined in Types.TypeInstance | |
Ord StorageType Source # | |
Defined in Types.TypeInstance Methods compare :: StorageType -> StorageType -> Ordering # (<) :: StorageType -> StorageType -> Bool # (<=) :: StorageType -> StorageType -> Bool # (>) :: StorageType -> StorageType -> Bool # (>=) :: StorageType -> StorageType -> Bool # max :: StorageType -> StorageType -> StorageType # min :: StorageType -> StorageType -> StorageType # |
data TypeFilter Source #
Constructors
TypeFilter | |
Fields | |
DefinesFilter | |
Fields |
Instances
Eq TypeFilter Source # | |
Defined in Types.TypeInstance | |
Ord TypeFilter Source # | |
Defined in Types.TypeInstance Methods compare :: TypeFilter -> TypeFilter -> Ordering # (<) :: TypeFilter -> TypeFilter -> Bool # (<=) :: TypeFilter -> TypeFilter -> Bool # (>) :: TypeFilter -> TypeFilter -> Bool # (>=) :: TypeFilter -> TypeFilter -> Bool # max :: TypeFilter -> TypeFilter -> TypeFilter # min :: TypeFilter -> TypeFilter -> TypeFilter # | |
Show TypeFilter Source # | |
Defined in Types.TypeInstance Methods showsPrec :: Int -> TypeFilter -> ShowS # show :: TypeFilter -> String # showList :: [TypeFilter] -> ShowS # | |
ParseFromSource TypeFilter Source # | |
Defined in Parser.TypeInstance Methods |
data TypeInstance Source #
Constructors
TypeInstance | |
Fields |
Instances
Eq TypeInstance Source # | |
Defined in Types.TypeInstance | |
Ord TypeInstance Source # | |
Defined in Types.TypeInstance Methods compare :: TypeInstance -> TypeInstance -> Ordering # (<) :: TypeInstance -> TypeInstance -> Bool # (<=) :: TypeInstance -> TypeInstance -> Bool # (>) :: TypeInstance -> TypeInstance -> Bool # (>=) :: TypeInstance -> TypeInstance -> Bool # max :: TypeInstance -> TypeInstance -> TypeInstance # min :: TypeInstance -> TypeInstance -> TypeInstance # | |
Show TypeInstance Source # | |
Defined in Types.TypeInstance Methods showsPrec :: Int -> TypeInstance -> ShowS # show :: TypeInstance -> String # showList :: [TypeInstance] -> ShowS # | |
ParseFromSource TypeInstance Source # | |
Defined in Parser.TypeInstance Methods |
data TypeInstanceOrParam Source #
Constructors
JustTypeInstance | |
Fields | |
JustParamName | |
JustInferredType | |
Instances
class TypeResolver r where Source #
Methods
trRefines :: (MergeableM m, CompileErrorM m) => r -> TypeInstance -> CategoryName -> m InstanceParams Source #
trDefines :: (MergeableM m, CompileErrorM m) => r -> TypeInstance -> CategoryName -> m InstanceParams Source #
trVariance :: (MergeableM m, CompileErrorM m) => r -> CategoryName -> m InstanceVariances Source #
trTypeFilters :: (MergeableM m, CompileErrorM m) => r -> TypeInstance -> m InstanceFilters Source #
trDefinesFilters :: (MergeableM m, CompileErrorM m) => r -> DefinesInstance -> m InstanceFilters Source #
trConcrete :: (MergeableM m, CompileErrorM m) => r -> CategoryName -> m Bool Source #
Instances
Constructors
ValueType | |
Fields |
Instances
Eq ValueType Source # | |
Ord ValueType Source # | |
Show ValueType Source # | |
ParseFromSource ValueType Source # | |
Defined in Parser.TypeInstance Methods |
checkDefinesMatch :: (MergeableM m, CompileErrorM m, TypeResolver r) => r -> ParamFilters -> DefinesInstance -> DefinesInstance -> m () Source #
checkGeneralMatch :: (MergeableM m, CompileErrorM m, TypeResolver r) => r -> ParamFilters -> Variance -> GeneralInstance -> GeneralInstance -> m (MergeTree InferredTypeGuess) Source #
checkValueTypeMatch :: (MergeableM m, CompileErrorM m, TypeResolver r) => r -> ParamFilters -> ValueType -> ValueType -> m (MergeTree InferredTypeGuess) Source #
checkValueTypeMatch_ :: (MergeableM m, CompileErrorM m, TypeResolver r) => r -> ParamFilters -> ValueType -> ValueType -> m () Source #
getValueForParam :: CompileErrorM m => ParamValues -> ParamName -> m GeneralInstance Source #
isBuiltinCategory :: CategoryName -> Bool Source #
isDefinesFilter :: TypeFilter -> Bool Source #
isRequiresFilter :: TypeFilter -> Bool Source #
isWeakValue :: ValueType -> Bool Source #
noInferredTypes :: (MergeableM m, CompileErrorM m) => m (MergeTree InferredTypeGuess) -> m () Source #
requiredParam :: ParamName -> ValueType Source #
uncheckedSubFilter :: (MergeableM m, CompileErrorM m) => (ParamName -> m GeneralInstance) -> TypeFilter -> m TypeFilter Source #
uncheckedSubFilters :: (MergeableM m, CompileErrorM m) => (ParamName -> m GeneralInstance) -> ParamFilters -> m ParamFilters Source #
uncheckedSubInstance :: (MergeableM m, CompileErrorM m) => (ParamName -> m GeneralInstance) -> GeneralInstance -> m GeneralInstance Source #
uncheckedSubValueType :: (MergeableM m, CompileErrorM m) => (ParamName -> m GeneralInstance) -> ValueType -> m ValueType Source #
validateAssignment :: (MergeableM m, CompileErrorM m, TypeResolver r) => r -> ParamFilters -> GeneralInstance -> [TypeFilter] -> m () Source #
validateDefinesInstance :: (MergeableM m, CompileErrorM m, TypeResolver r) => r -> ParamFilters -> DefinesInstance -> m () Source #
validateDefinesVariance :: (MergeableM m, CompileErrorM m, TypeResolver r) => r -> ParamVariances -> Variance -> DefinesInstance -> m () Source #
validateGeneralInstance :: (MergeableM m, CompileErrorM m, TypeResolver r) => r -> ParamFilters -> GeneralInstance -> m () Source #
validateInstanceVariance :: (MergeableM m, CompileErrorM m, TypeResolver r) => r -> ParamVariances -> Variance -> GeneralInstance -> m () Source #
validateTypeFilter :: (MergeableM m, CompileErrorM m, TypeResolver r) => r -> ParamFilters -> TypeFilter -> m () Source #
validateTypeInstance :: (MergeableM m, CompileErrorM m, TypeResolver r) => r -> ParamFilters -> TypeInstance -> m () Source #