| Safe Haskell | None | 
|---|
Language.HERMIT.Context
- data HermitC
- initHermitC :: ModGuts -> HermitC
- addAltBindings :: [Var] -> HermitC -> HermitC
- addBinding :: CoreBind -> HermitC -> HermitC
- addCaseBinding :: (Id, CoreExpr, CoreAlt) -> HermitC -> HermitC
- addLambdaBinding :: Var -> HermitC -> HermitC
- hermitBindings :: HermitC -> Map Var HermitBinding
- hermitDepth :: HermitC -> Int
- hermitPath :: HermitC -> AbsolutePath
- hermitModGuts :: HermitC -> ModGuts
- lookupHermitBinding :: Var -> HermitC -> Maybe HermitBinding
- boundVars :: HermitC -> [Var]
- boundIn :: Var -> HermitC -> Bool
- findBoundVars :: Name -> HermitC -> [Var]
- data HermitBinding
- hermitBindingDepth :: HermitBinding -> Int
The HERMIT Context
The HERMIT context, containing all bindings in scope and the current location in the AST. The bindings here are lazy by choice, so that we can avoid the cost of building the context if we never use it.
Instances
| PathContext HermitC | The HERMIT context stores an  | 
| Walker HermitC Core | |
| Extern (BiRewriteH Core) | |
| Extern (RewriteH Core) | |
| Extern (TranslateH Core String) | |
| Extern (TranslateH Core ()) | |
| Extern (TranslateH Core Path) | 
Adding to the Context
addAltBindings :: [Var] -> HermitC -> HermitCSource
Add the variables bound by a DataCon in a case. Like lambda bindings,
 in that we know nothing about them, but all bound at the same depth,
 so we cannot just fold addLambdaBinding over the list.
addBinding :: CoreBind -> HermitC -> HermitCSource
Add all bindings in a binding group to a context.
addCaseBinding :: (Id, CoreExpr, CoreAlt) -> HermitC -> HermitCSource
Add the bindings for a specific case alternative.
addLambdaBinding :: Var -> HermitC -> HermitCSource
Add a lambda bound variable to a context. All that is known is the variable, which may shadow something. If so, we don't worry about that here, it is instead checked during inlining.
Reading from the Context
hermitBindings :: HermitC -> Map Var HermitBindingSource
All (important) bindings in scope.
hermitDepth :: HermitC -> IntSource
The depth of the bindings.
hermitPath :: HermitC -> AbsolutePathSource
The AbsolutePath to the current node from the root.
hermitModGuts :: HermitC -> ModGutsSource
The ModGuts of the current module.
lookupHermitBinding :: Var -> HermitC -> Maybe HermitBindingSource
Lookup the binding for a variable in a context.
findBoundVars :: Name -> HermitC -> [Var]Source
List all variables bound in the context that match the given name.
Bindings
data HermitBinding Source
HERMIT's representation of variable bindings.
Constructors
| BIND Int Bool CoreExpr | Binding depth, whether it is recursive, and the bound value (which cannot be inlined without checking for scoping issues). | 
| LAM Int | For a lambda binding you only know the depth. | 
| CASE Int CoreExpr (AltCon, [Id]) | For case wildcard binders. We store both the scrutinised expression,
   and the case alternative  | 
hermitBindingDepth :: HermitBinding -> IntSource
Get the depth of a binding.