Safe Haskell | None |
---|
- type Unknown = Int
- class Partial t where
- class Partial t => Unifiable m t | t -> m where
- data Substitution t = Substitution {
- runSubstitution :: HashMap Int t
- data UnifyState t = UnifyState {}
- defaultUnifyState :: Partial t => UnifyState t
- newtype UnifyT t m a = UnifyT {
- unUnify :: StateT (UnifyState t) m a
- runUnify :: UnifyState t -> UnifyT t m a -> m (a, UnifyState t)
- substituteOne :: Partial t => Unknown -> t -> Substitution t
- (=:=) :: (Error e, Monad m, MonadError e m, Unifiable m t) => Unknown -> t -> UnifyT t m ()
- occursCheck :: (Error e, Monad m, MonadError e m, Partial t) => Unknown -> t -> UnifyT t m ()
- fresh' :: Monad m => UnifyT t m Unknown
- fresh :: (Monad m, Partial t) => UnifyT t m t
Documentation
A type which can contain unification variables
data Substitution t Source
A substitution maintains a mapping from unification variables to their values
Partial t => Monoid (Substitution t) |
data UnifyState t Source
State required for type checking
UnifyState | |
|
defaultUnifyState :: Partial t => UnifyState tSource
An empty UnifyState
The type checking monad, which provides the state of the type checker, and error reporting capabilities
UnifyT | |
|
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