Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides a monadic facility similar (and built on top
of) Futhark.FreshNames. The removes the need for a (small) amount of
boilerplate, at the cost of using some GHC extensions. The idea is
that if your compiler pass runs in a monad that is an instance of
MonadFreshNames
, you can automatically use the name generation
functions exported by this module.
Synopsis
- class (Applicative m, Monad m) => MonadFreshNames m where
- getNameSource :: m VNameSource
- putNameSource :: VNameSource -> m ()
- modifyNameSource :: MonadFreshNames m => (VNameSource -> (a, VNameSource)) -> m a
- newName :: MonadFreshNames m => VName -> m VName
- newNameFromString :: MonadFreshNames m => String -> m VName
- newID :: MonadFreshNames m => Name -> m VName
- newIDFromString :: MonadFreshNames m => String -> m VName
- newVName :: MonadFreshNames m => String -> m VName
- newVName' :: MonadFreshNames m => (String -> String) -> String -> m VName
- newIdent :: MonadFreshNames m => String -> Type -> m Ident
- newIdent' :: MonadFreshNames m => (String -> String) -> Ident -> m Ident
- newIdents :: MonadFreshNames m => String -> [Type] -> m [Ident]
- newParam :: MonadFreshNames m => String -> attr -> m (Param attr)
- newParam' :: MonadFreshNames m => (String -> String) -> Param attr -> m (Param attr)
- data VNameSource
- blankNameSource :: VNameSource
- newNameSource :: Int -> VNameSource
- newVNameFromName :: VNameSource -> Name -> (VName, VNameSource)
Documentation
class (Applicative m, Monad m) => MonadFreshNames m where Source #
A monad that stores a name source. The following is a good
instance for a monad in which the only state is a NameSource vn
:
instance MonadFreshNames vn MyMonad where getNameSource = get putNameSource = put
getNameSource :: m VNameSource Source #
putNameSource :: VNameSource -> m () Source #
Instances
modifyNameSource :: MonadFreshNames m => (VNameSource -> (a, VNameSource)) -> m a Source #
Run a computation needing a fresh name source and returning a new
one, using getNameSource
and putNameSource
before and after the
computation.
newName :: MonadFreshNames m => VName -> m VName Source #
Produce a fresh name, using the given name as a template.
newNameFromString :: MonadFreshNames m => String -> m VName Source #
As newName
, but takes a String
for the name template.
newID :: MonadFreshNames m => Name -> m VName Source #
Produce a fresh ID
, using the given base name as a template.
newIDFromString :: MonadFreshNames m => String -> m VName Source #
newVName :: MonadFreshNames m => String -> m VName Source #
Produce a fresh VName
, using the given base name as a template.
newVName' :: MonadFreshNames m => (String -> String) -> String -> m VName Source #
Produce a fresh VName
, using the given name as a template, but
possibly appending something more..
newIdent :: MonadFreshNames m => String -> Type -> m Ident Source #
Produce a fresh Ident
, using the given name as a template.
newIdents :: MonadFreshNames m => String -> [Type] -> m [Ident] Source #
Produce several Ident
s, using the given name as a template,
based on a list of types.
newParam :: MonadFreshNames m => String -> attr -> m (Param attr) Source #
Produce a fresh ParamT
, using the given name as a template.
data VNameSource Source #
A name source is conceptually an infinite sequence of names with no repeating entries. In practice, when asked for a name, the name source will return the name along with a new name source, which should then be used in place of the original.
The Ord
instance is based on how many names have been extracted
from the name source.
Instances
blankNameSource :: VNameSource Source #
A blank name source.
newNameSource :: Int -> VNameSource Source #
A new name source that starts counting from the given number.
newVNameFromName :: VNameSource -> Name -> (VName, VNameSource) Source #
Produce a fresh VName
, using the given base name as a template.