unbound-0.4.4: Generic support for programming with names and binders

LicenseBSD-like (see LICENSE)
MaintainerBrent Yorgey <byorgey@cis.upenn.edu>
Stabilityexperimental
Portabilityunportable (GHC 7 only)
Safe HaskellNone
LanguageHaskell2010

Unbound.LocallyNameless.Fresh

Contents

Description

The Fresh and LFresh classes, which govern monads with fresh name generation capabilities, and the FreshM(T) and LFreshM(T) monad (transformers) which provide useful default implementations.

Synopsis

The Fresh class

class Monad m => Fresh m where Source

The Fresh type class governs monads which can generate new globally unique Names based on a given Name.

Methods

fresh :: Name a -> m (Name a) Source

Generate a new globally unique name based on the given one.

Instances

Fresh m => Fresh (ListT m) Source 
Fresh m => Fresh (MaybeT m) Source 
Fresh m => Fresh (IdentityT m) Source 
Monad m => Fresh (FreshMT m) Source 
Fresh m => Fresh (ContT r m) Source 
Fresh m => Fresh (ReaderT r m) Source 
Fresh m => Fresh (StateT s m) Source 
Fresh m => Fresh (StateT s m) Source 
Fresh m => Fresh (ExceptT e m) Source 
(Monoid w, Fresh m) => Fresh (WriterT w m) Source 
(Monoid w, Fresh m) => Fresh (WriterT w m) Source 

type FreshM = FreshMT Identity Source

A convenient monad which is an instance of Fresh. It keeps track of a global index used for generating fresh names, which is incremented every time fresh is called.

runFreshM :: FreshM a -> a Source

Run a FreshM computation (with the global index starting at zero).

contFreshM :: FreshM a -> Integer -> a Source

Run a FreshM computation given a starting index.

newtype FreshMT m a Source

The FreshM monad transformer. Keeps track of the lowest index still globally unused, and increments the index every time it is asked for a fresh name.

Constructors

FreshMT 

Fields

unFreshMT :: StateT Integer m a
 

runFreshMT :: Monad m => FreshMT m a -> m a Source

Run a FreshMT computation (with the global index starting at zero).

contFreshMT :: Monad m => FreshMT m a -> Integer -> m a Source

Run a FreshMT computation given a starting index for fresh name generation.

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 :: Rep 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

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

unLFreshMT :: ReaderT (Set AnyName) m a
 

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.