ghc-7.4.1: The GHC API

Safe HaskellSafe-Infered

HscTypes

Contents

Description

Types for the per-module compiler

Synopsis

compilation state

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 

Fields

hsc_dflags :: DynFlags

The dynamic flag settings

hsc_targets :: [Target]

The targets (or roots) of the current session

hsc_mod_graph :: ModuleGraph

The module graph of the current session

hsc_IC :: InteractiveContext

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

(This changes a previous invariant: changed Jan 05.)

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 :: OptFuelState

Settings 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 tcg_type_env_var for TcGblEnv

hsc_safeInf :: !(IORef Bool)

Have we infered the module being compiled as being safe?

hscEPS :: HscEnv -> IO ExternalPackageStateSource

Retrieve the ExternalPackageState cache.

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 Module

The module was found

NoPackage PackageId

The requested package was not found

FoundMultiple [PackageId]

_Error_: both in multiple packages

NotFound

Not found

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 

Fields

targetId :: TargetId

module or filename

targetAllowObjCode :: Bool

object code allowed?

targetContents :: Maybe (StringBuffer, ClockTime)

in-memory text buffer?

Instances

data TargetId Source

Constructors

TargetModule ModuleName

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

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 topSortModuleGraph and flattenSCC to achieve this.

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 

Fields

md_exports :: [AvailInfo]
 
md_types :: !TypeEnv

Local 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 :: !VectInfo

Module vectorisation information

emptyModDetails :: ModDetailsSource

Constructs an empty ModDetails

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

Constructors

ModGuts 

Fields

mg_module :: !Module

Module being compiled

mg_boot :: IsBootInterface

Whether it's an hs-boot module

mg_exports :: ![AvailInfo]

What it exports

mg_deps :: !Dependencies

What it depends on, directly or otherwise

mg_dir_imps :: !ImportedMods

Directly-imported modules; used to generate initialisation code

mg_used_names :: !NameSet

What the module needed (used in mkIface)

mg_used_th :: !Bool

Did we run a TH splice?

mg_rdr_env :: !GlobalRdrEnv

Top-level lexical environment

mg_fix_env :: !FixityEnv

Fixities declared in this module ToDo: I'm unconvinced this is actually used anywhere

mg_tcs :: ![TyCon]

TyCons declared in this module (includes TyCons for classes)

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 See Note [Overall plumbing for rules] in Rules.lhs

mg_binds :: !CoreProgram

Bindings for this module

mg_foreign :: !ForeignStubs

Foreign exports declared in this module

mg_warns :: !Warnings

Warnings declared in the module

mg_anns :: [Annotation]

Annotations declared in this module

mg_hpc_info :: !HpcInfo

Coverage tick boxes in the module

mg_modBreaks :: !ModBreaks

Breakpoints for the module

mg_vect_decls :: ![CoreVect]

Vectorisation declarations in this module (produced by desugarer & consumed by vectoriser)

mg_vect_info :: !VectInfo

Pool of vectorised declarations in the module

mg_inst_env :: InstEnv

Class instance environment from home-package modules (including this one); c.f. tcg_inst_env

mg_fam_inst_env :: FamInstEnv

Type-family instance enviroment for home-package modules (including this one); c.f. tcg_fam_inst_env

mg_trust_pkg :: Bool

Do we need to trust our own package for Safe Haskell? See Note [RnNames . Trust Own Package]

mg_dependent_files :: [FilePath]

dependencies from addDependentFile

data CgGuts Source

A restricted form of ModGuts for code generation purposes

Constructors

CgGuts 

Fields

cg_module :: !Module

Module 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 :: CoreProgram

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_foreign :: !ForeignStubs

Foreign export stubs

cg_dep_pkgs :: ![PackageId]

Dependent packages, used to generate #includes for C code gen

cg_hpc_info :: !HpcInfo

Program coverage tick box information

cg_modBreaks :: !ModBreaks

Module breakpoints

data ForeignStubs Source

Foreign export stubs

Constructors

NoStubs

We 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 [ImportedModsVal]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 

Fields

ms_mod :: Module

Identity of the module

ms_hsc_src :: HscSource

The module source either plain Haskell, hs-boot or external core

ms_location :: ModLocation

Location of the various files belonging to the module

ms_hs_date :: ClockTime

Timestamp of source file

ms_obj_date :: Maybe ClockTime

Timestamp of object, if we have one

ms_srcimps :: [Located (ImportDecl RdrName)]

Source imports of the module

ms_textual_imps :: [Located (ImportDecl RdrName)]

Non-source imports of the module from the module *text*

ms_hspp_file :: FilePath

Filename of preprocessed source file

ms_hspp_opts :: DynFlags

Cached flags from OPTIONS, INCLUDE and LANGUAGE pragmas in the modules source code

ms_hspp_buf :: Maybe StringBuffer

The actual preprocessed source, if we have it

isBootSummary :: ModSummary -> BoolSource

Did this ModSummary originate from a hs-boot file?

data SourceModified Source

Indicates whether a given module's source has been modified since it was last compiled.

Constructors

SourceModified

the source has been modified

SourceUnmodified

the source has not been modified. Compilation may or may not be necessary, depending on whether any dependencies have changed since we last compiled.

SourceUnmodifiedAndStable

the source has not been modified, and furthermore all of its (transitive) dependencies are up to date; it definitely does not need to be recompiled. This is important for two reasons: (a) we can omit the version check in checkOldIface, and (b) if the module used TH splices we don't need to force recompilation.

Information about the module being compiled

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 

Fields

hm_iface :: !ModIface

The basic loaded interface file: every loaded module has one of these, even if it is imported from another package

hm_details :: !ModDetails

Extra 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 (load), all hm_linkable fields in the HomePackageTable will be Just.

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

emptyHomePackageTable :: HomePackageTableSource

Constructs an empty HomePackageTable

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 

Fields

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 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 :: !PackageTypeEnv

Result of typechecking all the external package interface files we have sucked in. The domain of the mapping is external-package modules

eps_inst_env :: !PackageInstEnv

The total InstEnv accumulated from all the external-package modules

eps_fam_inst_env :: !PackageFamInstEnv

The total FamInstEnv accumulated from all the external-package modules

eps_rule_base :: !PackageRuleBase

The total RuleEnv accumulated from all the external-package modules

eps_vect_info :: !PackageVectInfo

The total VectInfo accumulated from all the external-package modules

eps_ann_env :: !PackageAnnEnv

The 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 :: !EpsStats

Stastics 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 

addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStatsSource

Add stats for one newly-read interface

type PackageIfaceTable = ModuleEnv ModIfaceSource

Helps us find information about modules in the imported packages

emptyPackageIfaceTable :: PackageIfaceTableSource

Constructs an empty PackageIfaceTable

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

Constructs an empty ModIface

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 about the state of the context in which statements are executed in a GHC session.

Constructors

InteractiveContext 

Fields

ic_imports :: [InteractiveImport]

The GHCi context is extended with these imports

This field is only stored here so that the client can retrieve it with GHC.getContext. GHC itself doesn't use it, but does reset it to empty sometimes (such as before a GHC.load). The context is set with GHC.setContext.

ic_rn_gbl_env :: GlobalRdrEnv

The cached GlobalRdrEnv, built by setContext and updated regularly

ic_tythings :: [TyThing]

TyThings defined by the user, in reverse order of definition.

ic_sys_vars :: [Id]

Variables defined automatically by the system (e.g. record field selectors). See Notes [ic_sys_vars]

ic_instances :: ([Instance], [FamInst])

All instances and family instances created during this session. These are grabbed en masse after each update to be sure that proper overlapping is retained. That is, rather than re-check the overlapping each time we update the context, we just take the results from the instance code that already does that.

ic_resume :: [Resume]

The stack of breakpoint contexts

ic_cwd :: Maybe FilePath
 

emptyInteractiveContext :: InteractiveContextSource

Constructs an empty InteractiveContext.

icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualifiedSource

Get the PrintUnqualified function based on the flags and this InteractiveContext

icInScopeTTs :: InteractiveContext -> [TyThing]Source

This function returns the list of visible TyThings (useful for e.g. showBindings)

icPlusGblRdrEnv :: [TyThing] -> GlobalRdrEnv -> GlobalRdrEnvSource

Add TyThings to the GlobalRdrEnv, earlier ones in the list shadowing later ones, and shadowing existing entries in the GlobalRdrEnv.

extendInteractiveContext :: InteractiveContext -> [TyThing] -> InteractiveContextSource

This function is called with new TyThings recently defined to update the InteractiveContext to include them. Ids are easily removed when shadowed, but Classes and TyCons are not. Some work could be done to determine whether they are entirely shadowed, but as you could still have references to them (e.g. instances for classes or values of the type for TyCons), it's not clear whether removing them is even the appropriate behavior.

data InteractiveImport Source

Constructors

IIDecl (ImportDecl RdrName)

Bring the exports of a particular module (filtered by an import decl) into scope

IIModule Module

Bring into scope the entire top-level envt of of this module, including the things imported into it.

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

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 

Fields

mi_module :: !Module

Name of the module we are for

mi_iface_hash :: !Fingerprint

Hash of the whole interface

mi_mod_hash :: !Fingerprint

Hash of the ABI only

mi_flag_hash :: !Fingerprint

Hash of the important flags used when compiling this module

mi_orphan :: !WhetherHasOrphans

Whether this module has orphans

mi_finsts :: !WhetherHasFamInst

Whether this module has family instances

mi_boot :: !IsBootInterface

Read from an hi-boot file?

mi_deps :: Dependencies

The 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) NOT STRICT! we read this field lazily from the interface file It is *only* consulted by the recompilation checker

mi_exports :: ![IfaceExport]

Exports Kept sorted by (mod,occ), to make version comparisons easier Records the modules that are the declaration points for things exported by this module, and the OccNames of those things

mi_exp_hash :: !Fingerprint

Hash of export list

mi_used_th :: !Bool

Module required TH splices when it was compiled. This disables recompilation avoidance (see #481).

mi_fixities :: [(OccName, Fixity)]

Fixities NOT STRICT! we read this field lazily from the interface file

mi_warns :: Warnings

Warnings NOT STRICT! we read this field lazily from the interface file

mi_anns :: [IfaceAnnotation]

Annotations NOT STRICT! we read this field lazily from the interface file

mi_decls :: [(Fingerprint, IfaceDecl)]

Type, class and variable declarations The hash of an Id changes if its fixity or deprecations change (as well as its type of course) Ditto data constructors, class operations, except that the hash of the parent class/tycon changes

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 :: !Fingerprint

Hash for orphan rules, class and family instances, and vectorise pragmas combined

mi_vect_info :: !IfaceVectInfo

Vectorisation information

mi_warn_fn :: Name -> Maybe WarningTxt

Cached lookup for mi_warns

mi_fix_fn :: OccName -> Fixity

Cached 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 :: !AnyHpcUsage

True if this program uses Hpc at any point in the program.

mi_trust :: !IfaceTrustInfo

Safe Haskell Trust information for this module.

mi_trust_pkg :: !Bool

Do we require the package this module resides in be trusted to trust this module? This is used for the situation where a module is Safe (so doesn't require the package be trusted itself) but imports some trustworthy modules from its own package (which does require its own package be trusted). See Note [RnNames . Trust Own Package]

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

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 

Instances

TyThings and type environments

data TyThing Source

A typecheckable-thing, essentially anything that has a name

tyThingAvailInfo :: TyThing -> AvailInfoSource

The Names that a TyThing should bring into scope. Used to build the GlobalRdrEnv for the InteractiveContext.

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

tyThingCoAxiom :: TyThing -> CoAxiomSource

Get the CoAxiom from a TyThing if it is a coercion axiom thing. Panics otherwise

tyThingParent_maybe :: TyThing -> Maybe TyThingSource

tyThingParent_maybe x returns (Just p) when pprTyThingInContext sould print a declaration for p (albeit with some ... in it) when asked to show x It returns the *immediate* parent. So a datacon returns its tycon but the tycon could be the associated type of a class, so it in turn might have a parent.

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

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

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
  • A vectorisation pragma

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

UsagePackageModule

Module from another package

Fields

usg_mod :: Module

External package module depended on

usg_mod_hash :: Fingerprint

Cached module fingerprint

Cached module fingerprint

usg_safe :: IsSafeImport

Was this module imported as a safe import

Was this module imported as a safe import

UsageHomeModule

Module from the current package

Fields

usg_mod_name :: ModuleName

Name of the module

usg_mod_hash :: Fingerprint

Cached module fingerprint

Cached module 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 Fingerprint

Fingerprint for the export list we used to depend on this module, if we depend on the export list

usg_safe :: IsSafeImport

Was this module imported as a safe import

Was this module imported as a safe import

UsageFile 

Fields

usg_file_path :: FilePath
 
usg_mtime :: ClockTime

External file dependency. From a CPP #include or TH addDependentFile. Should be absolute.

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 

Fields

dep_mods :: [(ModuleName, IsBootInterface)]

Home-package module dependencies

dep_pkgs :: [(PackageId, Bool)]

External package dependencies. The bool indicates if the package is required to be trusted when the module is imported as a safe import (Safe Haskell). See Note [RnNames . Tracking Trust Transitively]

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)

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 

Fields

nsUniqs :: UniqSupply

Supply of uniques

nsNames :: OrigNameCache

Ensures that one original name gets one unique

nsIPs :: OrigIParamCache

Ensures that one implicit parameter name gets one unique

type OrigNameCache = ModuleEnv (OccEnv Name)Source

Per-module cache of original OccNames given Names

type OrigIParamCache = Map FastString (IPName Name)Source

Module-local cache of implicit parameter OccNames given Names

type IfaceExport = AvailInfoSource

The original names declared of a certain module that are exported

Warnings

data Warnings Source

Warning information for a module

Constructors

NoWarnings

Nothing deprecated

WarnAll WarningTxt

Whole module deprecated

WarnSome [(OccName, WarningTxt)]

Some specific things deprecated

Linker stuff

data Linkable Source

Information we can use to dynamically link modules into the compiler

Constructors

LM 

Fields

linkableTime :: ClockTime

Time at which this linkable was built (i.e. when the bytecodes were produced, or the mod date on the files)

linkableModule :: Module

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

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

Instances

data Unlinked Source

Objects which have yet to be linked by the compiler

Constructors

DotO FilePath

An object file (.o)

DotA FilePath

Static archive file (.a)

DotDLL FilePath

Dynamically linked library file (.so, .dll, .dylib)

BCOs CompiledByteCode ModBreaks

A byte-code object, lives only in memory

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 
NoHpcInfo 

Fields

hpcUsed :: AnyHpcUsage

Is hpc used anywhere on the module *tree*?

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 

Fields

modBreaks_flags :: BreakArray

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

modBreaks_decls :: !(Array BreakIndex [String])

An array giving the names of the declarations enclosing each breakpoint.

type BreakIndex = IntSource

Breakpoint index

emptyModBreaks :: ModBreaksSource

Construct an empty ModBreaks

Vectorisation information

data VectInfo Source

Vectorisation information for ModGuts, ModDetails and ExternalPackageState; see also documentation at GlobalEnv.

NB: The following tables may also include Vars, TyCons and DataCons from imported modules, which have been subsequently vectorised in the current module.

Constructors

VectInfo 

Fields

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

vectInfoScalarVars :: VarSet

set of purely scalar variables

vectInfoScalarTyCons :: NameSet

set of scalar type constructors

Instances

data IfaceVectInfo Source

Vectorisation information for ModIface; i.e, the vectorisation information propagated across module boundaries.

NB: The field ifaceVectInfoVar explicitly contains the workers of data constructors as well as class selectors — i.e., their mappings are not implicitly generated from the data types. Moreover, whether the worker of a data constructor is in ifaceVectInfoVar determines whether that data constructor was vectorised (or is part of an abstractly vectorised type constructor).

Constructors

IfaceVectInfo 

Fields

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 mkVectTyConOcc and mkVectDataConOcc; the names of the isomorphisms are determined by 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 mkVectIsoOcc

ifaceVectInfoScalarVars :: [Name]
 
ifaceVectInfoScalarTyCons :: [Name]
 

Safe Haskell information

hscGetSafeInf :: HscEnv -> IO BoolSource

Get if the current module is considered safe or not by inference.

hscSetSafeInf :: HscEnv -> Bool -> IO ()Source

Set if the current module is considered safe or not by inference.

data IfaceTrustInfo Source

Safe Haskell information for ModIface Simply a wrapper around SafeHaskellMode to sepperate iface and flags

type IsSafeImport = BoolSource

Is an import a safe import?

result of the parser

data HsParsedModule Source

Constructors

HsParsedModule 

Fields

hpm_module :: Located (HsModule RdrName)
 
hpm_src_files :: [FilePath]

extra source files (e.g. from #includes). The lexer collects these from '# file line' pragmas, which the C preprocessor leaves behind. These files and their timestamps are stored in the .hi file, so that we can force recompilation if any of them change (#3589)

Compilation errors and 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.

data GhcApiError Source

An error thrown if the GHC API is used in an incorrect fashion.

handleSourceErrorSource

Arguments

:: ExceptionMonad m 
=> (SourceError -> m a)

exception handler

-> m a

action to perform

-> m a 

Perform the given action and call the exception handler if the action throws a SourceError. See SourceError for more information.

printOrThrowWarnings :: DynFlags -> Bag WarnMsg -> IO ()Source

Given a bag of warnings, turn them into an exception if -Werror is enabled, or print them out otherwise.