Copyright | Copyright (c) 2007--2015 wren gayle romano |
---|---|
License | BSD |
Maintainer | wren@community.haskell.org |
Stability | experimental |
Portability | semi-portable (MPTCs,...) |
Safe Haskell | None |
Language | Haskell98 |
This module defines a state monad for functional pointers
represented by integers as keys into an IntMap
. This technique
was independently discovered by Dijkstra et al. This module
extends the approach by using a state monad transformer, which
can be made into a backtracking state monad by setting the
underlying monad to some MonadLogic
(part of the logict
library, described by Kiselyov et al.).
- Atze Dijkstra, Arie Middelkoop, S. Doaitse Swierstra (2008) Efficient Functional Unification and Substitution, Technical Report UU-CS-2008-027, Utrecht University.
- Oleg Kiselyov, Chung-chieh Shan, Daniel P. Friedman, and Amr Sabry (2005) Backtracking, Interleaving, and Terminating Monad Transformers, ICFP.
Synopsis
- newtype IntVar = IntVar Int
- data IntBindingState t
- data IntBindingT t m a
- runIntBindingT :: IntBindingT t m a -> m (a, IntBindingState t)
- evalIntBindingT :: Monad m => IntBindingT t m a -> m a
- execIntBindingT :: Monad m => IntBindingT t m a -> m (IntBindingState 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 IntBindingState t Source #
Binding state for IntVar
.
Instances
Show (t (UTerm t IntVar)) => Show (IntBindingState t) Source # | |
Defined in Control.Unification.IntVar showsPrec :: Int -> IntBindingState t -> ShowS # show :: IntBindingState t -> String # showList :: [IntBindingState t] -> ShowS # | |
Monad m => MonadState (IntBindingState t) (IntBindingT t m) Source # | |
Defined in Control.Unification.IntVar get :: IntBindingT t m (IntBindingState t) # put :: IntBindingState t -> IntBindingT t m () # state :: (IntBindingState t -> (a, IntBindingState t)) -> IntBindingT t m a # |
data IntBindingT 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
runIntBindingT :: IntBindingT t m a -> m (a, IntBindingState t) Source #
evalIntBindingT :: Monad m => IntBindingT t m a -> m a Source #
N.B., you should explicitly apply bindings before calling this function, or else the bindings will be lost
execIntBindingT :: Monad m => IntBindingT t m a -> m (IntBindingState t) Source #