|
|
|
|
|
Description |
Types for the per-module compiler
|
|
Synopsis |
|
newtype Ghc a = Ghc {} | | newtype GhcT m a = GhcT {} | | liftGhcT :: Monad m => m a -> GhcT m a | | class (Functor m, MonadIO m, WarnLogMonad m, ExceptionMonad m) => GhcMonad m where | | | class Monad m => WarnLogMonad m where | | | 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 | | data Session = Session !(IORef HscEnv) !(IORef WarningMessages) | | withSession :: GhcMonad m => (HscEnv -> m a) -> m a | | modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m () | | data HscEnv = HscEnv {} | | hscEPS :: HscEnv -> IO ExternalPackageState | | type FinderCache = ModuleNameEnv FindResult | | | | type ModLocationCache = ModuleEnv ModLocation | | data Target = Target {} | | | | pprTarget :: Target -> SDoc | | pprTargetId :: TargetId -> SDoc | | type ModuleGraph = [ModSummary] | | emptyMG :: ModuleGraph | | data ModDetails = ModDetails {} | | emptyModDetails :: ModDetails | | data ModGuts = ModGuts {} | | data CoreModule = CoreModule {} | | data CgGuts = CgGuts {} | | | | type ImportedMods = ModuleEnv [(ModuleName, Bool, SrcSpan)] | | data ModSummary = ModSummary {} | | ms_mod_name :: ModSummary -> ModuleName | | showModMsg :: HscTarget -> Bool -> ModSummary -> String | | isBootSummary :: ModSummary -> Bool | | msHsFilePath :: ModSummary -> FilePath | | msHiFilePath :: ModSummary -> FilePath | | msObjFilePath :: ModSummary -> FilePath | | | | isHsBoot :: HscSource -> Bool | | hscSourceString :: HscSource -> String | | type HomePackageTable = ModuleNameEnv HomeModInfo | | data HomeModInfo = HomeModInfo {} | | emptyHomePackageTable :: HomePackageTable | | hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([Instance], [FamInst]) | | hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule] | | hptVectInfo :: HscEnv -> VectInfo | | data ExternalPackageState = EPS {} | | data EpsStats = EpsStats {} | | 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 | | data InteractiveContext = InteractiveContext {} | | emptyInteractiveContext :: InteractiveContext | | icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified | | mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified | | extendInteractiveContext :: InteractiveContext -> [Id] -> TyVarSet -> InteractiveContext | | substInteractiveContext :: InteractiveContext -> TvSubst -> InteractiveContext | | data ModIface = ModIface {} | | 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 | | | | 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 | | | type WhetherHasOrphans = Bool | | type IsBootInterface = Bool | | | | data Dependencies = Deps {} | | noDependencies :: Dependencies | | data NameCache = NameCache {} | | 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] | | | | type AvailInfo = GenAvailInfo Name | | type RdrAvailInfo = GenAvailInfo OccName | | type IfaceExport = (Module, [GenAvailInfo OccName]) | | | | | | plusWarns :: Warnings -> Warnings -> Warnings | | data Linkable = LM {} | | isObjectLinkable :: Linkable -> Bool | | | | data CompiledByteCode | | isObject :: Unlinked -> Bool | | nameOfObject :: Unlinked -> FilePath | | isInterpretable :: Unlinked -> Bool | | byteCodeOfObject :: Unlinked -> CompiledByteCode | | | | emptyHpcInfo :: AnyHpcUsage -> HpcInfo | | isHpcUsed :: HpcInfo -> AnyHpcUsage | | type AnyHpcUsage = Bool | | data ModBreaks = ModBreaks {} | | type BreakIndex = Int | | emptyModBreaks :: ModBreaks | | data VectInfo = VectInfo {} | | data IfaceVectInfo = IfaceVectInfo {} | | noVectInfo :: VectInfo | | plusVectInfo :: VectInfo -> VectInfo -> VectInfo | | noIfaceVectInfo :: IfaceVectInfo |
|
|
|
Ghc monad stuff
|
|
newtype Ghc a |
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 | | Instances | |
|
|
newtype GhcT m a |
A monad transformer to add GHC specific features to another monad.
Note that the wrapped monad must support IO and handling of exceptions.
| Constructors | | Instances | |
|
|
liftGhcT :: Monad m => m a -> GhcT m a |
|
class (Functor m, MonadIO m, WarnLogMonad m, ExceptionMonad m) => GhcMonad m where |
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 | | | Instances | |
|
|
class Monad m => WarnLogMonad m where |
A monad that allows logging of warnings.
| | Methods | | | Instances | |
|
|
liftIO :: MonadIO m => IO a -> m a |
|
ioMsgMaybe :: GhcMonad m => IO (Messages, Maybe a) -> m a |
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 a |
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 () |
|
clearWarnings :: WarnLogMonad m => m () |
Clear the log of Warnings.
|
|
hasWarnings :: WarnLogMonad m => m Bool |
Returns true if there were any 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.
| Instances | |
|
|
data GhcApiError |
XXX: what exactly is an API error?
| Instances | |
|
|
mkSrcErr :: ErrorMessages -> SourceError |
|
srcErrorMessages :: SourceError -> ErrorMessages |
|
mkApiErr :: SDoc -> GhcApiError |
|
throwOneError :: MonadIO m => ErrMsg -> m ab |
|
handleSourceError |
|
|
reflectGhc :: Ghc a -> Session -> IO a |
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 a |
|
Sessions and compilation state
|
|
data Session |
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 | |
|
|
withSession :: GhcMonad m => (HscEnv -> m a) -> m a |
Call the argument with the current session.
|
|
modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m () |
Set the current session to the result of applying the current session to
the argument.
|
|
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 | | 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.
| 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 TcRnTypes.tcg_type_env_var for
TcRunTypes.TcGblEnv
| hsc_global_rdr_env :: GlobalRdrEnv | A 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 :: TypeEnv | Typing information about all those things in global scope.
Not necessarily just the things directly imported by the module
being compiled!
|
|
|
|
|
hscEPS :: HscEnv -> IO ExternalPackageState |
|
type FinderCache = ModuleNameEnv FindResult |
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 |
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 [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 PackageId | The module was not found in this package
|
|
|
|
type ModLocationCache = ModuleEnv ModLocation |
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 |
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 | | 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.
|
| Instances | |
|
|
pprTarget :: Target -> SDoc |
|
pprTargetId :: TargetId -> SDoc |
|
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.
|
|
emptyMG :: ModuleGraph |
|
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 | | 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_vect_info :: !VectInfo | Module vectorisation information
|
|
|
|
|
emptyModDetails :: 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 dicarded.
| Constructors | ModGuts | | 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.mkIface)
| 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_types :: !TypeEnv | Types 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 :: !ForeignStubs | Foreign exports declared in this module
| mg_warns :: !Warnings | Warnings declared in the module
| mg_hpc_info :: !HpcInfo | Coverage tick boxes in the module
| mg_modBreaks :: !ModBreaks | Breakpoints for the module
| 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
|
|
|
|
|
data CoreModule |
A CoreModule consists of just the fields of a ModGuts that are needed for
the GHC.compileToCoreModule interface.
| Constructors | CoreModule | | cm_module :: !Module | Module name
| cm_types :: !TypeEnv | Type environment for types declared in this module
| cm_binds :: [CoreBind] | Declarations
| cm_imports :: ![Module] | Imports
|
|
| Instances | |
|
|
data CgGuts |
A restricted form of ModGuts for code generation purposes
| Constructors | CgGuts | | 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 :: [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 :: !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 |
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 [(ModuleName, Bool, SrcSpan)] |
Records the modules directly imported by a module for extracting e.g. usage information
|
|
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
- An external-core source module
| Constructors | ModSummary | | 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 ModuleName] | Source imports of the module
| ms_imps :: [Located ModuleName] | Non-source imports of the module
| 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
|
|
| Instances | |
|
|
ms_mod_name :: ModSummary -> ModuleName |
|
showModMsg :: HscTarget -> Bool -> ModSummary -> String |
|
isBootSummary :: ModSummary -> Bool |
Did this ModSummary originate from a hs-boot file?
|
|
msHsFilePath :: ModSummary -> FilePath |
|
msHiFilePath :: ModSummary -> FilePath |
|
msObjFilePath :: ModSummary -> FilePath |
|
Information about the module being compiled
|
|
data HscSource |
Constructors | HsSrcFile | | HsBootFile | | ExtCoreFile | |
| Instances | |
|
|
isHsBoot :: HscSource -> Bool |
|
hscSourceString :: HscSource -> String |
|
State relating to modules in this package
|
|
type HomePackageTable = ModuleNameEnv HomeModInfo |
Helps us find information about modules in the home package
|
|
data HomeModInfo |
Information about modules in the package being compiled
| Constructors | HomeModInfo | | 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 (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 :: HomePackageTable |
|
hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([Instance], [FamInst]) |
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] |
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 | | 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 :: !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_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 |
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 -> EpsStats |
Add stats for one newly-read interface
|
|
type PackageTypeEnv = TypeEnv |
|
type PackageIfaceTable = ModuleEnv ModIface |
Helps us find information about modules in the imported packages
|
|
emptyPackageIfaceTable :: 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 |
|
type PackageInstEnv = InstEnv |
|
type PackageRuleBase = RuleBase |
|
Interactive context
|
|
data InteractiveContext |
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 :: GlobalRdrEnv | The 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 :: TyVarSet | Skolem 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 :: InteractiveContext |
|
icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified |
|
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
|
|
extendInteractiveContext :: InteractiveContext -> [Id] -> TyVarSet -> InteractiveContext |
|
substInteractiveContext :: InteractiveContext -> TvSubst -> InteractiveContext |
|
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 | | 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_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)
| 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 :: !Fingerprint | Hash of export list
| mi_fixities :: [(OccName, Fixity)] | Fixities
| mi_warns :: Warnings | Warnings
| 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 :: !Fingerprint | Hash for orphan rules and
class and family instances
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.
|
|
| Instances | |
|
|
mkIfaceWarnCache :: Warnings -> Name -> 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 -> Fixity |
Creates cached lookup for the mi_fix_fn field of ModIface
|
|
emptyIfaceWarnCache :: Name -> Maybe WarningTxt |
|
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 | | Instances | |
|
|
lookupFixity :: FixityEnv -> Name -> Fixity |
|
emptyFixityEnv :: FixityEnv |
|
TyThings and type environments
|
|
data TyThing |
A typecheckable-thing, essentially anything that has a name
| Constructors | | Instances | |
|
|
tyThingClass :: TyThing -> Class |
Get the Class from a TyThing if it is a class thing. Panics otherwise
|
|
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
|
|
tyThingId :: TyThing -> Id |
Get the Id from a TyThing if it is a id *or* data constructor thing. Panics otherwise
|
|
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
|
|
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] |
|
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
| | Methods | | | Instances | |
|
|
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
|
|
type IsBootInterface = Bool |
Did this module originate from a *-boot file?
|
|
data Usage |
Records modules that we depend on by making a direct import from
| Constructors | UsagePackageModule | Module from another package
| | UsageHomeModule | Module from the current package
| usg_mod_name :: ModuleName | Name of the module
| usg_mod_hash :: 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
|
|
| Instances | |
|
|
data Dependencies |
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)
|
|
| Instances | |
|
|
noDependencies :: Dependencies |
|
data NameCache |
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 :: 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) |
Per-module cache of original OccNames given Names
|
|
type OrigIParamCache = FiniteMap (IPName OccName) (IPName Name) |
Module-local cache of implicit parameter OccNames given Names
|
|
type Avails = [AvailInfo] |
A collection of AvailInfo - several things that are "available"
|
|
availsToNameSet :: [AvailInfo] -> NameSet |
|
availsToNameEnv :: [AvailInfo] -> NameEnv AvailInfo |
|
availName :: GenAvailInfo name -> name |
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] |
All names made available by the availability information
|
|
data GenAvailInfo name |
Records what things are available, i.e. in scope
| Constructors | Avail name | An 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, ==, /=]
|
| Instances | |
|
|
type AvailInfo = GenAvailInfo Name |
Named things that are available
|
|
type RdrAvailInfo = GenAvailInfo OccName |
RdrNamed things that are available
|
|
type IfaceExport = (Module, [GenAvailInfo OccName]) |
The original names declared of a certain module that are exported
|
|
Warnings
|
|
data Warnings |
Warning information for a module
| Constructors | | Instances | |
|
|
data WarningTxt |
Constructors | | Instances | |
|
|
plusWarns :: Warnings -> Warnings -> Warnings |
|
Linker stuff
|
|
data Linkable |
Information we can use to dynamically link modules into the compiler
| Constructors | LM | | 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.
XXX: Do items get removed from this list when they get linked?
|
|
| Instances | |
|
|
isObjectLinkable :: Linkable -> Bool |
|
data Unlinked |
Objects which have yet to be linked by the compiler
| Constructors | | Instances | |
|
|
data CompiledByteCode |
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 | | hpcInfoTickCount :: Int | | hpcInfoHash :: Int | |
| NoHpcInfo | | hpcUsed :: AnyHpcUsage | Is hpc used anywhere on the module *tree*?
|
|
|
|
|
emptyHpcInfo :: AnyHpcUsage -> HpcInfo |
|
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 given module
| Constructors | ModBreaks | | 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.
|
|
|
|
|
type BreakIndex = Int |
Breakpoint index
|
|
emptyModBreaks :: ModBreaks |
|
Vectorisation information
|
|
data VectInfo |
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 |
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
|
|
| Instances | |
|
|
noVectInfo :: VectInfo |
|
plusVectInfo :: VectInfo -> VectInfo -> VectInfo |
|
noIfaceVectInfo :: IfaceVectInfo |
|
Produced by Haddock version 2.4.2 |