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

Safe HaskellNone
LanguageHaskell2010

HERMIT.GHC

Contents

Synopsis

GHC Imports

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

module GhcPlugins

ppIdInfo :: Id -> IdInfo -> SDoc Source

Pretty-print an identifier.

zapVarOccInfo :: Var -> Var Source

Erase all OccInfo in a variable if it is is an Id, or do nothing if it's a TyVar or CoVar (which have no OccInfo).

var2String :: Var -> String Source

Convert a variable to a neat string for printing (unqualfied name).

varNameNS :: NameSpace Source

Rename this namespace, as varName is already a function in Var.

cmpString2Name :: String -> Name -> Bool Source

Compare a String to a Name for equality. Strings containing a period are assumed to be fully qualified names. (Except for ".", which is an unqualified reference to composition.)

cmpString2Var :: String -> Var -> Bool Source

Compare a String to a Var for equality. See cmpString2Name.

fqName :: Name -> String Source

Get the fully qualified name from a Name.

uqName :: NamedThing nm => nm -> String Source

Get the unqualified name from a NamedThing.

findNamesFromString :: GlobalRdrEnv -> String -> [Name] Source

Find Names matching a given fully qualified or unqualified name.

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 similar 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

PhaseFailed String ExitCode 
Signal Int

Some other fatal signal (SIGHUP,SIGTERM)

UsageError String

Prints the short usage msg after the error

CmdLineError String

A problem with the command line arguments, but don't print usage.

Panic String

The impossible happened.

PprPanic String SDoc 
Sorry String

The user tickled something that's known not to work yet, but we're not counting it as a bug.

PprSorry String SDoc 
InstallationError String

An installation problem.

ProgramError String

An error in the user's code, probably.

PprProgramError String SDoc 

exprArity :: CoreExpr -> Arity

An approximate, fast, version of exprEtaExpandArity

isKind :: Kind -> Bool

Is this a kind (i.e. a type-of-types)?

data CoAxiom br :: * -> *

A CoAxiom is a "coercion constructor", i.e. a named equality axiom.

Instances

Eq (CoAxiom br) 
Typeable * br => Data (CoAxiom br) 
Ord (CoAxiom br) 
NamedThing (CoAxiom br) 
Uniquable (CoAxiom br) 
Outputable (CoAxiom br) 
Typeable (* -> *) CoAxiom 

data Branched :: *

Instances

notElemVarSet :: Var -> VarSet -> Bool Source

Determine if a Var is not an element of a VarSet.

varSetToStrings :: VarSet -> [String] Source

Convert a VarSet to a list of user-readable strings.

showVarSet :: VarSet -> String Source

Show a human-readable version of a VarSet.

data Pair a :: * -> *

Constructors

Pair 

Fields

pFst :: a
 
pSnd :: a
 

buildDictionary :: ModGuts -> Id -> CoreM (Id, [CoreBind]) Source

Build a dictionary for the given

lookupRdrNameInModuleForPlugins :: HscEnv -> ModGuts -> ModuleName -> RdrName -> IO (Maybe Name) Source

Finds the Name corresponding to the given RdrName in the context of the ModuleName. Returns Nothing if no such Name could be found. Any other condition results in an exception:

  • If the module could not be found
  • If we could not determine the imports of the module

This is adapted from GHC's function of the same name, but using initTcFromModGuts instead of initTcInteractive.

mkSigmaTy :: [TyVar] -> [PredType] -> Type -> Type