ghc-8.2.2: The GHC API

Safe HaskellNone
LanguageHaskell2010

HscTypes

Contents

Description

Types for the per-module compiler

Synopsis

compilation state

data HscEnv #

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_type_env_var :: Maybe (Module, IORef TypeEnv)

    Used for one-shot compilation only, to initialise the IfGblEnv. See tcg_type_env_var for TcGblEnv. See also Note [hsc_type_env_var hack]

  • hsc_iserv :: MVar (Maybe IServ)

    interactive server process. Created the first time it is needed.

hscEPS :: HscEnv -> IO ExternalPackageState #

Retrieve the ExternalPackageState cache.

type FinderCache = InstalledModuleEnv InstalledFindResult #

The FinderCache maps modules 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.

data FindResult #

The result of searching for an imported module.

NB: FindResult manages both user source-import lookups (which can result in Module) as well as direct imports for interfaces (which always result in InstalledModule).

Constructors

Found ModLocation Module

The module was found

NoPackage UnitId

The requested package was not found

FoundMultiple [(Module, ModuleOrigin)]

_Error_: both in multiple packages

NotFound

Not found

data Target #

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

Instances

data TargetId #

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] #

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.

data HscStatus #

Status of a compilation to hard-code

Hsc monad

newtype Hsc a #

Constructors

Hsc (HscEnv -> WarningMessages -> IO (a, WarningMessages)) 

Instances

Monad Hsc # 

Methods

(>>=) :: Hsc a -> (a -> Hsc b) -> Hsc b Source #

(>>) :: Hsc a -> Hsc b -> Hsc b Source #

return :: a -> Hsc a Source #

fail :: String -> Hsc a Source #

Functor Hsc # 

Methods

fmap :: (a -> b) -> Hsc a -> Hsc b Source #

(<$) :: a -> Hsc b -> Hsc a Source #

Applicative Hsc # 

Methods

pure :: a -> Hsc a Source #

(<*>) :: Hsc (a -> b) -> Hsc a -> Hsc b Source #

liftA2 :: (a -> b -> c) -> Hsc a -> Hsc b -> Hsc c Source #

(*>) :: Hsc a -> Hsc b -> Hsc b Source #

(<*) :: Hsc a -> Hsc b -> Hsc a Source #

MonadIO Hsc # 

Methods

liftIO :: IO a -> Hsc a Source #

HasDynFlags Hsc # 

runHsc :: HscEnv -> Hsc a -> IO a #

Information about modules

data ModDetails #

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

emptyModDetails :: ModDetails #

Constructs an empty ModDetails

data ModGuts #

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

data CgGuts #

A restricted form of ModGuts for code generation purposes

Constructors

CgGuts 

Fields

data ForeignStubs #

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 [ImportedBy] #

Records the modules directly imported by a module for extracting e.g. usage information, and also to give better error message

data ImportedBy #

If a module was "imported" by the user, we associate it with more detailed usage information ImportedModsVal; a module imported by the system only gets used for usage information.

data ImportedModsVal #

Constructors

ImportedModsVal 

Fields

data SptEntry #

An entry to be inserted into a module's static pointer table. See Note [Grand plan for static forms] in StaticPtrTable.

Constructors

SptEntry Id Fingerprint 

Instances

data ForeignSrcLang :: * Source #

Constructors

LangC 
LangCxx 
LangObjc 
LangObjcxx 

Instances

Eq ForeignSrcLang 
Show ForeignSrcLang 
Generic ForeignSrcLang 
type Rep ForeignSrcLang 
type Rep ForeignSrcLang = D1 * (MetaData "ForeignSrcLang" "GHC.ForeignSrcLang.Type" "ghc-boot-th-8.2.2" False) ((:+:) * ((:+:) * (C1 * (MetaCons "LangC" PrefixI False) (U1 *)) (C1 * (MetaCons "LangCxx" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "LangObjc" PrefixI False) (U1 *)) (C1 * (MetaCons "LangObjcxx" PrefixI False) (U1 *))))

data ModSummary #

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

Constructors

ModSummary 

Fields

isBootSummary :: ModSummary -> Bool #

Did this ModSummary originate from a hs-boot file?

data SourceModified #

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 = DModuleNameEnv HomeModInfo #

Helps us find information about modules in the home package

data HomeModInfo #

Information about modules in the package being compiled

Constructors

HomeModInfo 

Fields

emptyHomePackageTable :: HomePackageTable #

Constructs an empty HomePackageTable

hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [FamInst]) #

Find all the instance declarations (of classes and families) from the Home Package Table filtered by the provided predicate function. Used in tcRnImports, to select the instances that are in the transitive closure of imports from the currently compiled module.

hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule] #

Get rules from modules "below" this one (in the dependency sense)

hptVectInfo :: HscEnv -> VectInfo #

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 #

Information about other packages that we have slurped in by reading their interface files

Constructors

EPS 

Fields

data EpsStats #

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

addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats #

Add stats for one newly-read interface

type PackageIfaceTable = ModuleEnv ModIface #

Helps us find information about modules in the imported packages

emptyPackageIfaceTable :: PackageIfaceTable #

Constructs an empty PackageIfaceTable

lookupIfaceByModule :: DynFlags -> HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface #

Find the ModIface for a Module, searching in both the loaded home and external package module information

emptyModIface :: Module -> ModIface #

Constructs an empty ModIface

Metaprogramming

data MetaRequest #

The supported metaprogramming result types

data MetaResult #

data constructors not exported to ensure correct result type

Annotations

prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv #

Deal with gathering annotations in from all possible places and combining them into a single AnnEnv

Interactive context

data InteractiveContext #

Interactive context, recording information about the state of the context in which statements are executed in a GHC session.

Constructors

InteractiveContext 

Fields

  • ic_dflags :: DynFlags

    The DynFlags used to evaluate interative expressions and statements.

  • ic_mod_index :: Int

    Each GHCi stmt or declaration brings some new things into scope. We give them names like interactive:Ghci9.T, where the ic_index is the '9'. The ic_mod_index is incremented whenever we add something to ic_tythings See Note [The interactive package]

  • ic_imports :: [InteractiveImport]

    The GHCi top-level scope (ic_rn_gbl_env) 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_tythings :: [TyThing]

    TyThings defined by the user, in reverse order of definition (ie most recent at the front) See Note [ic_tythings]

  • ic_rn_gbl_env :: GlobalRdrEnv

    The cached GlobalRdrEnv, built by setContext and updated regularly It contains everything in scope at the command line, including everything in ic_tythings

  • ic_instances :: ([ClsInst], [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_fix_env :: FixityEnv

    Fixities declared in let statements

  • ic_default :: Maybe [Type]

    The current default types, set by a 'default' declaration

  • ic_resume :: [Resume]

    The stack of breakpoint contexts

  • ic_monad :: Name

    The monad that GHCi is executing in

  • ic_int_print :: Name

    The function that is used for printing results of expressions in ghci and -e mode.

  • ic_cwd :: Maybe FilePath
     

emptyInteractiveContext :: DynFlags -> InteractiveContext #

Constructs an empty InteractiveContext.

icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified #

Get the PrintUnqualified function based on the flags and this InteractiveContext

icInScopeTTs :: InteractiveContext -> [TyThing] #

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

icExtendGblRdrEnv :: GlobalRdrEnv -> [TyThing] -> GlobalRdrEnv #

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

extendInteractiveContext :: InteractiveContext -> [TyThing] -> [ClsInst] -> [FamInst] -> Maybe [Type] -> FixityEnv -> InteractiveContext #

extendInteractiveContext 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 #

Constructors

IIDecl (ImportDecl RdrName)

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

IIModule ModuleName

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

mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified #

Creates some functions that work out the best ways to format names for the user according to a set of heuristics.

mkQualPackage :: DynFlags -> QueryQualifyPackage #

Creates a function for formatting packages based on two heuristics: (1) don't qualify if the package in question is "main", and (2) only qualify with a unit id if the package ID would be ambiguous.

mkQualModule :: DynFlags -> QueryQualifyModule #

Creates a function for formatting modules based on two heuristics: (1) if the module is the current module, don't qualify, and (2) if there is only one exposed package which exports this module, don't qualify.

pkgQual :: DynFlags -> PrintUnqualified #

A function which only qualifies package names if necessary; but qualifies all other identifiers.

Interfaces

data ModIface #

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_sig_of :: !(Maybe Module)

    Are we a sig of another mod?

  • 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. See Note [The type family instance consistency story].

  • mi_hsc_src :: !HscSource

    Boot? Signature?

  • 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 :: [IfaceClsInst]

    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 :: OccName -> Maybe WarningTxt

    Cached lookup for mi_warns

  • mi_fix_fn :: OccName -> Maybe 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]

  • mi_complete_sigs :: [IfaceCompleteMatch]
     

Instances

mkIfaceWarnCache :: Warnings -> OccName -> Maybe WarningTxt #

Constructs the cache for the mi_warn_fn field of a ModIface

mkIfaceHashCache :: [(Fingerprint, IfaceDecl)] -> OccName -> Maybe (OccName, Fingerprint) #

Constructs cache for the mi_hash_fn field of a ModIface

mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Maybe Fixity #

Creates cached lookup for the mi_fix_fn field of ModIface

mi_boot :: ModIface -> Bool #

Old-style accessor for whether or not the ModIface came from an hs-boot file.

mi_fix :: ModIface -> OccName -> Fixity #

Lookups up a (possibly cached) fixity from a ModIface. If one cannot be found, defaultFixity is returned instead.

mi_semantic_module :: ModIface -> Module #

The semantic module for this interface; e.g., if it's a interface for a signature, if mi_module is p[A=A]:A, mi_semantic_module will be A.

mi_free_holes :: ModIface -> UniqDSet ModuleName #

The "precise" free holes, e.g., the signatures that this ModIface depends on.

renameFreeHoles :: UniqDSet ModuleName -> [(ModuleName, Module)] -> UniqDSet ModuleName #

Given a set of free holes, and a unit identifier, rename the free holes according to the instantiation of the unit identifier. For example, if we have A and B free, and our unit identity is p[A=C,B=impl:B], the renamed free holes are just C.

Fixity

type FixityEnv = NameEnv FixItem #

Fixity environment mapping names to their fixities

data FixItem #

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 #

A global typecheckable-thing, essentially anything that has a name. Not to be confused with a TcTyThing, which is also a typecheckable thing but in the *local* context. See TcEnv for how to retrieve a TyThing given a Name.

tyThingAvailInfo :: TyThing -> [AvailInfo] #

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

tyThingTyCon :: TyThing -> TyCon #

Get the TyCon from a TyThing if it is a type constructor thing. Panics otherwise

tyThingDataCon :: TyThing -> DataCon #

Get the DataCon from a TyThing if it is a data constructor thing. Panics otherwise

tyThingConLike :: TyThing -> ConLike #

Get the ConLike from a TyThing if it is a data constructor thing. Panics otherwise

tyThingId :: TyThing -> Id #

Get the Id from a TyThing if it is a id *or* data constructor thing. Panics otherwise

tyThingCoAxiom :: TyThing -> CoAxiom Branched #

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

tyThingParent_maybe :: TyThing -> Maybe TyThing #

tyThingParent_maybe x returns (Just p) when pprTyThingInContext should 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] #

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 -> Bool #

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 TyThing #

A map from Names to TyThings, constructed by typechecking local declarations or interface files

lookupType :: DynFlags -> HomePackageTable -> PackageTypeEnv -> Name -> Maybe TyThing #

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) #

As lookupType, but with a marginally easier-to-use interface if you have a HscEnv

MonadThings

class Monad m => MonadThings m where #

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

Minimal complete definition

lookupThing

Information on imports and exports

type WhetherHasOrphans = Bool #

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 = Bool #

Did this module originate from a *-boot file?

data Usage #

Records modules for which changes may force recompilation of this module See wiki: http://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/RecompilationAvoidance

This differs from Dependencies. A module X may be in the dep_mods of this module (via an import chain) but if we don't use anything from X it won't appear in our Usage

Constructors

UsagePackageModule

Module from another package

Fields

UsageHomeModule

Module from the current package | A file upon which the module depends, e.g. a CPP #include, or using TH's addDependentFile

Fields

UsageFile 

Fields

UsageMergedRequirement

A requirement which was merged into this one.

Fields

Instances

Eq Usage # 

Methods

(==) :: Usage -> Usage -> Bool #

(/=) :: Usage -> Usage -> Bool #

Binary Usage # 

Methods

put_ :: BinHandle -> Usage -> IO () #

put :: BinHandle -> Usage -> IO (Bin * Usage) #

get :: BinHandle -> IO Usage #

data Dependencies #

Dependency information about ALL 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)]

    All home-package modules transitively below this one I.e. modules that this one imports, or that are in the dep_mods of those directly-imported modules

  • dep_pkgs :: [(InstalledUnitId, Bool)]

    All packages transitively below this module I.e. packages to which this module's direct imports belong, or that are in the dep_pkgs of those modules 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]

    Transitive closure of orphan modules (whether home or external pkg).

    (Possible optimization: don't include family instance orphans as they are anyway included in dep_finsts. But then be careful about code which relies on dep_orphs having the complete list!) This does NOT include us, unlike imp_orphs.

  • dep_finsts :: [Module]

    Transitive closure of depended upon modules which contain family instances (whether home or external). This is used by checkFamInstConsistency. This does NOT include us, unlike imp_finsts. See Note [The type family instance consistency story].

type IfaceExport = AvailInfo #

The original names declared of a certain module that are exported

Warnings

data Warnings #

Warning information for a module

Constructors

NoWarnings

Nothing deprecated

WarnAll WarningTxt

Whole module deprecated

WarnSome [(OccName, WarningTxt)]

Some specific things deprecated

data WarningTxt #

Warning Text

reason/explanation from a WARNING or DEPRECATED pragma

Instances

Eq WarningTxt # 
Data WarningTxt # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WarningTxt -> c WarningTxt Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WarningTxt Source #

toConstr :: WarningTxt -> Constr Source #

dataTypeOf :: WarningTxt -> DataType Source #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c WarningTxt) Source #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WarningTxt) Source #

gmapT :: (forall b. Data b => b -> b) -> WarningTxt -> WarningTxt Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WarningTxt -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WarningTxt -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> WarningTxt -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WarningTxt -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WarningTxt -> m WarningTxt Source #

Outputable WarningTxt # 
Binary WarningTxt # 

Linker stuff

data Linkable #

Information we can use to dynamically link modules into the compiler

Constructors

LM 

Fields

  • linkableTime :: UTCTime

    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 #

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 [SptEntry]

A byte-code object, lives only in memory. Also carries some static pointer table entries which should be loaded along with the BCOs. See Note [Grant plan for static forms] in StaticPtrTable.

Instances

isObject :: Unlinked -> Bool #

Is this an actual file on disk we can link in somehow?

nameOfObject :: Unlinked -> FilePath #

Retrieve the filename of the linkable if possible. Panic if it is a byte-code object

isInterpretable :: Unlinked -> Bool #

Is this a bytecode linkable with no file on disk?

byteCodeOfObject :: Unlinked -> CompiledByteCode #

Retrieve the compiled byte-code if possible. Panic if it is a file-based linkable

Program coverage

data HpcInfo #

Information about a modules use of Haskell Program Coverage

Constructors

HpcInfo 
NoHpcInfo 

Fields

isHpcUsed :: HpcInfo -> AnyHpcUsage #

Find out if HPC is used by this module or any of the modules it depends upon

type AnyHpcUsage = Bool #

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 #

All the information about the breakpoints for a module

Constructors

ModBreaks 

Fields

emptyModBreaks :: ModBreaks #

Construct an empty ModBreaks

Vectorisation information

data VectInfo #

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

Instances

data IfaceVectInfo #

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

Safe Haskell information

data IfaceTrustInfo #

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

type IsSafeImport = Bool #

Is an import a safe import?

result of the parser

data HsParsedModule #

Constructors

HsParsedModule 

Fields

Compilation errors and warnings

data SourceError #

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.

throwOneError :: MonadIO m => ErrMsg -> m ab #

handleSourceError #

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 () #

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

COMPLETE signature

data CompleteMatch #

A list of conlikes which represents a complete pattern match. These arise from COMPLETE signatures.

Constructors

CompleteMatch 

Fields