monad-unify-0.2.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

class (Typeable t, Data t) => 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

($?) :: Partial t => Substitution t -> t -> tSource

Apply a substitution to a value

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) (ErrorT String m) a
 

Instances

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

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

Collect all unknowns occurring inside a value

runUnify :: UnifyState t -> UnifyT t m a -> m (Either String (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

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

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

occursCheck :: (Monad 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