monad-unify-0.2.2: Generic first-order unification

Safe HaskellNone

Control.Monad.Unify

Description

 

Synopsis

Documentation

type Unknown = IntSource

Untyped unification variables

class Partial t whereSource

A type which can contain unification variables

class Partial t => Unifiable m t | t -> m whereSource

Identifies types which support unification

Methods

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

data Substitution t Source

A substitution maintains a mapping from unification variables to their values

Constructors

Substitution 

Instances

data UnifyState t Source

State required for type checking

Constructors

UnifyState 

Fields

unifyNextVar :: Int

The next fresh unification variable

unifyCurrentSubstitution :: Substitution t

The current substitution

defaultUnifyState :: Partial t => UnifyState tSource

An empty UnifyState

newtype UnifyT t m a Source

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

Constructors

UnifyT 

Fields

unUnify :: StateT (UnifyState t) m a
 

Instances

MonadError e m => MonadError e (UnifyT t m) 
MonadState s m => MonadState s (UnifyT t m) 
Monad m => Monad (UnifyT t m) 
Functor m => Functor (UnifyT t m) 
MonadPlus m => MonadPlus (UnifyT t m) 
(Monad m, Functor m) => Applicative (UnifyT t m) 

runUnify :: UnifyState t -> UnifyT t m a -> m (a, UnifyState t)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 :: Partial t => Unknown -> t -> Substitution tSource

Substitute a single unification variable

(=:=) :: (Error e, Monad m, MonadError e m, Unifiable m t) => Unknown -> t -> UnifyT t m ()Source

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

occursCheck :: (Error e, Monad m, MonadError e m, Partial t) => Unknown -> t -> UnifyT t m ()Source

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

fresh' :: Monad m => UnifyT t m UnknownSource

Generate a fresh untyped unification variable

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

Generate a fresh unification variable at a specific type