Copyright | (c) 2011, Stephanie Weirich |
---|---|
License | BSD3 (See LFresh.hs) |
Maintainer | Aleksey Kliger |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Extensions |
|
Unbound.Generics.LocallyNameless.LFresh
Contents
Description
Local freshness monad.
- class Monad m => LFresh m where
- type LFreshM = LFreshMT Identity
- runLFreshM :: LFreshM a -> a
- contLFreshM :: LFreshM a -> Set AnyName -> a
- newtype LFreshMT m a = LFreshMT {
- unLFreshMT :: ReaderT (Set AnyName) m a
- runLFreshMT :: LFreshMT m a -> m a
- contLFreshMT :: LFreshMT m a -> Set AnyName -> m a
The LFresh
class
class Monad m => LFresh m where Source
This is the class of monads that support freshness in an (implicit) local scope. Generated names are fresh for the current local scope, not necessarily globally fresh.
Methods
lfresh :: Typeable a => Name a -> m (Name a) Source
Pick a new name that is fresh for the current (implicit) scope.
avoid :: [AnyName] -> m a -> m a Source
Avoid the given names when freshening in the subcomputation, that is, add the given names to the in-scope set.
getAvoids :: m (Set AnyName) Source
Get the set of names currently being avoided.
Instances
LFresh m => LFresh (IdentityT m) | |
LFresh m => LFresh (ListT m) | |
LFresh m => LFresh (MaybeT m) | |
Monad m => LFresh (LFreshMT m) | |
LFresh m => LFresh (ContT r m) | |
LFresh m => LFresh (ReaderT r m) | |
LFresh m => LFresh (StateT s m) | |
LFresh m => LFresh (StateT s m) | |
LFresh m => LFresh (ExceptT e m) | |
(Error e, LFresh m) => LFresh (ErrorT e m) | |
(Monoid w, LFresh m) => LFresh (WriterT w m) | |
(Monoid w, LFresh m) => LFresh (WriterT w m) |
type LFreshM = LFreshMT Identity Source
A convenient monad which is an instance of LFresh
. It keeps
track of a set of names to avoid, and when asked for a fresh one
will choose the first unused numerical name.
runLFreshM :: LFreshM a -> a Source
Run a LFreshM computation in an empty context.
contLFreshM :: LFreshM a -> Set AnyName -> a Source
Run a LFreshM computation given a set of names to avoid.
The LFresh monad transformer. Keeps track of a set of names to avoid, and when asked for a fresh one will choose the first numeric prefix of the given name which is currently unused.
Constructors
LFreshMT | |
Fields
|
Instances
MonadTrans LFreshMT | |
MonadError e m => MonadError e (LFreshMT m) | |
MonadReader r m => MonadReader r (LFreshMT m) | |
MonadState s m => MonadState s (LFreshMT m) | |
MonadWriter w m => MonadWriter w (LFreshMT m) | |
Alternative m => Alternative (LFreshMT m) | |
Monad m => Monad (LFreshMT m) | |
Functor m => Functor (LFreshMT m) | |
MonadFix m => MonadFix (LFreshMT m) | |
MonadPlus m => MonadPlus (LFreshMT m) | |
Applicative m => Applicative (LFreshMT m) | |
MonadIO m => MonadIO (LFreshMT m) | |
MonadCont m => MonadCont (LFreshMT m) | |
Monad m => LFresh (LFreshMT m) |
runLFreshMT :: LFreshMT m a -> m a Source
Run an LFreshMT
computation in an empty context.