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

Safe HaskellNone

HERMIT.Core

Contents

Synopsis

Generic Data Type

data CoreProg Source

A program is a telescope of nested binding groups. That is, each binding scopes over the remainder of the program. In GHC Core, programs are encoded as [CoreBind]. This data type is isomorphic.

Constructors

ProgNil

An empty program.

ProgCons CoreBind CoreProg

A binding group and the program it scopes over.

data CoreDef Source

A (potentially recursive) definition is an identifier and an expression. In GHC Core, recursive definitions are encoded as (Id, CoreExpr) pairs. This data type is isomorphic.

Constructors

Def Id CoreExpr 

type CoreTickish = Tickish IdSource

Unlike everything else, there is no synonym for Tickish Id provided by GHC, so we define one.

Equality

We define both syntactic equality and alpha equality.

Syntactic Equality

progSyntaxEq :: CoreProg -> CoreProg -> BoolSource

Syntactic Equality of programs.

bindSyntaxEq :: CoreBind -> CoreBind -> BoolSource

Syntactic Equality of binding groups.

defSyntaxEq :: CoreDef -> CoreDef -> BoolSource

Syntactic Equality of recursive definitions.

exprSyntaxEq :: CoreExpr -> CoreExpr -> BoolSource

Syntactic Equality of expressions.

altSyntaxEq :: CoreAlt -> CoreAlt -> BoolSource

Syntactic Equality of case alternatives.

typeSyntaxEq :: Type -> Type -> BoolSource

Syntactic Equality of Types.

coercionSyntaxEq :: Coercion -> Coercion -> BoolSource

Syntactic Equality of Coercions.

Alpha Equality

progAlphaEq :: CoreProg -> CoreProg -> BoolSource

Alpha equality of programs.

bindAlphaEq :: CoreBind -> CoreBind -> BoolSource

Alpha equality of binding groups.

defAlphaEq :: CoreDef -> CoreDef -> BoolSource

Alpha equality of recursive definitions.

exprAlphaEq :: CoreExpr -> CoreExpr -> BoolSource

Alpha equality of expressions.

altAlphaEq :: CoreAlt -> CoreAlt -> BoolSource

Alpha equality of case alternatives.

typeAlphaEq :: Type -> Type -> BoolSource

Alpha equality of types.

coercionAlphaEq :: Coercion -> Coercion -> BoolSource

Alpha equality of coercions.

Conversions to/from Core

defsToRecBind :: [CoreDef] -> CoreBindSource

Convert a list of recursive definitions into an (isomorphic) recursive binding group.

defToIdExpr :: CoreDef -> (Id, CoreExpr)Source

Convert a definition to an identifier/expression pair.

progToBinds :: CoreProg -> [CoreBind]Source

Get the list of bindings in a program.

bindsToProg :: [CoreBind] -> CoreProgSource

Build a program from a list of bindings. Note that bindings earlier in the list are considered scope over bindings later in the list.

bindToVarExprs :: CoreBind -> [(Var, CoreExpr)]Source

Extract the list of identifier/expression pairs from a binding group.

Collecting variable bindings

progIds :: CoreProg -> [Id]Source

List all identifiers bound at the top-level in a program.

bindVars :: CoreBind -> [Var]Source

List all variables bound in a binding group.

defId :: CoreDef -> IdSource

Return the identifier bound by a recursive definition.

altVars :: CoreAlt -> [Var]Source

List the variables bound by a case alternative.

Collecting free variables

The GHC Function exprFreeVars defined in CoreFVs only returns *locally-defined* free variables. In HERMIT, this is typically not what we want, so we define our own functions. We reuse some of the functionality in CoreFVs, but alas much of it is not exposed, so we have to reimplement some of it.

freeVarsProg :: CoreProg -> VarSetSource

Find all free variables in a program.

freeVarsBind :: CoreBind -> VarSetSource

Find all free identifiers in a binding group, which excludes any variables bound in the group.

freeVarsDef :: CoreDef -> VarSetSource

Find all free variables is a recursive definition, which excludes the bound variable.

freeVarsExpr :: CoreExpr -> VarSetSource

Find all free variables in an expression.

freeVarsAlt :: CoreAlt -> VarSetSource

Find all free variables in a case alternative, which excludes any variables bound in the alternative.

freeVarsType :: Type -> TyVarSetSource

Find all free variables in a type.

freeVarsCoercion :: Coercion -> VarSetSource

Find all free variables in a coercion.

localFreeVarsExpr :: CoreExpr -> VarSetSource

Find all locally defined free variables in an expression.

freeIdsExpr :: CoreExpr -> IdSetSource

Find all free identifiers in an expression.

localFreeIdsExpr :: CoreExpr -> VarSetSource

Find all locally defined free identifiers in an expression.

Utilities

isCoArg :: CoreExpr -> BoolSource

Returns True iff the expression is a Coercion expression at its top level.

exprKindOrType :: CoreExpr -> KindOrTypeSource

GHC's exprType function throws an error if applied to a Type. This function returns the Kind of a Type, but otherwise behaves as exprType.

exprTypeM :: Monad m => CoreExpr -> m TypeSource

GHC's exprType function throws an error if applied to a Type. This function catches that case as failure in an arbitrary monad.

endoFunType :: Monad m => CoreExpr -> m TypeSource

Return the domain/codomain type of an endofunction expression.

splitFunTypeM :: Monad m => Type -> m (Type, Type)Source

Return the domain and codomain types of a function type, if it is a function type.

funArgResTypes :: Monad m => CoreExpr -> m (Type, Type)Source

Return the domain and codomain types of a function expression.

funsWithInverseTypes :: MonadCatch m => CoreExpr -> CoreExpr -> m (Type, Type)Source

Check two expressions have types a -> b and b -> a, returning (a,b).

appCount :: CoreExpr -> IntSource

Count the number of nested applications.

mapAlts :: (CoreExpr -> CoreExpr) -> [CoreAlt] -> [CoreAlt]Source

Map a function over the RHS of each case alternative.

Crumbs

deprecatedLeftSibling :: Crumb -> Maybe CrumbSource

Converts a Crumb into the Crumb pointing to its left-sibling, if a such a Crumb exists. This is for backwards compatibility purposes with the old Int representation.

deprecatedRightSibling :: Crumb -> Maybe CrumbSource

Converts a Crumb into the Crumb pointing to its right-sibling, if a such a Crumb exists. This is for backwards compatibility purposes with the old Int representation.