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

Safe HaskellNone

Language.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.

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.

bindToIdExprs :: CoreBind -> [(Id, CoreExpr)]Source

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

Utilities

isCoArg :: CoreExpr -> BoolSource

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

exprTypeOrKind :: CoreExpr -> TypeSource

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

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

Return the domain/codomain type of an endofunction expression.

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.

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.