| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
HERMIT.GHC
Contents
- module GhcPlugins
- ppIdInfo :: Id -> IdInfo -> SDoc
- zapVarOccInfo :: Var -> Var
- var2String :: Var -> String
- thRdrNameGuesses :: Name -> [RdrName]
- varNameNS :: NameSpace
- isQualified :: String -> Bool
- cmpString2Name :: String -> Name -> Bool
- cmpString2Var :: String -> Var -> Bool
- fqName :: Name -> String
- uqName :: NamedThing nm => nm -> String
- findNamesFromString :: GlobalRdrEnv -> String -> [Name]
- alphaTyVars :: [TyVar]
- data Type :: *
- data TyLit :: *
- data GhcException :: *
- throwGhcException :: GhcException -> a
- exprArity :: CoreExpr -> Arity
- occurAnalyseExpr :: CoreExpr -> CoreExpr
- isKind :: Kind -> Bool
- isLiftedTypeKindCon :: TyCon -> Bool
- coAxiomName :: CoAxiom br -> Name
- type BranchIndex = Int
- data CoAxiom br :: * -> *
- data Branched :: *
- notElemVarSet :: Var -> VarSet -> Bool
- varSetToStrings :: VarSet -> [String]
- showVarSet :: VarSet -> String
- data Pair a :: * -> * = Pair {}
- bndrRuleAndUnfoldingVars :: Var -> VarSet
- runDsMtoCoreM :: ModGuts -> DsM a -> CoreM a
- runTcMtoCoreM :: ModGuts -> TcM a -> CoreM a
- buildTypeable :: ModGuts -> Type -> CoreM (Id, [CoreBind])
- buildDictionary :: ModGuts -> Id -> CoreM (Id, [CoreBind])
- eqExprX :: IdUnfoldingFun -> RnEnv2 -> CoreExpr -> CoreExpr -> Bool
- lookupRdrNameInModuleForPlugins :: HscEnv -> ModGuts -> ModuleName -> RdrName -> IO (Maybe Name)
- mkPhiTy :: [PredType] -> Type -> Type
- mkSigmaTy :: [TyVar] -> [PredType] -> Type -> Type
- getHscEnvCoreM :: CoreM HscEnv
GHC Imports
Things that have been copied from GHC, or imported directly, for various reasons.
module GhcPlugins
zapVarOccInfo :: Var -> Var Source
var2String :: Var -> String Source
Convert a variable to a neat string for printing (unqualfied name).
thRdrNameGuesses :: Name -> [RdrName]
isQualified :: String -> Bool Source
cmpString2Name :: String -> Name -> Bool Source
cmpString2Var :: String -> Var -> Bool Source
Compare a String to a Var for equality. See cmpString2Name.
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.
alphaTyVars :: [TyVar]
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 1) Function: must not be a 2) Argument type |
| TyConApp TyCon [KindOrType] | Application of a 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 |
| ForAllTy Var Type | A polymorphic type |
| LitTy TyLit | Type literals are similar to type constructors. |
data TyLit :: *
Constructors
| NumTyLit Integer | |
| StrTyLit FastString |
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 |
| 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 |
Instances
throwGhcException :: GhcException -> a
exprArity :: CoreExpr -> Arity
An approximate, fast, version of exprEtaExpandArity
occurAnalyseExpr :: CoreExpr -> CoreExpr
isLiftedTypeKindCon :: TyCon -> Bool
coAxiomName :: CoAxiom br -> Name Source
type BranchIndex = Int
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 :: * -> *
Instances
runDsMtoCoreM :: ModGuts -> DsM a -> CoreM a Source
runTcMtoCoreM :: ModGuts -> TcM a -> CoreM a Source
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.