Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Documentation
data AnyTypeResolver Source #
forall r.TypeResolver r => AnyTypeResolver r |
Instances
TypeResolver AnyTypeResolver Source # | |
Defined in Types.TypeInstance trRefines :: CollectErrorsM m => AnyTypeResolver -> TypeInstance -> CategoryName -> m InstanceParams Source # trDefines :: CollectErrorsM m => AnyTypeResolver -> TypeInstance -> CategoryName -> m InstanceParams Source # trVariance :: CollectErrorsM m => AnyTypeResolver -> CategoryName -> m InstanceVariances Source # trTypeFilters :: CollectErrorsM m => AnyTypeResolver -> TypeInstance -> m InstanceFilters Source # trDefinesFilters :: CollectErrorsM m => AnyTypeResolver -> DefinesInstance -> m InstanceFilters Source # trConcrete :: CollectErrorsM m => AnyTypeResolver -> CategoryName -> m Bool Source # trImmutable :: CollectErrorsM m => AnyTypeResolver -> CategoryName -> m Bool Source # |
data CategoryName Source #
CategoryName | |
BuiltinBool | |
BuiltinChar | |
BuiltinCharBuffer | |
BuiltinInt | |
BuiltinFloat | |
BuiltinString | |
BuiltinPointer | |
BuiltinIdentifier | |
BuiltinFormatted | |
BuiltinOrder | |
BuiltinTestcase | |
CategoryNone |
Instances
data DefinesInstance Source #
Instances
Show DefinesInstance Source # | |
Defined in Types.TypeInstance showsPrec :: Int -> DefinesInstance -> ShowS # show :: DefinesInstance -> String # showList :: [DefinesInstance] -> ShowS # | |
Eq DefinesInstance Source # | |
Defined in Types.TypeInstance (==) :: DefinesInstance -> DefinesInstance -> Bool # (/=) :: DefinesInstance -> DefinesInstance -> Bool # | |
Ord DefinesInstance Source # | |
Defined in Types.TypeInstance compare :: DefinesInstance -> DefinesInstance -> Ordering # (<) :: DefinesInstance -> DefinesInstance -> Bool # (<=) :: DefinesInstance -> DefinesInstance -> Bool # (>) :: DefinesInstance -> DefinesInstance -> Bool # (>=) :: DefinesInstance -> DefinesInstance -> Bool # max :: DefinesInstance -> DefinesInstance -> DefinesInstance # min :: DefinesInstance -> DefinesInstance -> DefinesInstance # | |
ParseFromSource DefinesInstance Source # | |
Defined in Parser.TypeInstance |
data FilterDirection Source #
Instances
Eq FilterDirection Source # | |
Defined in Types.TypeInstance (==) :: FilterDirection -> FilterDirection -> Bool # (/=) :: FilterDirection -> FilterDirection -> Bool # | |
Ord FilterDirection Source # | |
Defined in Types.TypeInstance 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 #
Instances
Show InferredTypeGuess Source # | |
Defined in Types.TypeInstance showsPrec :: Int -> InferredTypeGuess -> ShowS # show :: InferredTypeGuess -> String # showList :: [InferredTypeGuess] -> ShowS # | |
Eq InferredTypeGuess Source # | |
Defined in Types.TypeInstance (==) :: InferredTypeGuess -> InferredTypeGuess -> Bool # (/=) :: InferredTypeGuess -> InferredTypeGuess -> Bool # | |
Ord InferredTypeGuess Source # | |
Defined in Types.TypeInstance compare :: InferredTypeGuess -> InferredTypeGuess -> Ordering # (<) :: InferredTypeGuess -> InferredTypeGuess -> Bool # (<=) :: InferredTypeGuess -> InferredTypeGuess -> Bool # (>) :: InferredTypeGuess -> InferredTypeGuess -> Bool # (>=) :: InferredTypeGuess -> InferredTypeGuess -> Bool # max :: InferredTypeGuess -> InferredTypeGuess -> InferredTypeGuess # min :: InferredTypeGuess -> InferredTypeGuess -> InferredTypeGuess # |
type InstanceFilters = Positional [TypeFilter] Source #
type InstanceVariances = Positional Variance Source #
type ParamFilters = Map ParamName [TypeFilter] Source #
type ParamValues = Map ParamName GeneralInstance Source #
data StorageType Source #
Instances
Eq StorageType Source # | |
Defined in Types.TypeInstance (==) :: StorageType -> StorageType -> Bool # (/=) :: StorageType -> StorageType -> Bool # | |
Ord StorageType Source # | |
Defined in Types.TypeInstance 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 #
Instances
Show TypeFilter Source # | |
Defined in Types.TypeInstance showsPrec :: Int -> TypeFilter -> ShowS # show :: TypeFilter -> String # showList :: [TypeFilter] -> ShowS # | |
Eq TypeFilter Source # | |
Defined in Types.TypeInstance (==) :: TypeFilter -> TypeFilter -> Bool # (/=) :: TypeFilter -> TypeFilter -> Bool # | |
Ord TypeFilter Source # | |
Defined in Types.TypeInstance compare :: TypeFilter -> TypeFilter -> Ordering # (<) :: TypeFilter -> TypeFilter -> Bool # (<=) :: TypeFilter -> TypeFilter -> Bool # (>) :: TypeFilter -> TypeFilter -> Bool # (>=) :: TypeFilter -> TypeFilter -> Bool # max :: TypeFilter -> TypeFilter -> TypeFilter # min :: TypeFilter -> TypeFilter -> TypeFilter # | |
ParseFromSource TypeFilter Source # | |
Defined in Parser.TypeInstance |
data TypeInstance Source #
Instances
Show TypeInstance Source # | |
Defined in Types.TypeInstance showsPrec :: Int -> TypeInstance -> ShowS # show :: TypeInstance -> String # showList :: [TypeInstance] -> ShowS # | |
Eq TypeInstance Source # | |
Defined in Types.TypeInstance (==) :: TypeInstance -> TypeInstance -> Bool # (/=) :: TypeInstance -> TypeInstance -> Bool # | |
Ord TypeInstance Source # | |
Defined in Types.TypeInstance compare :: TypeInstance -> TypeInstance -> Ordering # (<) :: TypeInstance -> TypeInstance -> Bool # (<=) :: TypeInstance -> TypeInstance -> Bool # (>) :: TypeInstance -> TypeInstance -> Bool # (>=) :: TypeInstance -> TypeInstance -> Bool # max :: TypeInstance -> TypeInstance -> TypeInstance # min :: TypeInstance -> TypeInstance -> TypeInstance # | |
ParseFromSource TypeInstance Source # | |
Defined in Parser.TypeInstance |
data TypeInstanceOrParam Source #
Instances
class TypeResolver r where Source #
trRefines :: CollectErrorsM m => r -> TypeInstance -> CategoryName -> m InstanceParams Source #
trDefines :: CollectErrorsM m => r -> TypeInstance -> CategoryName -> m InstanceParams Source #
trVariance :: CollectErrorsM m => r -> CategoryName -> m InstanceVariances Source #
trTypeFilters :: CollectErrorsM m => r -> TypeInstance -> m InstanceFilters Source #
trDefinesFilters :: CollectErrorsM m => r -> DefinesInstance -> m InstanceFilters Source #
trConcrete :: CollectErrorsM m => r -> CategoryName -> m Bool Source #
trImmutable :: CollectErrorsM m => r -> CategoryName -> m Bool Source #
Instances
checkDefinesMatch :: (CollectErrorsM m, TypeResolver r) => r -> ParamFilters -> DefinesInstance -> DefinesInstance -> m (MergeTree InferredTypeGuess) Source #
checkGeneralMatch :: (CollectErrorsM m, TypeResolver r) => r -> ParamFilters -> Variance -> GeneralInstance -> GeneralInstance -> m (MergeTree InferredTypeGuess) Source #
checkValueAssignment :: (CollectErrorsM m, TypeResolver r) => r -> ParamFilters -> ValueType -> ValueType -> m () Source #
checkValueTypeImmutable :: (CollectErrorsM m, TypeResolver r) => r -> ParamFilters -> ValueType -> m () Source #
checkValueTypeMatch :: (CollectErrorsM m, TypeResolver r) => r -> ParamFilters -> Variance -> ValueType -> ValueType -> m (MergeTree InferredTypeGuess) Source #
dedupGeneralInstance :: (CollectErrorsM m, TypeResolver r) => r -> ParamFilters -> GeneralInstance -> m GeneralInstance Source #
filterLookup :: ErrorContextM m => ParamFilters -> ParamName -> m [TypeFilter] Source #
getValueForParam :: ErrorContextM m => ParamValues -> ParamName -> m GeneralInstance Source #
isDefinesFilter :: TypeFilter -> Bool Source #
isOptionalValue :: ValueType -> Bool Source #
isRequiresFilter :: TypeFilter -> Bool Source #
isWeakValue :: ValueType -> Bool Source #
mapTypeGuesses :: MergeTree InferredTypeGuess -> Map ParamName (MergeTree InferredTypeGuess) Source #
noInferredTypes :: CollectErrorsM m => m (MergeTree InferredTypeGuess) -> m () Source #
replaceSelfFilter :: CollectErrorsM m => GeneralInstance -> TypeFilter -> m TypeFilter Source #
replaceSelfInstance :: CollectErrorsM m => GeneralInstance -> GeneralInstance -> m GeneralInstance Source #
replaceSelfSingle :: CollectErrorsM m => GeneralInstance -> TypeInstance -> m TypeInstance Source #
replaceSelfValueType :: CollectErrorsM m => GeneralInstance -> ValueType -> m ValueType Source #
requiredParam :: ParamName -> ValueType Source #
reverseSelfInstance :: CollectErrorsM m => TypeInstance -> GeneralInstance -> m GeneralInstance Source #
uncheckedSubFilter :: CollectErrorsM m => (ParamName -> m GeneralInstance) -> TypeFilter -> m TypeFilter Source #
uncheckedSubFilters :: CollectErrorsM m => (ParamName -> m GeneralInstance) -> ParamFilters -> m ParamFilters Source #
uncheckedSubInstance :: CollectErrorsM m => (ParamName -> m GeneralInstance) -> GeneralInstance -> m GeneralInstance Source #
uncheckedSubSingle :: CollectErrorsM m => (ParamName -> m GeneralInstance) -> TypeInstance -> m TypeInstance Source #
uncheckedSubValueType :: CollectErrorsM m => (ParamName -> m GeneralInstance) -> ValueType -> m ValueType Source #
validateAssignment :: (CollectErrorsM m, TypeResolver r) => r -> ParamFilters -> GeneralInstance -> [TypeFilter] -> m () Source #
validateDefinesInstance :: (CollectErrorsM m, TypeResolver r) => r -> Set ParamName -> DefinesInstance -> m () Source #
validateDefinesVariance :: (CollectErrorsM m, TypeResolver r) => r -> ParamVariances -> Variance -> DefinesInstance -> m () Source #
validateGeneralInstance :: (CollectErrorsM m, TypeResolver r) => r -> Set ParamName -> GeneralInstance -> m () Source #
validateGeneralInstanceForCall :: (CollectErrorsM m, TypeResolver r) => r -> ParamFilters -> GeneralInstance -> m () Source #
validateInstanceVariance :: (CollectErrorsM m, TypeResolver r) => r -> ParamVariances -> Variance -> GeneralInstance -> m () Source #
validateTypeInstance :: (CollectErrorsM m, TypeResolver r) => r -> Set ParamName -> TypeInstance -> m () Source #
validateTypeInstanceForCall :: (CollectErrorsM m, TypeResolver r) => r -> ParamFilters -> TypeInstance -> m () Source #
validateTypeFilter :: (CollectErrorsM m, TypeResolver r) => r -> Set ParamName -> TypeFilter -> m () Source #