unbound-generics-0.3.2: Support for programming with names and binders using GHC Generics

Copyright(c) 2011 Stephanie Weirich
LicenseBSD3 (See LFresh.hs)
MaintainerAleksey Kliger
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010
Extensions
  • Cpp
  • UndecidableInstances
  • TypeSynonymInstances
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • GeneralizedNewtypeDeriving

Unbound.Generics.LocallyNameless.LFresh

Contents

Description

Local freshness monad.

Synopsis

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.

Minimal complete definition

lfresh, avoid, getAvoids

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 (ListT m) Source # 

Methods

lfresh :: Typeable * a => Name a -> ListT m (Name a) Source #

avoid :: [AnyName] -> ListT m a -> ListT m a Source #

getAvoids :: ListT m (Set AnyName) Source #

LFresh m => LFresh (MaybeT m) Source # 

Methods

lfresh :: Typeable * a => Name a -> MaybeT m (Name a) Source #

avoid :: [AnyName] -> MaybeT m a -> MaybeT m a Source #

getAvoids :: MaybeT m (Set AnyName) Source #

Monad m => LFresh (LFreshMT m) Source # 
LFresh m => LFresh (IdentityT * m) Source # 
(Error e, LFresh m) => LFresh (ErrorT e m) Source # 

Methods

lfresh :: Typeable * a => Name a -> ErrorT e m (Name a) Source #

avoid :: [AnyName] -> ErrorT e m a -> ErrorT e m a Source #

getAvoids :: ErrorT e m (Set AnyName) Source #

LFresh m => LFresh (ExceptT e m) Source # 

Methods

lfresh :: Typeable * a => Name a -> ExceptT e m (Name a) Source #

avoid :: [AnyName] -> ExceptT e m a -> ExceptT e m a Source #

getAvoids :: ExceptT e m (Set AnyName) Source #

LFresh m => LFresh (StateT s m) Source # 

Methods

lfresh :: Typeable * a => Name a -> StateT s m (Name a) Source #

avoid :: [AnyName] -> StateT s m a -> StateT s m a Source #

getAvoids :: StateT s m (Set AnyName) Source #

LFresh m => LFresh (StateT s m) Source # 

Methods

lfresh :: Typeable * a => Name a -> StateT s m (Name a) Source #

avoid :: [AnyName] -> StateT s m a -> StateT s m a Source #

getAvoids :: StateT s m (Set AnyName) Source #

(Monoid w, LFresh m) => LFresh (WriterT w m) Source # 

Methods

lfresh :: Typeable * a => Name a -> WriterT w m (Name a) Source #

avoid :: [AnyName] -> WriterT w m a -> WriterT w m a Source #

getAvoids :: WriterT w m (Set AnyName) Source #

(Monoid w, LFresh m) => LFresh (WriterT w m) Source # 

Methods

lfresh :: Typeable * a => Name a -> WriterT w m (Name a) Source #

avoid :: [AnyName] -> WriterT w m a -> WriterT w m a Source #

getAvoids :: WriterT w m (Set AnyName) Source #

LFresh m => LFresh (ContT * r m) Source # 

Methods

lfresh :: Typeable * a => Name a -> ContT * r m (Name a) Source #

avoid :: [AnyName] -> ContT * r m a -> ContT * r m a Source #

getAvoids :: ContT * r m (Set AnyName) Source #

LFresh m => LFresh (ReaderT * r m) Source # 

Methods

lfresh :: Typeable * a => Name a -> ReaderT * r m (Name a) Source #

avoid :: [AnyName] -> ReaderT * r m a -> ReaderT * r m a Source #

getAvoids :: ReaderT * r m (Set AnyName) Source #

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.

newtype LFreshMT m a Source #

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 Source # 

Methods

lift :: Monad m => m a -> LFreshMT m a #

MonadWriter w m => MonadWriter w (LFreshMT m) Source # 

Methods

writer :: (a, w) -> LFreshMT m a #

tell :: w -> LFreshMT m () #

listen :: LFreshMT m a -> LFreshMT m (a, w) #

pass :: LFreshMT m (a, w -> w) -> LFreshMT m a #

MonadState s m => MonadState s (LFreshMT m) Source # 

Methods

get :: LFreshMT m s #

put :: s -> LFreshMT m () #

state :: (s -> (a, s)) -> LFreshMT m a #

MonadReader r m => MonadReader r (LFreshMT m) Source # 

Methods

ask :: LFreshMT m r #

local :: (r -> r) -> LFreshMT m a -> LFreshMT m a #

reader :: (r -> a) -> LFreshMT m a #

MonadError e m => MonadError e (LFreshMT m) Source # 

Methods

throwError :: e -> LFreshMT m a #

catchError :: LFreshMT m a -> (e -> LFreshMT m a) -> LFreshMT m a #

Monad m => Monad (LFreshMT m) Source # 

Methods

(>>=) :: LFreshMT m a -> (a -> LFreshMT m b) -> LFreshMT m b #

(>>) :: LFreshMT m a -> LFreshMT m b -> LFreshMT m b #

return :: a -> LFreshMT m a #

fail :: String -> LFreshMT m a #

Functor m => Functor (LFreshMT m) Source # 

Methods

fmap :: (a -> b) -> LFreshMT m a -> LFreshMT m b #

(<$) :: a -> LFreshMT m b -> LFreshMT m a #

MonadFix m => MonadFix (LFreshMT m) Source # 

Methods

mfix :: (a -> LFreshMT m a) -> LFreshMT m a #

Applicative m => Applicative (LFreshMT m) Source # 

Methods

pure :: a -> LFreshMT m a #

(<*>) :: LFreshMT m (a -> b) -> LFreshMT m a -> LFreshMT m b #

liftA2 :: (a -> b -> c) -> LFreshMT m a -> LFreshMT m b -> LFreshMT m c #

(*>) :: LFreshMT m a -> LFreshMT m b -> LFreshMT m b #

(<*) :: LFreshMT m a -> LFreshMT m b -> LFreshMT m a #

MonadIO m => MonadIO (LFreshMT m) Source # 

Methods

liftIO :: IO a -> LFreshMT m a #

Alternative m => Alternative (LFreshMT m) Source # 

Methods

empty :: LFreshMT m a #

(<|>) :: LFreshMT m a -> LFreshMT m a -> LFreshMT m a #

some :: LFreshMT m a -> LFreshMT m [a] #

many :: LFreshMT m a -> LFreshMT m [a] #

MonadPlus m => MonadPlus (LFreshMT m) Source # 

Methods

mzero :: LFreshMT m a #

mplus :: LFreshMT m a -> LFreshMT m a -> LFreshMT m a #

MonadThrow m => MonadThrow (LFreshMT m) Source # 

Methods

throwM :: Exception e => e -> LFreshMT m a #

MonadCatch m => MonadCatch (LFreshMT m) Source # 

Methods

catch :: Exception e => LFreshMT m a -> (e -> LFreshMT m a) -> LFreshMT m a #

MonadMask m => MonadMask (LFreshMT m) Source # 

Methods

mask :: ((forall a. LFreshMT m a -> LFreshMT m a) -> LFreshMT m b) -> LFreshMT m b #

uninterruptibleMask :: ((forall a. LFreshMT m a -> LFreshMT m a) -> LFreshMT m b) -> LFreshMT m b #

MonadCont m => MonadCont (LFreshMT m) Source # 

Methods

callCC :: ((a -> LFreshMT m b) -> LFreshMT m a) -> LFreshMT m a #

Monad m => LFresh (LFreshMT m) Source # 

runLFreshMT :: LFreshMT m a -> m a Source #

Run an LFreshMT computation in an empty context.

contLFreshMT :: LFreshMT m a -> Set AnyName -> m a Source #

Run an LFreshMT computation given a set of names to avoid.