monad-unify-0.1.0.0: Generic first-order unification

Safe HaskellNone

Control.Monad.Unify

Description

 

Synopsis

Documentation

newtype Unknown Source

Untyped unification variables

Constructors

Unknown 

Fields

runUnknown :: Int

The underlying integer representing the unification variable

newtype TypedUnknown t Source

The type of typed unification variables

Constructors

TypedUnknown 

Fields

runTypedUnknown :: Unknown

The underlying untyped unification variable

class (Typeable t, Data t, Show t) => Unifiable m t | t -> m whereSource

Identifies types which support unification

Methods

unknown :: TypedUnknown t -> tSource

isUnknown :: t -> Maybe (TypedUnknown t)Source

(?=) :: t -> t -> UnifyT m ()Source

newtype Substitution Source

A substitution maintains a mapping from unification variables to their values, ensuring that the type of a unification variable matches the type of its value.

Constructors

Substitution 

Fields

runSubstitution :: forall d. Data d => d -> d
 

Instances

data UnifyState Source

State required for type checking:

Constructors

UnifyState 

Fields

unifyNextVar :: Int

The next fresh unification variable

unifyCurrentSubstitution :: Substitution

The current substitution

defaultUnifyState :: UnifyStateSource

An empty UnifyState

newtype UnifyT m a Source

The type checking monad, which provides the state of the type checker, and error reporting capabilities

Constructors

UnifyT 

Instances

unknowns :: Data d => d -> [Unknown]Source

Collect all unknowns occurring inside a value

runUnify :: UnifyState -> UnifyT m a -> m (Either String (a, UnifyState))Source

Run a computation in the Unify monad, failing with an error, or succeeding with a return value and the new next unification variable

substituteOne :: Unifiable m t => TypedUnknown t -> t -> SubstitutionSource

Substitute a single unification variable

replace :: (Monad m, Unifiable m t) => TypedUnknown t -> t -> UnifyT m ()Source

Replace a unification variable with the specified value in the current substitution

occursCheck :: (Monad m, Unifiable m t) => TypedUnknown s -> t -> UnifyT m ()Source

Perform the occurs check, to make sure a unification variable does not occur inside a value

fresh' :: Monad m => UnifyT m UnknownSource

Generate a fresh untyped unification variable

fresh :: (Monad m, Unifiable m t) => UnifyT m tSource

Generate a fresh unification variable at a specific type