Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Futhark.Transform.Rename
Description
This module provides facilities for transforming Futhark programs
such that names are unique, via the renameProg
function.
Synopsis
- renameProg :: (Renameable rep, MonadFreshNames m) => Prog rep -> m (Prog rep)
- renameExp :: (Renameable rep, MonadFreshNames m) => Exp rep -> m (Exp rep)
- renameStm :: (Renameable rep, MonadFreshNames m) => Stm rep -> m (Stm rep)
- renameBody :: (Renameable rep, MonadFreshNames m) => Body rep -> m (Body rep)
- renameLambda :: (Renameable rep, MonadFreshNames m) => Lambda rep -> m (Lambda rep)
- renamePat :: (Rename dec, MonadFreshNames m) => Pat dec -> m (Pat dec)
- renameSomething :: (Rename a, MonadFreshNames m) => a -> m a
- renameBound :: [VName] -> RenameM a -> RenameM a
- renameStmsWith :: (MonadFreshNames m, Renameable rep, Rename a) => Stms rep -> a -> m (Stms rep, a)
- data RenameM a
- substituteRename :: Substitute a => a -> RenameM a
- renamingStms :: Renameable rep => Stms rep -> (Stms rep -> RenameM a) -> RenameM a
- class Rename a where
- type Renameable rep = (Rename (LetDec rep), Rename (ExpDec rep), Rename (BodyDec rep), Rename (FParamInfo rep), Rename (LParamInfo rep), Rename (RetType rep), Rename (BranchType rep), Rename (Op rep))
Renaming programs
renameProg :: (Renameable rep, MonadFreshNames m) => Prog rep -> m (Prog rep) Source #
Rename variables such that each is unique. The semantics of the program are unaffected, under the assumption that the program was correct to begin with. In particular, the renaming may make an invalid program valid.
Renaming parts of a program.
renameExp :: (Renameable rep, MonadFreshNames m) => Exp rep -> m (Exp rep) Source #
Rename bound variables such that each is unique. The semantics of the expression is unaffected, under the assumption that the expression was correct to begin with. Any free variables are left untouched.
renameStm :: (Renameable rep, MonadFreshNames m) => Stm rep -> m (Stm rep) Source #
Rename bound variables such that each is unique. The semantics of the binding is unaffected, under the assumption that the binding was correct to begin with. Any free variables are left untouched, as are the names in the pattern of the binding.
renameBody :: (Renameable rep, MonadFreshNames m) => Body rep -> m (Body rep) Source #
Rename bound variables such that each is unique. The semantics of the body is unaffected, under the assumption that the body was correct to begin with. Any free variables are left untouched.
renameLambda :: (Renameable rep, MonadFreshNames m) => Lambda rep -> m (Lambda rep) Source #
Rename bound variables such that each is unique. The semantics of the lambda is unaffected, under the assumption that the body was correct to begin with. Any free variables are left untouched. Note in particular that the parameters of the lambda are renamed.
renamePat :: (Rename dec, MonadFreshNames m) => Pat dec -> m (Pat dec) Source #
Produce an equivalent pattern but with each pattern element given a new name.
renameSomething :: (Rename a, MonadFreshNames m) => a -> m a Source #
Rename the bound variables in something (does not affect free variables).
renameBound :: [VName] -> RenameM a -> RenameM a Source #
Rename variables in binding position. The provided VNames are associated with new, fresh names in the renaming environment.
renameStmsWith :: (MonadFreshNames m, Renameable rep, Rename a) => Stms rep -> a -> m (Stms rep, a) Source #
Rename statements, then rename something within the scope of those statements.
Renaming annotations
The monad in which renaming is performed.
Instances
Applicative RenameM Source # | |
Functor RenameM Source # | |
Monad RenameM Source # | |
MonadFreshNames RenameM Source # | |
Defined in Futhark.Transform.Rename Methods getNameSource :: RenameM VNameSource Source # putNameSource :: VNameSource -> RenameM () Source # |
substituteRename :: Substitute a => a -> RenameM a Source #
Perform a renaming using the Substitute
instance. This only
works if the argument does not itself perform any name binding, but
it can save on boilerplate for simple types.
renamingStms :: Renameable rep => Stms rep -> (Stms rep -> RenameM a) -> RenameM a Source #
Rename some statements, then execute an action with the name substitutions induced by the statements active.
Members of class Rename
can be uniquely renamed.
Methods
rename :: a -> RenameM a Source #
Rename the given value such that it does not contain shadowing,
and has incorporated any substitutions present in the RenameM
environment.
Instances
type Renameable rep = (Rename (LetDec rep), Rename (ExpDec rep), Rename (BodyDec rep), Rename (FParamInfo rep), Rename (LParamInfo rep), Rename (RetType rep), Rename (BranchType rep), Rename (Op rep)) Source #
Representations in which all decorations are renameable.