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

Safe HaskellNone

Language.HERMIT.GHC

Contents

Synopsis

GHC Imports

Things that have been copied from GHC, or imported directly, for various reasons.

ppIdInfo :: Id -> IdInfo -> SDocSource

Pretty-print an identifier.

var2String :: Var -> StringSource

Convert a variable to a neat string for printing.

name2THName :: Name -> NameSource

Converts a GHC Name to a Template Haskell Name, going via a String.

var2THName :: Var -> NameSource

Converts an Var to a Template Haskell Name, going via a String.

cmpTHName2Name :: Name -> Name -> BoolSource

Hacks until we can find the correct way of doing these.

cmpString2Name :: String -> Name -> BoolSource

Hacks until we can find the correct way of doing these.

cmpTHName2Var :: Name -> Var -> BoolSource

Hacks until we can find the correct way of doing these.

cmpString2Var :: String -> Var -> BoolSource

Hacks until we can find the correct way of doing these.

unqualifiedVarName :: Var -> StringSource

Get the unqualified name from an Var.

findNameFromTH :: GlobalRdrEnv -> Name -> [Name]Source

This is hopeless O(n), because the we could not generate the OccNames that match, for use of the GHC OccEnv.

data Type

The key representation of types within the compiler

Constructors

TyVarTy Var

Vanilla type or kind variable (*never* a coercion variable)

AppTy Type Type

Type application to something other than a TyCon. Parameters:

1) Function: must not be a TyConApp, must be another AppTy, or TyVarTy

2) Argument type

TyConApp TyCon [KindOrType]

Application of a TyCon, including newtypes and synonyms. Invariant: saturated appliations of FunTyCon must use FunTy and saturated synonyms must use their own constructors. However, unsaturated FunTyCons do appear as TyConApps. Parameters:

1) Type constructor being applied to.

2) Type arguments. Might not have enough type arguments here to saturate the constructor. Even type synonyms are not necessarily saturated; for example unsaturated type synonyms can appear as the right hand side of a type synonym.

FunTy Type Type

Special case of TyConApp: TyConApp FunTyCon [t1, t2] See Note [Equality-constrained types]

ForAllTy Var Type

A polymorphic type

LitTy TyLit

Type literals are simillar to type constructors.

data GhcException

GHC's own exception type error messages all take the form:

      location: error

If the location is on the command line, or in GHC itself, then location=ghc. All of the error types below correspond to a location of ghc, except for ProgramError (where the string is assumed to contain a location already, so we don't print one).

Constructors

ProgramError String

An error in the user's code, probably.

exprArity :: CoreExpr -> Arity

An approximate, fast, version of exprEtaExpandArity