ghc-6.12.1: The GHC APISource codeContentsIndex
HscTypes
Contents
Ghc monad stuff
Sessions and compilation state
Callbacks
Information about modules
Information about the module being compiled
State relating to modules in this package
State relating to known packages
Annotations
Interactive context
Interfaces
Fixity
TyThings and type environments
MonadThings
Information on imports and exports
Warnings
Linker stuff
Program coverage
Breakpoints
Vectorisation information
Description
Types for the per-module compiler
Synopsis
newtype Ghc a = Ghc {
unGhc :: Session -> IO a
}
newtype GhcT m a = GhcT {
unGhcT :: Session -> m a
}
liftGhcT :: Monad m => m a -> GhcT m a
class (Functor m, MonadIO m, WarnLogMonad m, ExceptionMonad m) => GhcMonad m where
getSession :: m HscEnv
setSession :: HscEnv -> m ()
class Monad m => WarnLogMonad m where
setWarnings :: WarningMessages -> m ()
getWarnings :: m WarningMessages
liftIO :: MonadIO m => IO a -> m a
ioMsgMaybe :: GhcMonad m => IO (Messages, Maybe a) -> m a
ioMsg :: GhcMonad m => IO (Messages, a) -> m a
logWarnings :: WarnLogMonad m => WarningMessages -> m ()
clearWarnings :: WarnLogMonad m => m ()
hasWarnings :: WarnLogMonad m => m Bool
data SourceError
data GhcApiError
mkSrcErr :: ErrorMessages -> SourceError
srcErrorMessages :: SourceError -> ErrorMessages
mkApiErr :: SDoc -> GhcApiError
throwOneError :: MonadIO m => ErrMsg -> m ab
handleSourceError :: ExceptionMonad m => (SourceError -> m a) -> m a -> m a
reflectGhc :: Ghc a -> Session -> IO a
reifyGhc :: (Session -> IO a) -> Ghc a
handleFlagWarnings :: GhcMonad m => DynFlags -> [Located String] -> m ()
data Session = Session !(IORef HscEnv) !(IORef WarningMessages)
withSession :: GhcMonad m => (HscEnv -> m a) -> m a
modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m ()
withTempSession :: GhcMonad m => (HscEnv -> HscEnv) -> m a -> m a
data HscEnv = HscEnv {
hsc_dflags :: DynFlags
hsc_callbacks :: GhcApiCallbacks
hsc_targets :: [Target]
hsc_mod_graph :: ModuleGraph
hsc_IC :: InteractiveContext
hsc_HPT :: HomePackageTable
hsc_EPS :: !(IORef ExternalPackageState)
hsc_NC :: !(IORef NameCache)
hsc_FC :: !(IORef FinderCache)
hsc_MLC :: !(IORef ModLocationCache)
hsc_OptFuel :: OptFuelState
hsc_type_env_var :: Maybe (Module, IORef TypeEnv)
hsc_global_rdr_env :: GlobalRdrEnv
hsc_global_type_env :: TypeEnv
}
hscEPS :: HscEnv -> IO ExternalPackageState
type FinderCache = ModuleNameEnv FindResult
data FindResult
= Found ModLocation Module
| NoPackage PackageId
| FoundMultiple [PackageId]
| NotFound [FilePath] (Maybe PackageId) [PackageId] [PackageId]
| NotFoundInPackage PackageId
type ModLocationCache = ModuleEnv ModLocation
data Target = Target {
targetId :: TargetId
targetAllowObjCode :: Bool
targetContents :: Maybe (StringBuffer, ClockTime)
}
data TargetId
= TargetModule ModuleName
| TargetFile FilePath (Maybe Phase)
pprTarget :: Target -> SDoc
pprTargetId :: TargetId -> SDoc
type ModuleGraph = [ModSummary]
emptyMG :: ModuleGraph
data GhcApiCallbacks = GhcApiCallbacks {
reportModuleCompilationResult :: GhcMonad m => ModSummary -> Maybe SourceError -> m ()
}
withLocalCallbacks :: GhcMonad m => (GhcApiCallbacks -> GhcApiCallbacks) -> m a -> m a
data ModDetails = ModDetails {
md_exports :: [AvailInfo]
md_types :: !TypeEnv
md_insts :: ![Instance]
md_fam_insts :: ![FamInst]
md_rules :: ![CoreRule]
md_anns :: ![Annotation]
md_vect_info :: !VectInfo
}
emptyModDetails :: ModDetails
data ModGuts = ModGuts {
mg_module :: !Module
mg_boot :: IsBootInterface
mg_exports :: ![AvailInfo]
mg_deps :: !Dependencies
mg_dir_imps :: !ImportedMods
mg_used_names :: !NameSet
mg_rdr_env :: !GlobalRdrEnv
mg_fix_env :: !FixityEnv
mg_types :: !TypeEnv
mg_insts :: ![Instance]
mg_fam_insts :: ![FamInst]
mg_rules :: ![CoreRule]
mg_binds :: ![CoreBind]
mg_foreign :: !ForeignStubs
mg_warns :: !Warnings
mg_anns :: [Annotation]
mg_hpc_info :: !HpcInfo
mg_modBreaks :: !ModBreaks
mg_vect_info :: !VectInfo
mg_inst_env :: InstEnv
mg_fam_inst_env :: FamInstEnv
}
data CoreModule = CoreModule {
cm_module :: !Module
cm_types :: !TypeEnv
cm_binds :: [CoreBind]
cm_imports :: ![Module]
}
data CgGuts = CgGuts {
cg_module :: !Module
cg_tycons :: [TyCon]
cg_binds :: [CoreBind]
cg_dir_imps :: ![Module]
cg_foreign :: !ForeignStubs
cg_dep_pkgs :: ![PackageId]
cg_hpc_info :: !HpcInfo
cg_modBreaks :: !ModBreaks
}
data ForeignStubs
= NoStubs
| ForeignStubs SDoc SDoc
type ImportedMods = ModuleEnv [(ModuleName, Bool, SrcSpan)]
data ModSummary = ModSummary {
ms_mod :: Module
ms_hsc_src :: HscSource
ms_location :: ModLocation
ms_hs_date :: ClockTime
ms_obj_date :: Maybe ClockTime
ms_srcimps :: [Located (ImportDecl RdrName)]
ms_imps :: [Located (ImportDecl RdrName)]
ms_hspp_file :: FilePath
ms_hspp_opts :: DynFlags
ms_hspp_buf :: Maybe StringBuffer
}
ms_mod_name :: ModSummary -> ModuleName
showModMsg :: HscTarget -> Bool -> ModSummary -> String
isBootSummary :: ModSummary -> Bool
msHsFilePath :: ModSummary -> FilePath
msHiFilePath :: ModSummary -> FilePath
msObjFilePath :: ModSummary -> FilePath
data HscSource
= HsSrcFile
| HsBootFile
| ExtCoreFile
isHsBoot :: HscSource -> Bool
hscSourceString :: HscSource -> String
type HomePackageTable = ModuleNameEnv HomeModInfo
data HomeModInfo = HomeModInfo {
hm_iface :: !ModIface
hm_details :: !ModDetails
hm_linkable :: !(Maybe Linkable)
}
emptyHomePackageTable :: HomePackageTable
hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([Instance], [FamInst])
hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule]
hptVectInfo :: HscEnv -> VectInfo
data ExternalPackageState = EPS {
eps_is_boot :: !(ModuleNameEnv (ModuleName, IsBootInterface))
eps_PIT :: !PackageIfaceTable
eps_PTE :: !PackageTypeEnv
eps_inst_env :: !PackageInstEnv
eps_fam_inst_env :: !PackageFamInstEnv
eps_rule_base :: !PackageRuleBase
eps_vect_info :: !PackageVectInfo
eps_ann_env :: !PackageAnnEnv
eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv)
eps_stats :: !EpsStats
}
data EpsStats = EpsStats {
n_ifaces_in :: !Int
n_decls_in :: !Int
n_decls_out :: !Int
n_rules_in :: !Int
n_rules_out :: !Int
n_insts_in :: !Int
n_insts_out :: !Int
}
addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
type PackageTypeEnv = TypeEnv
type PackageIfaceTable = ModuleEnv ModIface
emptyPackageIfaceTable :: PackageIfaceTable
lookupIfaceByModule :: DynFlags -> HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
emptyModIface :: Module -> ModIface
type PackageInstEnv = InstEnv
type PackageRuleBase = RuleBase
prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv
data InteractiveContext = InteractiveContext {
ic_toplev_scope :: [Module]
ic_exports :: [Module]
ic_rn_gbl_env :: GlobalRdrEnv
ic_tmp_ids :: [Id]
ic_tyvars :: TyVarSet
ic_resume :: [Resume]
ic_cwd :: Maybe FilePath
}
emptyInteractiveContext :: InteractiveContext
icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified
extendInteractiveContext :: InteractiveContext -> [Id] -> TyVarSet -> InteractiveContext
substInteractiveContext :: InteractiveContext -> TvSubst -> InteractiveContext
mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified
pprModulePrefix :: PprStyle -> Module -> OccName -> SDoc
data ModIface = ModIface {
mi_module :: !Module
mi_iface_hash :: !Fingerprint
mi_mod_hash :: !Fingerprint
mi_orphan :: !WhetherHasOrphans
mi_finsts :: !WhetherHasFamInst
mi_boot :: !IsBootInterface
mi_deps :: Dependencies
mi_usages :: [Usage]
mi_exports :: ![IfaceExport]
mi_exp_hash :: !Fingerprint
mi_fixities :: [(OccName, Fixity)]
mi_warns :: Warnings
mi_anns :: [IfaceAnnotation]
mi_decls :: [(Fingerprint, IfaceDecl)]
mi_globals :: !(Maybe GlobalRdrEnv)
mi_insts :: [IfaceInst]
mi_fam_insts :: [IfaceFamInst]
mi_rules :: [IfaceRule]
mi_orphan_hash :: !Fingerprint
mi_vect_info :: !IfaceVectInfo
mi_warn_fn :: Name -> Maybe WarningTxt
mi_fix_fn :: OccName -> Fixity
mi_hash_fn :: OccName -> Maybe (OccName, Fingerprint)
mi_hpc :: !AnyHpcUsage
}
mkIfaceWarnCache :: Warnings -> Name -> Maybe WarningTxt
mkIfaceHashCache :: [(Fingerprint, IfaceDecl)] -> OccName -> Maybe (OccName, Fingerprint)
mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Fixity
emptyIfaceWarnCache :: Name -> Maybe WarningTxt
type FixityEnv = NameEnv FixItem
data FixItem = FixItem OccName Fixity
lookupFixity :: FixityEnv -> Name -> Fixity
emptyFixityEnv :: FixityEnv
data TyThing
= AnId Id
| ADataCon DataCon
| ATyCon TyCon
| AClass Class
tyThingClass :: TyThing -> Class
tyThingTyCon :: TyThing -> TyCon
tyThingDataCon :: TyThing -> DataCon
tyThingId :: TyThing -> Id
implicitTyThings :: TyThing -> [TyThing]
isImplicitTyThing :: TyThing -> Bool
type TypeEnv = NameEnv TyThing
lookupType :: DynFlags -> HomePackageTable -> PackageTypeEnv -> Name -> Maybe TyThing
lookupTypeHscEnv :: HscEnv -> Name -> IO (Maybe TyThing)
mkTypeEnv :: [TyThing] -> TypeEnv
emptyTypeEnv :: TypeEnv
extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
lookupTypeEnv :: TypeEnv -> Name -> Maybe TyThing
typeEnvElts :: TypeEnv -> [TyThing]
typeEnvClasses :: TypeEnv -> [Class]
typeEnvTyCons :: TypeEnv -> [TyCon]
typeEnvIds :: TypeEnv -> [Id]
typeEnvDataCons :: TypeEnv -> [DataCon]
class Monad m => MonadThings m where
lookupThing :: Name -> m TyThing
lookupId :: Name -> m Id
lookupDataCon :: Name -> m DataCon
lookupTyCon :: Name -> m TyCon
lookupClass :: Name -> m Class
type WhetherHasOrphans = Bool
type IsBootInterface = Bool
data Usage
= UsagePackageModule {
usg_mod :: Module
usg_mod_hash :: Fingerprint
}
| UsageHomeModule {
usg_mod_name :: ModuleName
usg_mod_hash :: Fingerprint
usg_entities :: [(OccName, Fingerprint)]
usg_exports :: Maybe Fingerprint
}
data Dependencies = Deps {
dep_mods :: [(ModuleName, IsBootInterface)]
dep_pkgs :: [PackageId]
dep_orphs :: [Module]
dep_finsts :: [Module]
}
noDependencies :: Dependencies
data NameCache = NameCache {
nsUniqs :: UniqSupply
nsNames :: OrigNameCache
nsIPs :: OrigIParamCache
}
type OrigNameCache = ModuleEnv (OccEnv Name)
type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name)
type Avails = [AvailInfo]
availsToNameSet :: [AvailInfo] -> NameSet
availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfo
availName :: GenAvailInfo name -> name
availNames :: GenAvailInfo name -> [name]
data GenAvailInfo name
= Avail name
| AvailTC name [name]
type AvailInfo = GenAvailInfo Name
type RdrAvailInfo = GenAvailInfo OccName
type IfaceExport = (Module, [GenAvailInfo OccName])
data Warnings
= NoWarnings
| WarnAll WarningTxt
| WarnSome [(OccName, WarningTxt)]
data WarningTxt
= WarningTxt [FastString]
| DeprecatedTxt [FastString]
plusWarns :: Warnings -> Warnings -> Warnings
data Linkable = LM {
linkableTime :: ClockTime
linkableModule :: Module
linkableUnlinked :: [Unlinked]
}
isObjectLinkable :: Linkable -> Bool
data Unlinked
= DotO FilePath
| DotA FilePath
| DotDLL FilePath
| BCOs CompiledByteCode ModBreaks
data CompiledByteCode
isObject :: Unlinked -> Bool
nameOfObject :: Unlinked -> FilePath
isInterpretable :: Unlinked -> Bool
byteCodeOfObject :: Unlinked -> CompiledByteCode
data HpcInfo
= HpcInfo {
hpcInfoTickCount :: Int
hpcInfoHash :: Int
}
| NoHpcInfo {
hpcUsed :: AnyHpcUsage
}
emptyHpcInfo :: AnyHpcUsage -> HpcInfo
isHpcUsed :: HpcInfo -> AnyHpcUsage
type AnyHpcUsage = Bool
data ModBreaks = ModBreaks {
modBreaks_flags :: BreakArray
modBreaks_locs :: !(Array BreakIndex SrcSpan)
modBreaks_vars :: !(Array BreakIndex [OccName])
}
type BreakIndex = Int
emptyModBreaks :: ModBreaks
data VectInfo = VectInfo {
vectInfoVar :: VarEnv (Var, Var)
vectInfoTyCon :: NameEnv (TyCon, TyCon)
vectInfoDataCon :: NameEnv (DataCon, DataCon)
vectInfoPADFun :: NameEnv (TyCon, Var)
vectInfoIso :: NameEnv (TyCon, Var)
}
data IfaceVectInfo = IfaceVectInfo {
ifaceVectInfoVar :: [Name]
ifaceVectInfoTyCon :: [Name]
ifaceVectInfoTyConReuse :: [Name]
}
noVectInfo :: VectInfo
plusVectInfo :: VectInfo -> VectInfo -> VectInfo
noIfaceVectInfo :: IfaceVectInfo
Ghc monad stuff
newtype Ghc a Source
A minimal implementation of a GhcMonad. If you need a custom monad, e.g., to maintain additional state consider wrapping this monad or using GhcT.
Constructors
Ghc
unGhc :: Session -> IO a
show/hide Instances
newtype GhcT m a Source

A monad transformer to add GHC specific features to another monad.

Note that the wrapped monad must support IO and handling of exceptions.

Constructors
GhcT
unGhcT :: Session -> m a
show/hide Instances
liftGhcT :: Monad m => m a -> GhcT m aSource
class (Functor m, MonadIO m, WarnLogMonad m, ExceptionMonad m) => GhcMonad m whereSource

A monad that has all the features needed by GHC API calls.

In short, a GHC monad

  • allows embedding of IO actions,
  • can log warnings,
  • allows handling of (extensible) exceptions, and
  • maintains a current session.

If you do not use Ghc or GhcT, make sure to call GHC.initGhcMonad before any call to the GHC API functions can occur.

Methods
getSession :: m HscEnvSource
setSession :: HscEnv -> m ()Source
show/hide Instances
class Monad m => WarnLogMonad m whereSource
A monad that allows logging of warnings.
Methods
setWarnings :: WarningMessages -> m ()Source
getWarnings :: m WarningMessagesSource
show/hide Instances
liftIO :: MonadIO m => IO a -> m aSource
ioMsgMaybe :: GhcMonad m => IO (Messages, Maybe a) -> m aSource

Lift an IO action returning errors messages into a GhcMonad.

In order to reduce dependencies to other parts of the compiler, functions outside the main parts of GHC return warnings and errors as a parameter and signal success via by wrapping the result in a Maybe type. This function logs the returned warnings and propagates errors as exceptions (of type SourceError).

This function assumes the following invariants:

1. If the second result indicates success (is of the form 'Just x'), there must be no error messages in the first result.

2. If there are no error messages, but the second result indicates failure there should be warnings in the first result. That is, if the action failed, it must have been due to the warnings (i.e., -Werror).

ioMsg :: GhcMonad m => IO (Messages, a) -> m aSource

Lift a non-failing IO action into a GhcMonad.

Like ioMsgMaybe, but assumes that the action will never return any error messages.

logWarnings :: WarnLogMonad m => WarningMessages -> m ()Source
clearWarnings :: WarnLogMonad m => m ()Source
Clear the log of Warnings.
hasWarnings :: WarnLogMonad m => m BoolSource
Returns true if there were any warnings.
data SourceError Source

A source error is an error that is caused by one or more errors in the source code. A SourceError is thrown by many functions in the compilation pipeline. Inside GHC these errors are merely printed via log_action, but API clients may treat them differently, for example, insert them into a list box. If you want the default behaviour, use the idiom:

 handleSourceError printExceptionAndWarnings $ do
   ... api calls that may fail ...

The SourceErrors error messages can be accessed via srcErrorMessages. This list may be empty if the compiler failed due to -Werror (Opt_WarnIsError).

See printExceptionAndWarnings for more information on what to take care of when writing a custom error handler.

show/hide Instances
data GhcApiError Source
XXX: what exactly is an API error?
show/hide Instances
mkSrcErr :: ErrorMessages -> SourceErrorSource
srcErrorMessages :: SourceError -> ErrorMessagesSource
mkApiErr :: SDoc -> GhcApiErrorSource
throwOneError :: MonadIO m => ErrMsg -> m abSource
handleSourceErrorSource
:: ExceptionMonad m
=> SourceError -> m aaction to perform
-> m a
-> m a
Perform the given action and call the exception handler if the action throws a SourceError. See SourceError for more information.
reflectGhc :: Ghc a -> Session -> IO aSource

Reflect a computation in the Ghc monad into the IO monad.

You can use this to call functions returning an action in the Ghc monad inside an IO action. This is needed for some (too restrictive) callback arguments of some library functions:

 libFunc :: String -> (Int -> IO a) -> IO a
 ghcFunc :: Int -> Ghc a

 ghcFuncUsingLibFunc :: String -> Ghc a -> Ghc a
 ghcFuncUsingLibFunc str =
   reifyGhc $ \s ->
     libFunc $ \i -> do
       reflectGhc (ghcFunc i) s
reifyGhc :: (Session -> IO a) -> Ghc aSource
handleFlagWarnings :: GhcMonad m => DynFlags -> [Located String] -> m ()Source
Sessions and compilation state
data Session Source
The Session is a handle to the complete state of a compilation session. A compilation session consists of a set of modules constituting the current program or library, the context for interactive evaluation, and various caches.
Constructors
Session !(IORef HscEnv) !(IORef WarningMessages)
withSession :: GhcMonad m => (HscEnv -> m a) -> m aSource
Call the argument with the current session.
modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m ()Source
Set the current session to the result of applying the current session to the argument.
withTempSession :: GhcMonad m => (HscEnv -> HscEnv) -> m a -> m aSource
Call an action with a temporarily modified Session.
data HscEnv Source

Hscenv is like Session, except that some of the fields are immutable. An HscEnv is used to compile a single module from plain Haskell source code (after preprocessing) to either C, assembly or C--. Things like the module graph don't change during a single compilation.

Historical note: "hsc" used to be the name of the compiler binary, when there was a separate driver and compiler. To compile a single module, the driver would invoke hsc on the source code... so nowadays we think of hsc as the layer of the compiler that deals with compiling a single module.

Constructors
HscEnv
hsc_dflags :: DynFlagsThe dynamic flag settings
hsc_callbacks :: GhcApiCallbacksCallbacks for the GHC API.
hsc_targets :: [Target]The targets (or roots) of the current session
hsc_mod_graph :: ModuleGraphThe module graph of the current session
hsc_IC :: InteractiveContextThe context for evaluating interactive statements
hsc_HPT :: HomePackageTable

The home package table describes already-compiled home-package modules, excluding the module we are compiling right now. (In one-shot mode the current module is the only home-package module, so hsc_HPT is empty. All other modules count as "external-package" modules. However, even in GHCi mode, hi-boot interfaces are demand-loaded into the external-package table.)

hsc_HPT is not mutable because we only demand-load external packages; the home package is eagerly loaded, module by module, by the compilation manager.

The HPT may contain modules compiled earlier by --make but not actually below the current module in the dependency graph.

hsc_EPS :: !(IORef ExternalPackageState)Information about the currently loaded external packages. This is mutable because packages will be demand-loaded during a compilation run as required.
hsc_NC :: !(IORef NameCache)As with hsc_EPS, this is side-effected by compiling to reflect sucking in interface files. They cache the state of external interface files, in effect.
hsc_FC :: !(IORef FinderCache)The cached result of performing finding in the file system
hsc_MLC :: !(IORef ModLocationCache)This caches the location of modules, so we don't have to search the filesystem multiple times. See also hsc_FC.
hsc_OptFuel :: OptFuelStateSettings to control the use of "optimization fuel": by limiting the number of transformations, we can use binary search to help find compiler bugs.
hsc_type_env_var :: Maybe (Module, IORef TypeEnv)Used for one-shot compilation only, to initialise the IfGblEnv. See TcRnTypes.tcg_type_env_var for TcRunTypes.TcGblEnv
hsc_global_rdr_env :: GlobalRdrEnvA mapping from RdrNames that are in global scope during the compilation of the current file to more detailed information about those names. Not necessarily just the names directly imported by the module being compiled!
hsc_global_type_env :: TypeEnvTyping information about all those things in global scope. Not necessarily just the things directly imported by the module being compiled!
hscEPS :: HscEnv -> IO ExternalPackageStateSource
type FinderCache = ModuleNameEnv FindResultSource

The FinderCache maps home module names to the result of searching for that module. It records the results of searching for modules along the search path. On :load, we flush the entire contents of this cache.

Although the FinderCache range is FindResult for convenience , in fact it will only ever contain Found or NotFound entries.

data FindResult Source
The result of searching for an imported module.
Constructors
Found ModLocation ModuleThe module was found
NoPackage PackageIdThe requested package was not found
FoundMultiple [PackageId]_Error_: both in multiple packages
NotFound [FilePath] (Maybe PackageId) [PackageId] [PackageId]The module was not found, including either * the specified places were searched * the package that this module should have been in * list of packages in which the module was hidden, * list of hidden packages containing this module
NotFoundInPackage PackageIdThe module was not found in this package
type ModLocationCache = ModuleEnv ModLocationSource
Cache that remembers where we found a particular module. Contains both home modules and package modules. On :load, only home modules are purged from this cache.
data Target Source

A compilation target.

A target may be supplied with the actual text of the module. If so, use this instead of the file contents (this is for use in an IDE where the file hasn't been saved by the user yet).

Constructors
Target
targetId :: TargetIdmodule or filename
targetAllowObjCode :: Boolobject code allowed?
targetContents :: Maybe (StringBuffer, ClockTime)in-memory text buffer?
show/hide Instances
data TargetId Source
Constructors
TargetModule ModuleNameA module name: search for the file
TargetFile FilePath (Maybe Phase)A filename: preprocess & parse it to find the module name. If specified, the Phase indicates how to compile this file (which phase to start from). Nothing indicates the starting phase should be determined from the suffix of the filename.
show/hide Instances
pprTarget :: Target -> SDocSource
pprTargetId :: TargetId -> SDocSource
type ModuleGraph = [ModSummary]Source

A ModuleGraph contains all the nodes from the home package (only). There will be a node for each source module, plus a node for each hi-boot module.

The graph is not necessarily stored in topologically-sorted order. Use GHC.topSortModuleGraph and Digraph.flattenSCC to achieve this.

emptyMG :: ModuleGraphSource
Callbacks
data GhcApiCallbacks Source

These functions are called in various places of the GHC API.

API clients can override any of these callbacks to change GHC's default behaviour.

Constructors
GhcApiCallbacks
reportModuleCompilationResult :: GhcMonad m => ModSummary -> Maybe SourceError -> m ()

Called by load after the compilating of each module.

The default implementation simply prints all warnings and errors to stderr. Don't forget to call clearWarnings when implementing your own call.

The first argument is the module that was compiled.

The second argument is Nothing if no errors occured, but there may have been warnings. If it is Just err at least one error has occured. If srcErrorMessages is empty, compilation failed due to -Werror.

withLocalCallbacks :: GhcMonad m => (GhcApiCallbacks -> GhcApiCallbacks) -> m a -> m aSource
Temporarily modify the callbacks. After the action is executed all callbacks are reset (not, however, any other modifications to the session state.)
Information about modules
data ModDetails Source
The ModDetails is essentially a cache for information in the ModIface for home modules only. Information relating to packages will be loaded into global environments in ExternalPackageState.
Constructors
ModDetails
md_exports :: [AvailInfo]
md_types :: !TypeEnvLocal type environment for this particular module
md_insts :: ![Instance]DFunIds for the instances in this module
md_fam_insts :: ![FamInst]
md_rules :: ![CoreRule]Domain may include Ids from other modules
md_anns :: ![Annotation]Annotations present in this module: currently they only annotate things also declared in this module
md_vect_info :: !VectInfoModule vectorisation information
emptyModDetails :: ModDetailsSource
data ModGuts Source
A ModGuts is carried through the compiler, accumulating stuff as it goes There is only one ModGuts at any time, the one for the module being compiled right now. Once it is compiled, a ModIface and ModDetails are extracted and the ModGuts is dicarded.
Constructors
ModGuts
mg_module :: !ModuleModule being compiled
mg_boot :: IsBootInterfaceWhether it's an hs-boot module
mg_exports :: ![AvailInfo]What it exports
mg_deps :: !DependenciesWhat it depends on, directly or otherwise
mg_dir_imps :: !ImportedModsDirectly-imported modules; used to generate initialisation code
mg_used_names :: !NameSetWhat the module needed (used in MkIface.mkIface)
mg_rdr_env :: !GlobalRdrEnvTop-level lexical environment
mg_fix_env :: !FixityEnvFixities declared in this module TODO: I'm unconvinced this is actually used anywhere
mg_types :: !TypeEnvTypes declared in this module
mg_insts :: ![Instance]Class instances declared in this module
mg_fam_insts :: ![FamInst]Family instances declared in this module
mg_rules :: ![CoreRule]Before the core pipeline starts, contains rules declared in this module. After the core pipeline starts, it is changed to contain all known rules for those things imported
mg_binds :: ![CoreBind]Bindings for this module
mg_foreign :: !ForeignStubsForeign exports declared in this module
mg_warns :: !WarningsWarnings declared in the module
mg_anns :: [Annotation]Annotations declared in this module
mg_hpc_info :: !HpcInfoCoverage tick boxes in the module
mg_modBreaks :: !ModBreaksBreakpoints for the module
mg_vect_info :: !VectInfoPool of vectorised declarations in the module
mg_inst_env :: InstEnvClass instance environment from home-package modules (including this one); c.f. tcg_inst_env
mg_fam_inst_env :: FamInstEnvType-family instance enviroment for home-package modules (including this one); c.f. tcg_fam_inst_env
data CoreModule Source
A CoreModule consists of just the fields of a ModGuts that are needed for the GHC.compileToCoreModule interface.
Constructors
CoreModule
cm_module :: !ModuleModule name
cm_types :: !TypeEnvType environment for types declared in this module
cm_binds :: [CoreBind]Declarations
cm_imports :: ![Module]Imports
show/hide Instances
data CgGuts Source
A restricted form of ModGuts for code generation purposes
Constructors
CgGuts
cg_module :: !ModuleModule being compiled
cg_tycons :: [TyCon]Algebraic data types (including ones that started life as classes); generate constructors and info tables. Includes newtypes, just for the benefit of External Core
cg_binds :: [CoreBind]The tidied main bindings, including previously-implicit bindings for record and class selectors, and data construtor wrappers. But *not* data constructor workers; reason: we we regard them as part of the code-gen of tycons
cg_dir_imps :: ![Module]Directly-imported modules; used to generate initialisation code
cg_foreign :: !ForeignStubsForeign export stubs
cg_dep_pkgs :: ![PackageId]Dependent packages, used to generate #includes for C code gen
cg_hpc_info :: !HpcInfoProgram coverage tick box information
cg_modBreaks :: !ModBreaksModule breakpoints
data ForeignStubs Source
Foreign export stubs
Constructors
NoStubsWe don't have any stubs
ForeignStubs SDoc SDoc

There are some stubs. Parameters:

1) Header file prototypes for foreign exported functions

2) C stubs to use when calling foreign exported functions

type ImportedMods = ModuleEnv [(ModuleName, Bool, SrcSpan)]Source
Records the modules directly imported by a module for extracting e.g. usage information
data ModSummary Source

A single node in a 'ModuleGraph. The nodes of the module graph are one of:

  • A regular Haskell source module
  • A hi-boot source module
  • An external-core source module
Constructors
ModSummary
ms_mod :: ModuleIdentity of the module
ms_hsc_src :: HscSourceThe module source either plain Haskell, hs-boot or external core
ms_location :: ModLocationLocation of the various files belonging to the module
ms_hs_date :: ClockTimeTimestamp of source file
ms_obj_date :: Maybe ClockTimeTimestamp of object, if we have one
ms_srcimps :: [Located (ImportDecl RdrName)]Source imports of the module
ms_imps :: [Located (ImportDecl RdrName)]Non-source imports of the module
ms_hspp_file :: FilePathFilename of preprocessed source file
ms_hspp_opts :: DynFlagsCached flags from OPTIONS, INCLUDE and LANGUAGE pragmas in the modules source code
ms_hspp_buf :: Maybe StringBufferThe actual preprocessed source, if we have it
show/hide Instances
ms_mod_name :: ModSummary -> ModuleNameSource
showModMsg :: HscTarget -> Bool -> ModSummary -> StringSource
isBootSummary :: ModSummary -> BoolSource
Did this ModSummary originate from a hs-boot file?
msHsFilePath :: ModSummary -> FilePathSource
msHiFilePath :: ModSummary -> FilePathSource
msObjFilePath :: ModSummary -> FilePathSource
Information about the module being compiled
data HscSource Source
Constructors
HsSrcFile
HsBootFile
ExtCoreFile
show/hide Instances
isHsBoot :: HscSource -> BoolSource
hscSourceString :: HscSource -> StringSource
State relating to modules in this package
type HomePackageTable = ModuleNameEnv HomeModInfoSource
Helps us find information about modules in the home package
data HomeModInfo Source
Information about modules in the package being compiled
Constructors
HomeModInfo
hm_iface :: !ModIfaceThe basic loaded interface file: every loaded module has one of these, even if it is imported from another package
hm_details :: !ModDetailsExtra information that has been created from the ModIface for the module, typically during typechecking
hm_linkable :: !(Maybe Linkable)

The actual artifact we would like to link to access things in this module.

hm_linkable might be Nothing:

1. If this is an .hs-boot module

2. Temporarily during compilation if we pruned away the old linkable because it was out of date.

After a complete compilation (GHC.load), all hm_linkable fields in the HomePackageTable will be Just.

When re-linking a module (HscMain.HscNoRecomp), we construct the HomeModInfo by building a new ModDetails from the old ModIface (only).

emptyHomePackageTable :: HomePackageTableSource
hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([Instance], [FamInst])Source
Find all the instance declarations (of classes and families) that are in modules imported by this one, directly or indirectly, and are in the Home Package Table. This ensures that we don't see instances from modules --make compiled before this one, but which are not below this one.
hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule]Source
Get rules from modules "below" this one (in the dependency sense)
hptVectInfo :: HscEnv -> VectInfoSource
Get the combined VectInfo of all modules in the home package table. In contrast to instances and rules, we don't care whether the modules are "below" us in the dependency sense. The VectInfo of those modules not "below" us does not affect the compilation of the current module.
State relating to known packages
data ExternalPackageState Source
Information about other packages that we have slurped in by reading their interface files
Constructors
EPS
eps_is_boot :: !(ModuleNameEnv (ModuleName, IsBootInterface))

In OneShot mode (only), home-package modules accumulate in the external package state, and are sucked in lazily. For these home-pkg modules (only) we need to record which are boot modules. We set this field after loading all the explicitly-imported interfaces, but before doing anything else

The ModuleName part is not necessary, but it's useful for debug prints, and it's convenient because this field comes direct from TcRnTypes.imp_dep_mods

eps_PIT :: !PackageIfaceTable

The ModIfaces for modules in external packages whose interfaces we have opened. The declarations in these interface files are held in the eps_decls, eps_inst_env, eps_fam_inst_env and eps_rules fields of this record, not in the mi_decls fields of the interface we have sucked in.

What is in the PIT is:

  • The Module
  • Fingerprint info
  • Its exports
  • Fixities
  • Deprecations and warnings
eps_PTE :: !PackageTypeEnvResult of typechecking all the external package interface files we have sucked in. The domain of the mapping is external-package modules
eps_inst_env :: !PackageInstEnvThe total InstEnv accumulated from all the external-package modules
eps_fam_inst_env :: !PackageFamInstEnvThe total FamInstEnv accumulated from all the external-package modules
eps_rule_base :: !PackageRuleBaseThe total RuleEnv accumulated from all the external-package modules
eps_vect_info :: !PackageVectInfoThe total VectInfo accumulated from all the external-package modules
eps_ann_env :: !PackageAnnEnvThe total AnnEnv accumulated from all the external-package modules
eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv)The family instances accumulated from external packages, keyed off the module that declared them
eps_stats :: !EpsStatsStastics about what was loaded from external packages
data EpsStats Source
Accumulated statistics about what we are putting into the ExternalPackageState. "In" means stuff that is just read from interface files, "Out" means actually sucked in and type-checked
Constructors
EpsStats
n_ifaces_in :: !Int
n_decls_in :: !Int
n_decls_out :: !Int
n_rules_in :: !Int
n_rules_out :: !Int
n_insts_in :: !Int
n_insts_out :: !Int
addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStatsSource
Add stats for one newly-read interface
type PackageTypeEnv = TypeEnvSource
type PackageIfaceTable = ModuleEnv ModIfaceSource
Helps us find information about modules in the imported packages
emptyPackageIfaceTable :: PackageIfaceTableSource
lookupIfaceByModule :: DynFlags -> HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIfaceSource
Find the ModIface for a Module, searching in both the loaded home and external package module information
emptyModIface :: Module -> ModIfaceSource
type PackageInstEnv = InstEnvSource
type PackageRuleBase = RuleBaseSource
Annotations
prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnvSource
Deal with gathering annotations in from all possible places and combining them into a single AnnEnv
Interactive context
data InteractiveContext Source
Interactive context, recording information relevant to GHCi
Constructors
InteractiveContext
ic_toplev_scope :: [Module]The context includes the top-level scope of these modules
ic_exports :: [Module]The context includes just the exports of these modules
ic_rn_gbl_env :: GlobalRdrEnvThe contexts' cached GlobalRdrEnv, built from ic_toplev_scope and ic_exports
ic_tmp_ids :: [Id]Names bound during interaction with the user. Later Ids shadow earlier ones with the same OccName.
ic_tyvars :: TyVarSetSkolem type variables free in ic_tmp_ids. These arise at breakpoints in a polymorphic context, where we have only partial type information.
ic_resume :: [Resume]The stack of breakpoint contexts
ic_cwd :: Maybe FilePath
emptyInteractiveContext :: InteractiveContextSource
icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualifiedSource
extendInteractiveContext :: InteractiveContext -> [Id] -> TyVarSet -> InteractiveContextSource
substInteractiveContext :: InteractiveContext -> TvSubst -> InteractiveContextSource
mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualifiedSource
Creates some functions that work out the best ways to format names for the user according to a set of heuristics
pprModulePrefix :: PprStyle -> Module -> OccName -> SDocSource
Interfaces
data ModIface Source

A ModIface plus a ModDetails summarises everything we know about a compiled module. The ModIface is the stuff *before* linking, and can be written out to an interface file. The 'ModDetails is after linking and can be completely recovered from just the ModIface.

When we read an interface file, we also construct a ModIface from it, except that we explicitly make the mi_decls and a few other fields empty; as when reading we consolidate the declarations etc. into a number of indexed maps and environments in the ExternalPackageState.

Constructors
ModIface
mi_module :: !ModuleName of the module we are for
mi_iface_hash :: !FingerprintHash of the whole interface
mi_mod_hash :: !FingerprintHash of the ABI only
mi_orphan :: !WhetherHasOrphansWhether this module has orphans
mi_finsts :: !WhetherHasFamInstWhether this module has family instances
mi_boot :: !IsBootInterfaceRead from an hi-boot file?
mi_deps :: DependenciesThe dependencies of the module. This is consulted for directly-imported modules, but not for anything else (hence lazy)
mi_usages :: [Usage]Usages; kept sorted so that it's easy to decide whether to write a new iface file (changing usages doesn't affect the hash of this module)
mi_exports :: ![IfaceExport]Records the modules that are the declaration points for things exported by this module, and the OccNames of those things
mi_exp_hash :: !FingerprintHash of export list
mi_fixities :: [(OccName, Fixity)]Fixities
mi_warns :: WarningsWarnings
mi_anns :: [IfaceAnnotation]Annotations
mi_decls :: [(Fingerprint, IfaceDecl)]Sorted type, variable, class etc. declarations
mi_globals :: !(Maybe GlobalRdrEnv)

Binds all the things defined at the top level in the original source code for this module. which is NOT the same as mi_exports, nor mi_decls (which may contains declarations for things not actually defined by the user). Used for GHCi and for inspecting the contents of modules via the GHC API only.

(We need the source file to figure out the top-level environment, if we didn't compile this module from source then this field contains Nothing).

Strictly speaking this field should live in the HomeModInfo, but that leads to more plumbing.

mi_insts :: [IfaceInst]Sorted class instance
mi_fam_insts :: [IfaceFamInst]Sorted family instances
mi_rules :: [IfaceRule]Sorted rules
mi_orphan_hash :: !FingerprintHash for orphan rules and class and family instances combined
mi_vect_info :: !IfaceVectInfoVectorisation information
mi_warn_fn :: Name -> Maybe WarningTxtCached lookup for mi_warns
mi_fix_fn :: OccName -> FixityCached lookup for mi_fixities
mi_hash_fn :: OccName -> Maybe (OccName, Fingerprint)Cached lookup for mi_decls. The Nothing in mi_hash_fn means that the thing isn't in decls. It's useful to know that when seeing if we are up to date wrt. the old interface. The OccName is the parent of the name, if it has one.
mi_hpc :: !AnyHpcUsageTrue if this program uses Hpc at any point in the program.
show/hide Instances
mkIfaceWarnCache :: Warnings -> Name -> Maybe WarningTxtSource
Constructs the cache for the mi_warn_fn field of a ModIface
mkIfaceHashCache :: [(Fingerprint, IfaceDecl)] -> OccName -> Maybe (OccName, Fingerprint)Source
Constructs cache for the mi_hash_fn field of a ModIface
mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> FixitySource
Creates cached lookup for the mi_fix_fn field of ModIface
emptyIfaceWarnCache :: Name -> Maybe WarningTxtSource
Fixity
type FixityEnv = NameEnv FixItemSource
Fixity environment mapping names to their fixities
data FixItem Source
Fixity information for an Name. We keep the OccName in the range so that we can generate an interface from it
Constructors
FixItem OccName Fixity
show/hide Instances
lookupFixity :: FixityEnv -> Name -> FixitySource
emptyFixityEnv :: FixityEnvSource
TyThings and type environments
data TyThing Source
A typecheckable-thing, essentially anything that has a name
Constructors
AnId Id
ADataCon DataCon
ATyCon TyCon
AClass Class
show/hide Instances
tyThingClass :: TyThing -> ClassSource
Get the Class from a TyThing if it is a class thing. Panics otherwise
tyThingTyCon :: TyThing -> TyConSource
Get the TyCon from a TyThing if it is a type constructor thing. Panics otherwise
tyThingDataCon :: TyThing -> DataConSource
Get the DataCon from a TyThing if it is a data constructor thing. Panics otherwise
tyThingId :: TyThing -> IdSource
Get the Id from a TyThing if it is a id *or* data constructor thing. Panics otherwise
implicitTyThings :: TyThing -> [TyThing]Source
Determine the TyThings brought into scope by another TyThing other than itself. For example, Id's don't have any implicit TyThings as they just bring themselves into scope, but classes bring their dictionary datatype, type constructor and some selector functions into scope, just for a start!
isImplicitTyThing :: TyThing -> BoolSource
Returns True if there should be no interface-file declaration for this thing on its own: either it is built-in, or it is part of some other declaration, or it is generated implicitly by some other declaration.
type TypeEnv = NameEnv TyThingSource
A map from Names to TyThings, constructed by typechecking local declarations or interface files
lookupType :: DynFlags -> HomePackageTable -> PackageTypeEnv -> Name -> Maybe TyThingSource
Find the TyThing for the given Name by using all the resources at our disposal: the compiled modules in the HomePackageTable and the compiled modules in other packages that live in PackageTypeEnv. Note that this does NOT look up the TyThing in the module being compiled: you have to do that yourself, if desired
lookupTypeHscEnv :: HscEnv -> Name -> IO (Maybe TyThing)Source
As lookupType, but with a marginally easier-to-use interface if you have a HscEnv
mkTypeEnv :: [TyThing] -> TypeEnvSource
emptyTypeEnv :: TypeEnvSource
extendTypeEnv :: TypeEnv -> TyThing -> TypeEnvSource
extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnvSource
extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnvSource
lookupTypeEnv :: TypeEnv -> Name -> Maybe TyThingSource
typeEnvElts :: TypeEnv -> [TyThing]Source
typeEnvClasses :: TypeEnv -> [Class]Source
typeEnvTyCons :: TypeEnv -> [TyCon]Source
typeEnvIds :: TypeEnv -> [Id]Source
typeEnvDataCons :: TypeEnv -> [DataCon]Source
MonadThings
class Monad m => MonadThings m whereSource
Class that abstracts out the common ability of the monads in GHC to lookup a TyThing in the monadic environment by Name. Provides a number of related convenience functions for accessing particular kinds of TyThing
Methods
lookupThing :: Name -> m TyThingSource
lookupId :: Name -> m IdSource
lookupDataCon :: Name -> m DataConSource
lookupTyCon :: Name -> m TyConSource
lookupClass :: Name -> m ClassSource
show/hide Instances
Information on imports and exports
type WhetherHasOrphans = BoolSource

Records whether a module has orphans. An "orphan" is one of:

  • An instance declaration in a module other than the definition module for one of the type constructors or classes in the instance head
  • A transformation rule in a module other than the one defining the function in the head of the rule
type IsBootInterface = BoolSource
Did this module originate from a *-boot file?
data Usage Source
Records modules that we depend on by making a direct import from
Constructors
UsagePackageModuleModule from another package
usg_mod :: ModuleExternal package module depended on
usg_mod_hash :: Fingerprint
UsageHomeModuleModule from the current package
usg_mod_name :: ModuleNameName of the module
usg_mod_hash :: Fingerprint
usg_entities :: [(OccName, Fingerprint)]Entities we depend on, sorted by occurrence name and fingerprinted. NB: usages are for parent names only, e.g. type constructors but not the associated data constructors.
usg_exports :: Maybe FingerprintFingerprint for the export list we used to depend on this module, if we depend on the export list
show/hide Instances
data Dependencies Source

Dependency information about modules and packages below this one in the import hierarchy.

Invariant: the dependencies of a module M never includes M.

Invariant: none of the lists contain duplicates.

Constructors
Deps
dep_mods :: [(ModuleName, IsBootInterface)]Home-package module dependencies
dep_pkgs :: [PackageId]External package dependencies
dep_orphs :: [Module]Orphan modules (whether home or external pkg), *not* including family instance orphans as they are anyway included in dep_finsts
dep_finsts :: [Module]Modules that contain family instances (whether the instances are from the home or an external package)
show/hide Instances
noDependencies :: DependenciesSource
data NameCache Source
The NameCache makes sure that there is just one Unique assigned for each original name; i.e. (module-name, occ-name) pair and provides something of a lookup mechanism for those names.
Constructors
NameCache
nsUniqs :: UniqSupplySupply of uniques
nsNames :: OrigNameCacheEnsures that one original name gets one unique
nsIPs :: OrigIParamCacheEnsures that one implicit parameter name gets one unique
type OrigNameCache = ModuleEnv (OccEnv Name)Source
Per-module cache of original OccNames given Names
type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name)Source
Module-local cache of implicit parameter OccNames given Names
type Avails = [AvailInfo]Source
A collection of AvailInfo - several things that are "available"
availsToNameSet :: [AvailInfo] -> NameSetSource
availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfoSource
availName :: GenAvailInfo name -> nameSource
Just the main name made available, i.e. not the available pieces of type or class brought into scope by the GenAvailInfo
availNames :: GenAvailInfo name -> [name]Source
All names made available by the availability information
data GenAvailInfo name Source
Records what things are available, i.e. in scope
Constructors
Avail nameAn ordinary identifier in scope
AvailTC name [name]

A type or class in scope. Parameters:

1) The name of the type or class

2) The available pieces of type or class. NB: If the type or class is itself to be in scope, it must be in this list. Thus, typically: AvailTC Eq [Eq, ==, /=]

show/hide Instances
type AvailInfo = GenAvailInfo NameSource
Named things that are available
type RdrAvailInfo = GenAvailInfo OccNameSource
RdrNamed things that are available
type IfaceExport = (Module, [GenAvailInfo OccName])Source
The original names declared of a certain module that are exported
Warnings
data Warnings Source
Warning information for a module
Constructors
NoWarningsNothing deprecated
WarnAll WarningTxtWhole module deprecated
WarnSome [(OccName, WarningTxt)]Some specific things deprecated
show/hide Instances
data WarningTxt Source
Constructors
WarningTxt [FastString]
DeprecatedTxt [FastString]
show/hide Instances
plusWarns :: Warnings -> Warnings -> WarningsSource
Linker stuff
data Linkable Source
Information we can use to dynamically link modules into the compiler
Constructors
LM
linkableTime :: ClockTimeTime at which this linkable was built (i.e. when the bytecodes were produced, or the mod date on the files)
linkableModule :: ModuleThe linkable module itself
linkableUnlinked :: [Unlinked]

Those files and chunks of code we have yet to link.

INVARIANT: A valid linkable always has at least one Unlinked item. If this list is empty, the Linkable represents a fake linkable, which is generated in HscNothing mode to avoid recompiling modules.

XXX: Do items get removed from this list when they get linked?

show/hide Instances
isObjectLinkable :: Linkable -> BoolSource
data Unlinked Source
Objects which have yet to be linked by the compiler
Constructors
DotO FilePathAn object file (.o)
DotA FilePathStatic archive file (.a)
DotDLL FilePathDynamically linked library file (.so, .dll, .dylib)
BCOs CompiledByteCode ModBreaksA byte-code object, lives only in memory
show/hide Instances
data CompiledByteCode Source
show/hide Instances
isObject :: Unlinked -> BoolSource
Is this an actual file on disk we can link in somehow?
nameOfObject :: Unlinked -> FilePathSource
Retrieve the filename of the linkable if possible. Panic if it is a byte-code object
isInterpretable :: Unlinked -> BoolSource
Is this a bytecode linkable with no file on disk?
byteCodeOfObject :: Unlinked -> CompiledByteCodeSource
Retrieve the compiled byte-code if possible. Panic if it is a file-based linkable
Program coverage
data HpcInfo Source
Information about a modules use of Haskell Program Coverage
Constructors
HpcInfo
hpcInfoTickCount :: Int
hpcInfoHash :: Int
NoHpcInfo
hpcUsed :: AnyHpcUsageIs hpc used anywhere on the module *tree*?
emptyHpcInfo :: AnyHpcUsage -> HpcInfoSource
isHpcUsed :: HpcInfo -> AnyHpcUsageSource
Find out if HPC is used by this module or any of the modules it depends upon
type AnyHpcUsage = BoolSource
This is used to signal if one of my imports used HPC instrumentation even if there is no module-local HPC usage
Breakpoints
data ModBreaks Source
All the information about the breakpoints for a given module
Constructors
ModBreaks
modBreaks_flags :: BreakArrayThe array of flags, one per breakpoint, indicating which breakpoints are enabled.
modBreaks_locs :: !(Array BreakIndex SrcSpan)An array giving the source span of each breakpoint.
modBreaks_vars :: !(Array BreakIndex [OccName])An array giving the names of the free variables at each breakpoint.
type BreakIndex = IntSource
Breakpoint index
emptyModBreaks :: ModBreaksSource
Vectorisation information
data VectInfo Source
Vectorisation information for ModGuts, ModDetails and ExternalPackageState. All of this information is always tidy, even in ModGuts.
Constructors
VectInfo
vectInfoVar :: VarEnv (Var, Var)(f, f_v) keyed on f
vectInfoTyCon :: NameEnv (TyCon, TyCon)(T, T_v) keyed on T
vectInfoDataCon :: NameEnv (DataCon, DataCon)(C, C_v) keyed on C
vectInfoPADFun :: NameEnv (TyCon, Var)(T_v, paT) keyed on T_v
vectInfoIso :: NameEnv (TyCon, Var)(T, isoT) keyed on T
data IfaceVectInfo Source
Vectorisation information for ModIface: a slightly less low-level view
Constructors
IfaceVectInfo
ifaceVectInfoVar :: [Name]All variables in here have a vectorised variant
ifaceVectInfoTyCon :: [Name]All TyCons in here have a vectorised variant; the name of the vectorised variant and those of its data constructors are determined by OccName.mkVectTyConOcc and OccName.mkVectDataConOcc; the names of the isomorphisms are determined by OccName.mkVectIsoOcc
ifaceVectInfoTyConReuse :: [Name]The vectorised form of all the TyCons in here coincides with the unconverted form; the name of the isomorphisms is determined by OccName.mkVectIsoOcc
show/hide Instances
noVectInfo :: VectInfoSource
plusVectInfo :: VectInfo -> VectInfo -> VectInfoSource
noIfaceVectInfo :: IfaceVectInfoSource
Produced by Haddock version 2.6.0