Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Hyper.Unify.Constraints
Description
A class for constraints for unification variables
Synopsis
- class (PartialOrd c, Monoid c) => TypeConstraints c where
- generalizeConstraints :: c -> c
- toScopeConstraints :: c -> c
- class TypeConstraints (TypeConstraintsOf ast) => HasTypeConstraints (ast :: HyperType) where
- type TypeConstraintsOf (ast :: HyperType) :: Type
- verifyConstraints :: TypeConstraintsOf ast -> (ast # h) -> Maybe (ast # WithConstraint h)
- data WithConstraint h ast = WithConstraint {
- _wcConstraint :: TypeConstraintsOf (GetHyperType ast)
- _wcBody :: h ast
- wcConstraint :: forall h ast. Lens' (WithConstraint h ast) (TypeConstraintsOf (GetHyperType ast))
- wcBody :: forall h ast h. Lens (WithConstraint h ast) (WithConstraint h ast) (h ast) (h ast)
Documentation
class (PartialOrd c, Monoid c) => TypeConstraints c where Source #
A class for constraints for unification variables.
Methods
generalizeConstraints :: c -> c Source #
Remove scope constraints.
When generalizing unification variables into universally quantified variables, and then into fresh unification variables upon instantiation, some constraints need to be carried over, and the "scope" constraints need to be erased.
toScopeConstraints :: c -> c Source #
Remove all constraints other than the scope constraints
Useful for comparing constraints to the current scope constraints
Instances
TypeConstraints ScopeLevel Source # | |
Defined in Hyper.Infer.ScopeLevel Methods |
class TypeConstraints (TypeConstraintsOf ast) => HasTypeConstraints (ast :: HyperType) where Source #
A class for terms that have constraints.
A dependency of Unify
Associated Types
type TypeConstraintsOf (ast :: HyperType) :: Type Source #
Methods
verifyConstraints :: TypeConstraintsOf ast -> (ast # h) -> Maybe (ast # WithConstraint h) Source #
Verify constraints on the ast and apply the given child verifier on children
data WithConstraint h ast Source #
A HyperType
to represent a term alongside a constraint.
Used for verifyConstraints
.
Constructors
WithConstraint | |
Fields
|
wcConstraint :: forall h ast. Lens' (WithConstraint h ast) (TypeConstraintsOf (GetHyperType ast)) Source #
wcBody :: forall h ast h. Lens (WithConstraint h ast) (WithConstraint h ast) (h ast) (h ast) Source #