Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Constraint
- = NoConstraint (Maybe Liftedness) SrcLoc
- | ParamType Liftedness SrcLoc
- | Constraint (TypeBase () ()) SrcLoc
- | Overloaded [PrimType] SrcLoc
- | HasFields (Map Name (TypeBase () ())) SrcLoc
- | Equality SrcLoc
- | HasConstrs [Name] SrcLoc
- type Constraints = Map VName Constraint
- lookupSubst :: VName -> Constraints -> Maybe (Subst (TypeBase () ()))
- class (MonadBreadCrumbs m, MonadError TypeError m) => MonadUnify m where
- getConstraints :: m Constraints
- putConstraints :: Constraints -> m ()
- modifyConstraints :: (Constraints -> Constraints) -> m ()
- newTypeVar :: Monoid als => SrcLoc -> String -> m (TypeBase dim als)
- data BreadCrumb
- = MatchingTypes (TypeBase () ()) (TypeBase () ())
- | MatchingFields Name
- typeError :: (MonadError TypeError m, MonadBreadCrumbs m) => SrcLoc -> String -> m a
- mkTypeVarName :: String -> Int -> Name
- zeroOrderType :: (MonadUnify m, Pretty (ShapeDecl dim), Monoid as) => SrcLoc -> String -> TypeBase dim as -> m ()
- mustHaveConstr :: MonadUnify m => SrcLoc -> Name -> TypeBase dim as -> m ()
- mustHaveField :: (MonadUnify m, Monoid as) => SrcLoc -> Name -> TypeBase dim as -> m (TypeBase dim as)
- mustBeOneOf :: MonadUnify m => [PrimType] -> SrcLoc -> TypeBase () () -> m ()
- equalityType :: (MonadUnify m, Pretty (ShapeDecl dim), Monoid as) => SrcLoc -> TypeBase dim as -> m ()
- normaliseType :: (Substitutable a, MonadUnify m) => a -> m a
- unify :: MonadUnify m => SrcLoc -> TypeBase () () -> TypeBase () () -> m ()
- doUnification :: SrcLoc -> [TypeParam] -> TypeBase () () -> TypeBase () () -> Either TypeError (TypeBase () ())
Documentation
data Constraint Source #
NoConstraint (Maybe Liftedness) SrcLoc | |
ParamType Liftedness SrcLoc | |
Constraint (TypeBase () ()) SrcLoc | |
Overloaded [PrimType] SrcLoc | |
HasFields (Map Name (TypeBase () ())) SrcLoc | |
Equality SrcLoc | |
HasConstrs [Name] SrcLoc |
Instances
Show Constraint Source # | |
Defined in Language.Futhark.TypeChecker.Unify showsPrec :: Int -> Constraint -> ShowS # show :: Constraint -> String # showList :: [Constraint] -> ShowS # | |
Located Constraint Source # | |
Defined in Language.Futhark.TypeChecker.Unify locOf :: Constraint -> Loc # locOfList :: [Constraint] -> Loc # |
type Constraints = Map VName Constraint Source #
Mapping from fresh type variables, instantiated from the type schemes of polymorphic functions, to (possibly) specific types as determined on application and the location of that application, or a partial constraint on their type.
lookupSubst :: VName -> Constraints -> Maybe (Subst (TypeBase () ())) Source #
class (MonadBreadCrumbs m, MonadError TypeError m) => MonadUnify m where Source #
getConstraints :: m Constraints Source #
putConstraints :: Constraints -> m () Source #
modifyConstraints :: (Constraints -> Constraints) -> m () Source #
newTypeVar :: Monoid als => SrcLoc -> String -> m (TypeBase dim als) Source #
data BreadCrumb Source #
A piece of information that describes what process the type checker currently performing. This is used to give better error messages.
MatchingTypes (TypeBase () ()) (TypeBase () ()) | |
MatchingFields Name |
Instances
Show BreadCrumb Source # | |
Defined in Language.Futhark.TypeChecker.Monad showsPrec :: Int -> BreadCrumb -> ShowS # show :: BreadCrumb -> String # showList :: [BreadCrumb] -> ShowS # |
typeError :: (MonadError TypeError m, MonadBreadCrumbs m) => SrcLoc -> String -> m a Source #
mkTypeVarName :: String -> Int -> Name Source #
Construct a the name of a new type variable given a base description and a tag number (note that this is distinct from actually constructing a VName; the tag here is intended for human consumption but the machine does not care).
zeroOrderType :: (MonadUnify m, Pretty (ShapeDecl dim), Monoid as) => SrcLoc -> String -> TypeBase dim as -> m () Source #
mustHaveConstr :: MonadUnify m => SrcLoc -> Name -> TypeBase dim as -> m () Source #
mustHaveField :: (MonadUnify m, Monoid as) => SrcLoc -> Name -> TypeBase dim as -> m (TypeBase dim as) Source #
mustBeOneOf :: MonadUnify m => [PrimType] -> SrcLoc -> TypeBase () () -> m () Source #
equalityType :: (MonadUnify m, Pretty (ShapeDecl dim), Monoid as) => SrcLoc -> TypeBase dim as -> m () Source #
normaliseType :: (Substitutable a, MonadUnify m) => a -> m a Source #
unify :: MonadUnify m => SrcLoc -> TypeBase () () -> TypeBase () () -> m () Source #
Unifies two types.
doUnification :: SrcLoc -> [TypeParam] -> TypeBase () () -> TypeBase () () -> Either TypeError (TypeBase () ()) Source #
Perform a unification of two types outside a monadic context. The type parameters are allowed to be instantiated (with 'TypeParamDim ignored); all other types are considered rigid.