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

Safe HaskellNone

Language.HERMIT.Context

Contents

Synopsis

The HERMIT Context

data HermitC Source

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.

initHermitC :: ModGuts -> HermitCSource

Create the initial HERMIT HermitC by providing a ModGuts.

Adding to the Context

(@@) :: HermitC -> Int -> HermitCSource

Update the context by extending the stored AbsolutePath to a child.

addAltBindings :: [Id] -> HermitC -> HermitCSource

Add the identifiers 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.

boundVars :: HermitC -> [Var]Source

List all the variables bound in a context.

boundIn :: Var -> HermitC -> BoolSource

Determine if a variable is bound 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 AltCon (which can be converted to Constructor or Literal) and identifiers.

hermitBindingDepth :: HermitBinding -> IntSource

Get the depth of a binding.