hypertypes-0.1.0.2: Typed ASTs
Safe HaskellNone
LanguageHaskell2010

Hyper.Class.Unify

Description

A class for unification

Synopsis

Documentation

class (Eq (UVarOf m # t), RTraversable t, ZipMatch t, HasTypeConstraints t, HasQuantifiedVar t, Monad m, MonadQuantify (TypeConstraintsOf t) (QVar t) m) => Unify m t where Source #

Unify m t enables unify to perform unification for t in the Monad m.

The unifyRecursive method represents the constraint that Unify m applies to all recursive child nodes. It replaces context for Unify to avoid UndecidableSuperClasses.

Minimal complete definition

binding

Methods

binding :: BindingDict (UVarOf m) m t Source #

The implementation for unification variables binding and lookup

unifyError :: (UnifyError t # UVarOf m) -> m a Source #

Handles a unification error.

If unifyError is called then unification has failed. A compiler implementation may present an error message based on the provided UnifyError when this occurs.

default unifyError :: (MonadError (e # Pure) m, HSubset' e (UnifyError t)) => (UnifyError t # UVarOf m) -> m a Source #

structureMismatch :: (forall c. Unify m c => (UVarOf m # c) -> (UVarOf m # c) -> m (UVarOf m # c)) -> (t # UVarOf m) -> (t # UVarOf m) -> m () Source #

What to do when top-levels of terms being unified do not match.

Usually this will cause a unifyError.

Some AST terms could be equivalent despite not matching structurally, like record field extentions with the fields ordered differently. Those would override the default implementation to handle the unification of mismatching structures.

unifyRecursive :: Proxy m -> Proxy t -> Dict (HNodesConstraint t (Unify m)) Source #

Instances

Instances details
Recursive (Unify m) Source # 
Instance details

Defined in Hyper.Class.Unify

Methods

recurse :: forall (h :: HyperType) proxy. (HNodes h, Unify m h) => proxy (Unify m h) -> Dict (HNodesConstraint h (Unify m)) Source #

type family UVarOf (m :: Type -> Type) :: HyperType Source #

Unification variable type for a unification monad

class Unify m t => UnifyGen m t where Source #

A class for unification monads with scope levels

Minimal complete definition

scopeConstraints

Methods

scopeConstraints :: Proxy t -> m (TypeConstraintsOf t) Source #

Get the current scope constraint

unifyGenRecursive :: Proxy m -> Proxy t -> Dict (HNodesConstraint t (UnifyGen m)) Source #

Instances

Instances details
Recursive (UnifyGen m) Source # 
Instance details

Defined in Hyper.Class.Unify

Methods

recurse :: forall (h :: HyperType) proxy. (HNodes h, UnifyGen m h) => proxy (UnifyGen m h) -> Dict (HNodesConstraint h (UnifyGen m)) Source #

data BindingDict v m t Source #

BindingDict implements unification variables for a type in a unification monad.

It is parameterized on:

Has 2 implementations in hypertypes:

Constructors

BindingDict 

Fields

applyBindings :: forall m t. Unify m t => (UVarOf m # t) -> m (Pure # t) Source #

Resolve a term from a unification variable.

Note that this must be done after all unifications involving the term and its children are done, as it replaces unification state with cached resolved terms.

semiPruneLookup :: Unify m t => (UVarOf m # t) -> m (UVarOf m # t, UTerm (UVarOf m) # t) Source #

Look up a variable, and return last variable pointing to result. Prunes all variables on way to point to the last variable (path-compression ala union-find).

occursError :: Unify m t => (UVarOf m # t) -> (UTermBody (UVarOf m) # t) -> m a Source #

Format and throw an occurs check error