Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- checkTypeExp :: MonadTypeChecker m => TypeExp Name -> m (TypeExp VName, StructType, Liftedness)
- checkTypeDecl :: MonadTypeChecker m => [TypeParam] -> TypeDeclBase NoInfo Name -> m (TypeDeclBase Info VName, Liftedness)
- unifyTypesU :: (Monoid als, Eq als, ArrayDim dim) => (Uniqueness -> Uniqueness -> Maybe Uniqueness) -> TypeBase dim als -> TypeBase dim als -> Maybe (TypeBase dim als)
- subtypeOf :: ArrayDim dim => TypeBase dim as1 -> TypeBase dim as2 -> Bool
- subuniqueOf :: Uniqueness -> Uniqueness -> Bool
- checkForDuplicateNames :: MonadTypeChecker m => [UncheckedPattern] -> m ()
- checkTypeParams :: MonadTypeChecker m => [TypeParamBase Name] -> ([TypeParamBase VName] -> m a) -> m a
- typeExpUses :: TypeExp VName -> ([VName], [VName])
- checkShapeParamUses :: (MonadTypeChecker m, Located a) => (a -> ([VName], [VName])) -> [TypeParam] -> [a] -> m ()
- data TypeSub
- = TypeSub TypeBinding
- | DimSub (DimDecl VName)
- type TypeSubs = Map VName TypeSub
- substituteTypes :: TypeSubs -> StructType -> StructType
- substituteTypesInBoundV :: TypeSubs -> BoundV -> BoundV
- data Subst t
- class Substitutable a where
- applySubst :: (VName -> Maybe (Subst (TypeBase () ()))) -> a -> a
- substTypesAny :: (ArrayDim dim, Monoid as) => (VName -> Maybe (Subst (TypeBase dim as))) -> TypeBase dim as -> TypeBase dim as
Documentation
checkTypeExp :: MonadTypeChecker m => TypeExp Name -> m (TypeExp VName, StructType, Liftedness) Source #
checkTypeDecl :: MonadTypeChecker m => [TypeParam] -> TypeDeclBase NoInfo Name -> m (TypeDeclBase Info VName, Liftedness) Source #
unifyTypesU :: (Monoid als, Eq als, ArrayDim dim) => (Uniqueness -> Uniqueness -> Maybe Uniqueness) -> TypeBase dim als -> TypeBase dim als -> Maybe (TypeBase dim als) Source #
unifyTypes uf t2 t2
attempts to unify t1
and t2
. If
unification cannot happen, Nothing
is returned, otherwise a type
that combines the aliasing of t1
and t2
is returned.
Uniqueness is unified with uf
.
subtypeOf :: ArrayDim dim => TypeBase dim as1 -> TypeBase dim as2 -> Bool Source #
x `subtypeOf` y
is true if x
is a subtype of y
(or equal to
y
), meaning x
is valid whenever y
is.
subuniqueOf :: Uniqueness -> Uniqueness -> Bool Source #
x
is true if subuniqueOf
yx
is not less unique than y
.
checkForDuplicateNames :: MonadTypeChecker m => [UncheckedPattern] -> m () Source #
Check for duplication of names inside a pattern group. Produces a description of all names used in the pattern group.
checkTypeParams :: MonadTypeChecker m => [TypeParamBase Name] -> ([TypeParamBase VName] -> m a) -> m a Source #
typeExpUses :: TypeExp VName -> ([VName], [VName]) Source #
Return the shapes used in a given type expression in positive and negative position, respectively.
checkShapeParamUses :: (MonadTypeChecker m, Located a) => (a -> ([VName], [VName])) -> [TypeParam] -> [a] -> m () Source #
Ensure that every shape parameter is used in positive position at least once before being used in negative position.
substituteTypes :: TypeSubs -> StructType -> StructType Source #
A type substituion may be a substitution or a yet-unknown substitution (but which is certainly an overloaded primitive type!). The latter is used to remove aliases from types that are yet-unknown but that we know cannot carry aliases (see issue #682).
class Substitutable a where Source #
Class of types which allow for substitution of types with no annotations for type variable names.
Instances
Substitutable (TypeBase () ()) Source # | |
Defined in Language.Futhark.TypeChecker.Types | |
Substitutable (TypeBase () Aliasing) Source # | |
Substitutable (TypeBase (DimDecl VName) ()) Source # | |
Substitutable (TypeBase (DimDecl VName) Aliasing) Source # | |