Copyright | Copyright (c) 2007--2015 wren gayle romano |
---|---|
License | BSD |
Maintainer | wren@community.haskell.org |
Stability | highly experimental |
Portability | semi-portable (MPTCs,...) |
Safe Haskell | None |
Language | Haskell98 |
A ranked variant of Control.Unification.IntVar.
Synopsis
- newtype IntVar = IntVar Int
- data IntRBindingState t
- data IntRBindingT t m a
- runIntRBindingT :: IntRBindingT t m a -> m (a, IntRBindingState t)
- evalIntRBindingT :: Monad m => IntRBindingT t m a -> m a
- execIntRBindingT :: Monad m => IntRBindingT t m a -> m (IntRBindingState t)
Documentation
A "mutable" unification variable implemented by an integer.
This provides an entirely pure alternative to truly mutable
alternatives (like STVar
), which can make backtracking easier.
N.B., because this implementation is pure, we can use it for both ranked and unranked monads.
Instances
Eq IntVar Source # | |
Show IntVar Source # | |
Variable IntVar Source # | |
(Unifiable t, Applicative m, Monad m) => RankedBindingMonad t IntVar (IntRBindingT t m) Source # | |
Defined in Control.Unification.Ranked.IntVar lookupRankVar :: IntVar -> IntRBindingT t m (Rank t IntVar) Source # incrementRank :: IntVar -> IntRBindingT t m () Source # incrementBindVar :: IntVar -> UTerm t IntVar -> IntRBindingT t m () Source # | |
(Unifiable t, Applicative m, Monad m) => BindingMonad t IntVar (IntBindingT t m) Source # | |
(Unifiable t, Applicative m, Monad m) => BindingMonad t IntVar (IntRBindingT t m) Source # | |
data IntRBindingState t Source #
Ranked binding state for IntVar
.
Instances
Show (t (UTerm t IntVar)) => Show (IntRBindingState t) Source # | |
Defined in Control.Unification.Ranked.IntVar showsPrec :: Int -> IntRBindingState t -> ShowS # show :: IntRBindingState t -> String # showList :: [IntRBindingState t] -> ShowS # | |
Monad m => MonadState (IntRBindingState t) (IntRBindingT t m) Source # | |
Defined in Control.Unification.Ranked.IntVar get :: IntRBindingT t m (IntRBindingState t) # put :: IntRBindingState t -> IntRBindingT t m () # state :: (IntRBindingState t -> (a, IntRBindingState t)) -> IntRBindingT t m a # |
data IntRBindingT t m a Source #
A monad for storing IntVar
bindings, implemented as a StateT
.
For a plain state monad, set m = Identity
; for a backtracking
state monad, set m = Logic
.
Instances
runIntRBindingT :: IntRBindingT t m a -> m (a, IntRBindingState t) Source #
evalIntRBindingT :: Monad m => IntRBindingT t m a -> m a Source #
N.B., you should explicitly apply bindings before calling this function, or else the bindings will be lost
execIntRBindingT :: Monad m => IntRBindingT t m a -> m (IntRBindingState t) Source #