hermit-0.2.0.0: Haskell Equational Reasoning Model-to-Implementation Tunnel

Safe HaskellNone

Language.HERMIT.Primitive.AlphaConversion

Contents

Synopsis

Alpha-Renaming and Shadowing

externals :: [External]Source

Externals for alpha-renaming.

Alpha-Renaming

alpha :: (ExtendPath c Crumb, AddBindings c, BoundVars c) => Rewrite c HermitM CoreSource

Alpha rename any bindings at this node. Note: does not rename case alternatives unless invoked on the alternative.

alphaLam :: (ExtendPath c Crumb, AddBindings c, BoundVars c) => Maybe Name -> Rewrite c HermitM CoreExprSource

Alpha rename a lambda binder. Optionally takes a suggested new name.

alphaCaseBinder :: (ExtendPath c Crumb, AddBindings c, BoundVars c) => Maybe Name -> Rewrite c HermitM CoreExprSource

Alpha rename a case binder. Optionally takes a suggested new name.

alphaAltWith :: (ExtendPath c Crumb, AddBindings c, BoundVars c) => [Name] -> Rewrite c HermitM CoreAltSource

Rename the variables bound in a case alternative with the given list of suggested names.

alphaAltVars :: (ExtendPath c Crumb, AddBindings c, BoundVars c) => [Var] -> Rewrite c HermitM CoreAltSource

Rename the specified variables in a case alternative.

alphaAlt :: (ExtendPath c Crumb, AddBindings c, BoundVars c) => Rewrite c HermitM CoreAltSource

Rename all identifiers bound in a case alternative.

alphaCase :: (ExtendPath c Crumb, AddBindings c, BoundVars c) => Rewrite c HermitM CoreExprSource

Rename all identifiers bound in a case expression.

alphaLetWith :: (ExtendPath c Crumb, AddBindings c, BoundVars c) => [Name] -> Rewrite c HermitM CoreExprSource

Rename the identifiers bound in a Let with the given list of suggested names.

alphaLetVars :: (ExtendPath c Crumb, AddBindings c, BoundVars c) => [Var] -> Rewrite c HermitM CoreExprSource

Rename the specified variables bound in a let.

alphaLet :: (ExtendPath c Crumb, AddBindings c, BoundVars c) => Rewrite c HermitM CoreExprSource

Rename all identifiers bound in a Let.

alphaConsWith :: (ExtendPath c Crumb, AddBindings c) => [Name] -> Rewrite c HermitM CoreProgSource

Rename the identifiers bound in the top-level binding at the head of the program with the given list of suggested names.

Shadow Detection and Unshadowing

unshadow :: forall c. (ExtendPath c Crumb, AddBindings c, BoundVars c) => Rewrite c HermitM CoreSource

Rename local variables with manifestly unique names (x, x0, x1, ...). Does not rename top-level definitions.

visibleVarsT :: (BoundVars c, Monad m) => Translate c m CoreExpr (Set Var)Source

List all visible identifiers (in the expression or the context).

freshNameGenT :: (BoundVars c, Monad m) => Maybe Name -> Translate c m CoreExpr (String -> String)Source

If a name is provided replace the string with that, otherwise modify the string making sure to not clash with any visible variables.

freshNameGenAvoiding :: Maybe Name -> Set Var -> String -> StringSource

Use the optional argument if given, otherwise generate a new name avoiding clashes with the list of variables.

replaceVarR :: (ExtendPath c Crumb, AddBindings c, Injection a Core, MonadCatch m) => Var -> Var -> Rewrite c m aSource

Replace all occurrences of a specified variable. Arguments are the variable to replace and the replacement variable, respectively.