unification-fd-0.8.0: Simple generic unification algorithms.

Portabilitysemi-portable (MPTCs, fundeps,...)
Stabilityexperimental
Maintainerwren@community.haskell.org
Safe HaskellSafe-Infered

Control.Unification.Types

Contents

Description

This module defines the classes and primitive types used by unification and related functions.

Synopsis

Unification terms

data UTerm t v Source

The type of terms generated by structures t over variables v. The structure type should implement Unifiable and the variable type should implement Variable.

The Show instance doesn't show the constructors, in order to improve legibility for large terms.

All the category theoretic instances (Functor, Foldable, Traversable,...) are provided because they are often useful; however, beware that since the implementations must be pure, they cannot read variables bound in the current context and therefore can create incoherent results. Therefore, you should apply the current bindings before using any of the functions provided by those classes.

Constructors

UVar !v

A unification variable.

UTerm !(t (UTerm t v))

Some structure containing subterms.

Instances

Functor t => Monad (UTerm t) 
Functor t => Functor (UTerm t) 
(Functor t, MonadPlus t) => MonadPlus (UTerm t) 
Functor t => Applicative (UTerm t) 
Foldable t => Foldable (UTerm t) 
Traversable t => Traversable (UTerm t) 
Alternative t => Alternative (UTerm t) 
(Show v, Show (t (UTerm t v))) => Show (UTerm t v) 

freeze :: Traversable t => UTerm t v -> Maybe (Fix t)Source

O(n). Extract a pure term from a mutable term, or return Nothing if the mutable term actually contains variables. N.B., this function is pure, so you should manually apply bindings before calling it.

unfreeze :: Functor t => Fix t -> UTerm t vSource

O(n). Embed a pure term as a mutable term.

Errors

data UnificationFailure t v Source

The possible failure modes that could be encountered in unification and related functions. While many of the functions could be given more accurate types if we used ad-hoc combinations of these constructors (i.e., because they can only throw one of the errors), the extra complexity is not considered worth it.

Constructors

OccursIn v (UTerm t v)

A cyclic term was encountered (i.e., the variable occurs free in a term it would have to be bound to in order to succeed). Infinite terms like this are not generally acceptable, so we do not support them. In logic programming this should simply be treated as unification failure; in type checking this should result in a "could not construct infinite type a = Foo a" error.

Note that since, by default, the library uses visited-sets instead of the occurs-check these errors will be thrown at the point where the cycle is dereferenced/unrolled (e.g., when applying bindings), instead of at the time when the cycle is created. However, the arguments to this constructor should express the same context as if we had performed the occurs-check, in order for error messages to be intelligable.

TermMismatch (t (UTerm t v)) (t (UTerm t v))

The top-most level of the terms do not match (according to zipMatch). In logic programming this should simply be treated as unification failure; in type checking this should result in a "could not match expected type Foo with inferred type Bar" error.

UnknownError String

Required for the Error instance, which in turn is required to appease ErrorT in the MTL. We do not use this anywhere.

Instances

(Show (t (UTerm t v)), Show v) => Show (UnificationFailure t v) 
Error (UnificationFailure t v) 

Basic type classes

class Traversable t => Unifiable t whereSource

An implementation of syntactically unifiable structure. The Traversable constraint is there because we also require terms to be functors and require the distributivity of sequence or mapM.

Methods

zipMatch :: t a -> t a -> Maybe (t (Either a (a, a)))Source

Perform one level of equality testing for terms. If the term constructors are unequal then return Nothing; if they are equal, then return the one-level spine filled with resolved subterms and/or pairs of subterms to be recursively checked.

class Eq v => Variable v whereSource

An implementation of unification variables. The Eq requirement is to determine whether two variables are equal as variables, without considering what they are bound to. We use Eq rather than having our own eqVar method so that clients can make use of library functions which commonly assume Eq.

Methods

getVarID :: v -> IntSource

Return a unique identifier for this variable, in order to support the use of visited-sets instead of occurs-checks. This function must satisfy the following coherence law with respect to the Eq instance:

x == y if and only if getVarID x == getVarID y

Instances

class (Unifiable t, Variable v, Applicative m, Monad m) => BindingMonad t v m | m -> t v whereSource

The basic class for generating, reading, and writing to bindings stored in a monad. These three functionalities could be split apart, but are combined in order to simplify contexts. Also, because most functions reading bindings will also perform path compression, there's no way to distinguish "true" mutation from mere path compression.

The superclass constraints are there to simplify contexts, since we make the same assumptions everywhere we use BindingMonad.

Methods

lookupVar :: v -> m (Maybe (UTerm t v))Source

Given a variable pointing to UTerm t v, return the term it's bound to, or Nothing if the variable is unbound.

freeVar :: m vSource

Generate a new free variable guaranteed to be fresh in m.

newVar :: UTerm t v -> m vSource

Generate a new variable (fresh in m) bound to the given term. The default implementation is:

 newVar t = do { v <- freeVar ; bindVar v t ; return v }

bindVar :: v -> UTerm t v -> m ()Source

Bind a variable to a term, overriding any previous binding.

Weighted path compression

data Rank t v Source

The target of variables for RankedBindingMonads. In order to support weighted path compression, each variable is bound to both another term (possibly) and also a "rank" which is related to the length of the variable chain to the term it's ultimately bound to.

The rank can be at most log V, where V is the total number of variables in the unification problem. Thus, A Word8 is sufficient for 2^(2^8) variables, which is far more than can be indexed by getVarID even on 64-bit architectures.

Constructors

Rank !Word8 !(Maybe (UTerm t v)) 

Instances

(Show v, Show (t (UTerm t v))) => Show (Rank t v) 

class BindingMonad t v m => RankedBindingMonad t v m | m -> t v whereSource

An advanced class for BindingMonads which also support weighted path compression. The weightedness adds non-trivial implementation complications; so even though weighted path compression is asymptotically optimal, the constant factors may make it worthwhile to stick with the unweighted path compression supported by BindingMonad.

Methods

lookupRankVar :: v -> m (Rank t v)Source

Given a variable pointing to UTerm t v, return its rank and the term it's bound to.

incrementRank :: v -> m ()Source

Increase the rank of a variable by one.

incrementBindVar :: v -> UTerm t v -> m ()Source

Bind a variable to a term and increment the rank at the same time. The default implementation is:

 incrementBindVar t v = do { incrementRank v ; bindVar v t }