Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- findDataConstructor :: DataConstructorName -> TypeConstructorMapping -> Maybe (TypeConstructorDef, DataConstructorDef)
- atomTypeForDataConstructorDefArg :: DataConstructorDefArg -> AtomType -> TypeConstructorMapping -> Either RelationalError AtomType
- atomTypeForDataConstructor :: TypeConstructorMapping -> DataConstructorName -> [AtomType] -> Either RelationalError AtomType
- resolveDataConstructorTypeVars :: DataConstructorDef -> [AtomType] -> TypeConstructorMapping -> Either RelationalError TypeVarMap
- resolveDataConstructorArgTypeVars :: DataConstructorDefArg -> AtomType -> TypeConstructorMapping -> Either RelationalError TypeVarMap
- resolveTypeConstructorTypeVars :: TypeConstructor -> AtomType -> TypeConstructorMapping -> Either RelationalError TypeVarMap
- resolveAttributeExprTypeVars :: AttributeExprBase a -> AtomType -> TypeConstructorMapping -> Either RelationalError TypeVarMap
- validateTypeConstructorDef :: TypeConstructorDef -> [DataConstructorDef] -> TypeConstructorMapping -> Either RelationalError ()
- validateDataConstructorDef :: DataConstructorDef -> TypeConstructorDef -> TypeConstructorMapping -> Either RelationalError ()
- validateDataConstructorDefArg :: DataConstructorDefArg -> TypeConstructorDef -> TypeConstructorMapping -> Either RelationalError ()
- atomTypeForTypeConstructor :: TypeConstructor -> TypeConstructorMapping -> TypeVarMap -> Either RelationalError AtomType
- atomTypeForTypeConstructorValidate :: Bool -> TypeConstructor -> TypeConstructorMapping -> TypeVarMap -> Either RelationalError AtomType
- atomTypeForAttributeExpr :: AttributeExprBase a -> TypeConstructorMapping -> TypeVarMap -> Either RelationalError AtomType
- isValidAtomTypeForTypeConstructor :: AtomType -> TypeConstructor -> TypeConstructorMapping -> Either RelationalError ()
- findTypeConstructor :: TypeConstructorName -> TypeConstructorMapping -> Maybe (TypeConstructorDef, [DataConstructorDef])
- resolveAttributes :: Attribute -> Attribute -> Either RelationalError Attribute
- resolveAtomType :: AtomType -> AtomType -> Either RelationalError AtomType
- resolveAtomTypesInTypeVarMap :: TypeVarMap -> TypeVarMap -> Either RelationalError TypeVarMap
- resolveTypeInAtom :: AtomType -> Atom -> TypeConstructorMapping -> Either RelationalError Atom
- resolveTypesInTuple :: Attributes -> TypeConstructorMapping -> RelationTuple -> Either RelationalError RelationTuple
- validateAtomType :: AtomType -> TypeConstructorMapping -> Either RelationalError ()
- validateAttributes :: TypeConstructorMapping -> Attributes -> Either RelationalError ()
- validateTypeVarMap :: TypeVarMap -> TypeConstructorMapping -> Either RelationalError ()
- validateTuple :: RelationTuple -> TypeConstructorMapping -> Either RelationalError ()
- validateAtom :: Atom -> TypeConstructorMapping -> Either RelationalError ()
- atomTypeVerify :: AtomType -> AtomType -> Either RelationalError AtomType
- typeVarMapsVerify :: TypeVarMap -> TypeVarMap -> Bool
- prettyAtomType :: AtomType -> Text
- prettyAttribute :: Attribute -> Text
- resolveTypeVariables :: [AtomType] -> [AtomType] -> Either RelationalError TypeVarMap
- resolveTypeVariable :: AtomType -> AtomType -> TypeVarMap
- resolveFunctionReturnValue :: FunctionName -> TypeVarMap -> AtomType -> Either RelationalError AtomType
- resolvedAtomTypesForDataConstructorDefArgs :: TypeConstructorMapping -> TypeVarMap -> DataConstructorDef -> Either RelationalError [AtomType]
- resolvedAtomTypeForDataConstructorDefArg :: TypeConstructorMapping -> TypeVarMap -> DataConstructorDefArg -> Either RelationalError AtomType
- isResolvedType :: AtomType -> Bool
- isResolvedAttributes :: Attributes -> Bool
- isResolvedAttribute :: Attribute -> Bool
- anyRelationAtomType :: AtomType
Documentation
findDataConstructor :: DataConstructorName -> TypeConstructorMapping -> Maybe (TypeConstructorDef, DataConstructorDef) Source #
atomTypeForDataConstructorDefArg :: DataConstructorDefArg -> AtomType -> TypeConstructorMapping -> Either RelationalError AtomType Source #
atomTypeForDataConstructor :: TypeConstructorMapping -> DataConstructorName -> [AtomType] -> Either RelationalError AtomType Source #
Used to determine if the atom arguments can be used with the data constructor. | This is the entry point for type-checking from RelationalExpression.hs
resolveDataConstructorTypeVars :: DataConstructorDef -> [AtomType] -> TypeConstructorMapping -> Either RelationalError TypeVarMap Source #
Walks the data and type constructors to extract the type variable map.
resolveDataConstructorArgTypeVars :: DataConstructorDefArg -> AtomType -> TypeConstructorMapping -> Either RelationalError TypeVarMap Source #
Attempt to match the data constructor argument to a type constructor type variable.
resolveTypeConstructorTypeVars :: TypeConstructor -> AtomType -> TypeConstructorMapping -> Either RelationalError TypeVarMap Source #
resolveAttributeExprTypeVars :: AttributeExprBase a -> AtomType -> TypeConstructorMapping -> Either RelationalError TypeVarMap Source #
validateTypeConstructorDef :: TypeConstructorDef -> [DataConstructorDef] -> TypeConstructorMapping -> Either RelationalError () Source #
validateDataConstructorDef :: DataConstructorDef -> TypeConstructorDef -> TypeConstructorMapping -> Either RelationalError () Source #
validateDataConstructorDefArg :: DataConstructorDefArg -> TypeConstructorDef -> TypeConstructorMapping -> Either RelationalError () Source #
atomTypeForTypeConstructor :: TypeConstructor -> TypeConstructorMapping -> TypeVarMap -> Either RelationalError AtomType Source #
atomTypeForTypeConstructorValidate :: Bool -> TypeConstructor -> TypeConstructorMapping -> TypeVarMap -> Either RelationalError AtomType Source #
Create an atom type iff all type variables are provided. Either Int Text -> ConstructedAtomType Either {Int , Text}
atomTypeForAttributeExpr :: AttributeExprBase a -> TypeConstructorMapping -> TypeVarMap -> Either RelationalError AtomType Source #
isValidAtomTypeForTypeConstructor :: AtomType -> TypeConstructor -> TypeConstructorMapping -> Either RelationalError () Source #
findTypeConstructor :: TypeConstructorName -> TypeConstructorMapping -> Maybe (TypeConstructorDef, [DataConstructorDef]) Source #
resolveAtomTypesInTypeVarMap :: TypeVarMap -> TypeVarMap -> Either RelationalError TypeVarMap Source #
resolveTypeInAtom :: AtomType -> Atom -> TypeConstructorMapping -> Either RelationalError Atom Source #
See notes at resolveTypesInTuple
. The typeFromRelation must not include any wildcards.
resolveTypesInTuple :: Attributes -> TypeConstructorMapping -> RelationTuple -> Either RelationalError RelationTuple Source #
When creating a tuple, the data constructor may not complete the type constructor arguments, so the wildcard "TypeVar x" fills in the type constructor's argument. The tuple type must be resolved before it can be part of a relation, however. Example: Nothing does not specify the the argument in "Maybe a", so allow delayed resolution in the tuple before it is added to the relation. Note that this resolution could cause a type error. Hardly a Hindley-Milner system.
validateAtomType :: AtomType -> TypeConstructorMapping -> Either RelationalError () Source #
Validate that the type is provided with complete type variables for type constructors.
validateAtom :: Atom -> TypeConstructorMapping -> Either RelationalError () Source #
atomTypeVerify :: AtomType -> AtomType -> Either RelationalError AtomType Source #
Determine if two types are equal or compatible (including special handling for TypeVar x).
typeVarMapsVerify :: TypeVarMap -> TypeVarMap -> Bool Source #
Determine if two typeVars are logically compatible.
prettyAtomType :: AtomType -> Text Source #
prettyAttribute :: Attribute -> Text Source #
resolveTypeVariables :: [AtomType] -> [AtomType] -> Either RelationalError TypeVarMap Source #
resolveTypeVariable :: AtomType -> AtomType -> TypeVarMap Source #
resolveFunctionReturnValue :: FunctionName -> TypeVarMap -> AtomType -> Either RelationalError AtomType Source #
resolvedAtomTypesForDataConstructorDefArgs :: TypeConstructorMapping -> TypeVarMap -> DataConstructorDef -> Either RelationalError [AtomType] Source #
resolvedAtomTypeForDataConstructorDefArg :: TypeConstructorMapping -> TypeVarMap -> DataConstructorDefArg -> Either RelationalError AtomType Source #
isResolvedType :: AtomType -> Bool Source #
isResolvedAttribute :: Attribute -> Bool Source #