Safe Haskell | None |
---|---|
Language | Haskell2010 |
Generalization of type schemes
Synopsis
- generalize :: forall m t. Unify m t => Tree (UVarOf m) t -> m (Tree (GTerm (UVarOf m)) t)
- instantiate :: Unify m t => Tree (GTerm (UVarOf m)) t -> m (Tree (UVarOf m) t)
- data GTerm v ast
- _GMono :: forall v ast. Prism' (GTerm v ast) (v ast)
- _GPoly :: forall v ast. Prism' (GTerm v ast) (v ast)
- _GBody :: forall v ast. Prism' (GTerm v ast) ((#) ast (GTerm v))
- data family KWitness k :: (Knot -> Type) -> Type
- instantiateWith :: forall m t a. Unify m t => m a -> (forall n. TypeConstraintsOf n -> Tree (UTerm (UVarOf m)) n) -> Tree (GTerm (UVarOf m)) t -> m (Tree (UVarOf m) t, a)
- instantiateForAll :: Unify m t => (TypeConstraintsOf t -> Tree (UTerm (UVarOf m)) t) -> Tree (UVarOf m) t -> WriterT [m ()] m (Tree (UVarOf m) t)
- instantiateH :: forall m t. Unify m t => (forall n. TypeConstraintsOf n -> Tree (UTerm (UVarOf m)) n) -> Tree (GTerm (UVarOf m)) t -> WriterT [m ()] m (Tree (UVarOf m) t)
Documentation
generalize :: forall m t. Unify m t => Tree (UVarOf m) t -> m (Tree (GTerm (UVarOf m)) t) Source #
Generalize a unification term pointed by the given variable to a GTerm
.
Unification variables that are scoped within the term
become universally quantified skolems.
instantiate :: Unify m t => Tree (GTerm (UVarOf m)) t -> m (Tree (UVarOf m) t) Source #
Instantiate a generalized type with fresh unification variables for the quantified variables
An efficient representation of a type scheme arising from generalizing a unification term. Type subexpressions which are completely monomoprhic are tagged as such, to avoid redundant instantation and unification work
GMono (v ast) | Completely monomoprhic term |
GPoly (v ast) | Points to a quantified variable (instantiation will
create fresh unification terms) ( |
GBody (ast # GTerm v) | Term with some polymorphic parts |
Instances
data family KWitness k :: (Knot -> Type) -> Type Source #
KWitness k n
is a witness that n
is a node of k
Instances
instantiateWith :: forall m t a. Unify m t => m a -> (forall n. TypeConstraintsOf n -> Tree (UTerm (UVarOf m)) n) -> Tree (GTerm (UVarOf m)) t -> m (Tree (UVarOf m) t, a) Source #
instantiateForAll :: Unify m t => (TypeConstraintsOf t -> Tree (UTerm (UVarOf m)) t) -> Tree (UVarOf m) t -> WriterT [m ()] m (Tree (UVarOf m) t) Source #
Exports for SPECIALIZE
pragmas.