Safe Haskell | None |
---|---|
Language | Haskell98 |
- compilation state
- Hsc monad
- Information about modules
- Information about the module being compiled
- State relating to modules in this package
- State relating to known packages
- Annotations
- Interactive context
- Interfaces
- Fixity
- TyThings and type environments
- MonadThings
- Information on imports and exports
- Warnings
- Linker stuff
- Program coverage
- Breakpoints
- Vectorisation information
- Safe Haskell information
- result of the parser
- Compilation errors and warnings
Types for the per-module compiler
- data HscEnv = HscEnv {
- hsc_dflags :: DynFlags
- hsc_targets :: [Target]
- hsc_mod_graph :: ModuleGraph
- hsc_IC :: InteractiveContext
- hsc_HPT :: HomePackageTable
- hsc_EPS :: !(IORef ExternalPackageState)
- hsc_NC :: !(IORef NameCache)
- hsc_FC :: !(IORef FinderCache)
- hsc_MLC :: !(IORef ModLocationCache)
- hsc_type_env_var :: Maybe (Module, IORef TypeEnv)
- hscEPS :: HscEnv -> IO ExternalPackageState
- type FinderCache = ModuleNameEnv FindResult
- data FindResult
- = Found ModLocation Module
- | NoPackage PackageId
- | FoundMultiple [PackageId]
- | NotFound {
- fr_paths :: [FilePath]
- fr_pkg :: Maybe PackageId
- fr_mods_hidden :: [PackageId]
- fr_pkgs_hidden :: [PackageId]
- fr_suggestions :: [Module]
- type ModLocationCache = ModuleEnv ModLocation
- data Target = Target {}
- data TargetId
- pprTarget :: Target -> SDoc
- pprTargetId :: TargetId -> SDoc
- type ModuleGraph = [ModSummary]
- emptyMG :: ModuleGraph
- data HscStatus
- newtype Hsc a = Hsc (HscEnv -> WarningMessages -> IO (a, WarningMessages))
- runHsc :: HscEnv -> Hsc a -> IO a
- runInteractiveHsc :: HscEnv -> Hsc a -> IO a
- data ModDetails = ModDetails {
- md_exports :: [AvailInfo]
- md_types :: !TypeEnv
- md_insts :: ![ClsInst]
- md_fam_insts :: ![FamInst]
- md_rules :: ![CoreRule]
- md_anns :: ![Annotation]
- md_vect_info :: !VectInfo
- emptyModDetails :: ModDetails
- data ModGuts = ModGuts {
- mg_module :: !Module
- mg_boot :: IsBootInterface
- mg_exports :: ![AvailInfo]
- mg_deps :: !Dependencies
- mg_dir_imps :: !ImportedMods
- mg_used_names :: !NameSet
- mg_used_th :: !Bool
- mg_rdr_env :: !GlobalRdrEnv
- mg_fix_env :: !FixityEnv
- mg_tcs :: ![TyCon]
- mg_insts :: ![ClsInst]
- mg_fam_insts :: ![FamInst]
- mg_patsyns :: ![PatSyn]
- mg_rules :: ![CoreRule]
- mg_binds :: !CoreProgram
- mg_foreign :: !ForeignStubs
- mg_warns :: !Warnings
- mg_anns :: [Annotation]
- mg_hpc_info :: !HpcInfo
- mg_modBreaks :: !ModBreaks
- mg_vect_decls :: ![CoreVect]
- mg_vect_info :: !VectInfo
- mg_inst_env :: InstEnv
- mg_fam_inst_env :: FamInstEnv
- mg_safe_haskell :: SafeHaskellMode
- mg_trust_pkg :: Bool
- mg_dependent_files :: [FilePath]
- data CgGuts = CgGuts {
- cg_module :: !Module
- cg_tycons :: [TyCon]
- cg_binds :: CoreProgram
- cg_foreign :: !ForeignStubs
- cg_dep_pkgs :: ![PackageId]
- cg_hpc_info :: !HpcInfo
- cg_modBreaks :: !ModBreaks
- data ForeignStubs
- appendStubC :: ForeignStubs -> SDoc -> ForeignStubs
- type ImportedMods = ModuleEnv [ImportedModsVal]
- type ImportedModsVal = (ModuleName, Bool, SrcSpan, IsSafeImport)
- data ModSummary = ModSummary {}
- ms_imps :: ModSummary -> [Located (ImportDecl RdrName)]
- ms_mod_name :: ModSummary -> ModuleName
- showModMsg :: DynFlags -> HscTarget -> Bool -> ModSummary -> String
- isBootSummary :: ModSummary -> Bool
- msHsFilePath :: ModSummary -> FilePath
- msHiFilePath :: ModSummary -> FilePath
- msObjFilePath :: ModSummary -> FilePath
- data SourceModified
- data HscSource
- isHsBoot :: HscSource -> Bool
- hscSourceString :: HscSource -> String
- type HomePackageTable = ModuleNameEnv HomeModInfo
- data HomeModInfo = HomeModInfo {
- hm_iface :: !ModIface
- hm_details :: !ModDetails
- hm_linkable :: !(Maybe Linkable)
- emptyHomePackageTable :: HomePackageTable
- hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [FamInst])
- hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule]
- hptVectInfo :: HscEnv -> VectInfo
- pprHPT :: HomePackageTable -> SDoc
- hptObjs :: HomePackageTable -> [FilePath]
- data ExternalPackageState = EPS {
- eps_is_boot :: !(ModuleNameEnv (ModuleName, IsBootInterface))
- eps_PIT :: !PackageIfaceTable
- eps_PTE :: !PackageTypeEnv
- eps_inst_env :: !PackageInstEnv
- eps_fam_inst_env :: !PackageFamInstEnv
- eps_rule_base :: !PackageRuleBase
- eps_vect_info :: !PackageVectInfo
- eps_ann_env :: !PackageAnnEnv
- eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv)
- eps_stats :: !EpsStats
- data EpsStats = EpsStats {
- n_ifaces_in :: !Int
- n_decls_in :: !Int
- n_decls_out :: !Int
- n_rules_in :: !Int
- n_rules_out :: !Int
- n_insts_in :: !Int
- n_insts_out :: !Int
- addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
- type PackageTypeEnv = TypeEnv
- type PackageIfaceTable = ModuleEnv ModIface
- emptyPackageIfaceTable :: PackageIfaceTable
- lookupIfaceByModule :: DynFlags -> HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
- emptyModIface :: Module -> ModIface
- type PackageInstEnv = InstEnv
- type PackageFamInstEnv = FamInstEnv
- type PackageRuleBase = RuleBase
- mkSOName :: Platform -> FilePath -> FilePath
- mkHsSOName :: Platform -> FilePath -> FilePath
- soExt :: Platform -> FilePath
- prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv
- data InteractiveContext = InteractiveContext {
- ic_dflags :: DynFlags
- ic_mod_index :: Int
- ic_imports :: [InteractiveImport]
- ic_tythings :: [TyThing]
- ic_rn_gbl_env :: GlobalRdrEnv
- ic_instances :: ([ClsInst], [FamInst])
- ic_fix_env :: FixityEnv
- ic_default :: Maybe [Type]
- ic_resume :: [Resume]
- ic_monad :: Name
- ic_int_print :: Name
- ic_cwd :: Maybe FilePath
- emptyInteractiveContext :: DynFlags -> InteractiveContext
- icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified
- icInScopeTTs :: InteractiveContext -> [TyThing]
- icExtendGblRdrEnv :: GlobalRdrEnv -> [TyThing] -> GlobalRdrEnv
- extendInteractiveContext :: InteractiveContext -> [TyThing] -> InteractiveContext
- substInteractiveContext :: InteractiveContext -> TvSubst -> InteractiveContext
- setInteractivePrintName :: InteractiveContext -> Name -> InteractiveContext
- icInteractiveModule :: InteractiveContext -> Module
- data InteractiveImport
- setInteractivePackage :: HscEnv -> HscEnv
- mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified
- pprModulePrefix :: PprStyle -> Module -> OccName -> SDoc
- data ModIface = ModIface {
- mi_module :: !Module
- mi_iface_hash :: !Fingerprint
- mi_mod_hash :: !Fingerprint
- mi_flag_hash :: !Fingerprint
- mi_orphan :: !WhetherHasOrphans
- mi_finsts :: !WhetherHasFamInst
- mi_boot :: !IsBootInterface
- mi_deps :: Dependencies
- mi_usages :: [Usage]
- mi_exports :: ![IfaceExport]
- mi_exp_hash :: !Fingerprint
- mi_used_th :: !Bool
- mi_fixities :: [(OccName, Fixity)]
- mi_warns :: Warnings
- mi_anns :: [IfaceAnnotation]
- mi_decls :: [(Fingerprint, IfaceDecl)]
- mi_globals :: !(Maybe GlobalRdrEnv)
- mi_insts :: [IfaceClsInst]
- mi_fam_insts :: [IfaceFamInst]
- mi_rules :: [IfaceRule]
- mi_orphan_hash :: !Fingerprint
- mi_vect_info :: !IfaceVectInfo
- mi_warn_fn :: Name -> Maybe WarningTxt
- mi_fix_fn :: OccName -> Fixity
- mi_hash_fn :: OccName -> Maybe (OccName, Fingerprint)
- mi_hpc :: !AnyHpcUsage
- mi_trust :: !IfaceTrustInfo
- mi_trust_pkg :: !Bool
- mkIfaceWarnCache :: Warnings -> Name -> Maybe WarningTxt
- mkIfaceHashCache :: [(Fingerprint, IfaceDecl)] -> OccName -> Maybe (OccName, Fingerprint)
- mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Fixity
- emptyIfaceWarnCache :: Name -> Maybe WarningTxt
- type FixityEnv = NameEnv FixItem
- data FixItem = FixItem OccName Fixity
- lookupFixity :: FixityEnv -> Name -> Fixity
- emptyFixityEnv :: FixityEnv
- data TyThing
- tyThingAvailInfo :: TyThing -> AvailInfo
- tyThingTyCon :: TyThing -> TyCon
- tyThingDataCon :: TyThing -> DataCon
- tyThingId :: TyThing -> Id
- tyThingCoAxiom :: TyThing -> CoAxiom Branched
- tyThingParent_maybe :: TyThing -> Maybe TyThing
- tyThingsTyVars :: [TyThing] -> TyVarSet
- implicitTyThings :: TyThing -> [TyThing]
- implicitTyConThings :: TyCon -> [TyThing]
- implicitClassThings :: Class -> [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
- typeEnvFromEntities :: [Id] -> [TyCon] -> [FamInst] -> TypeEnv
- mkTypeEnvWithImplicits :: [TyThing] -> TypeEnv
- extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv
- extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv
- extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv
- lookupTypeEnv :: TypeEnv -> Name -> Maybe TyThing
- typeEnvElts :: TypeEnv -> [TyThing]
- typeEnvTyCons :: TypeEnv -> [TyCon]
- typeEnvIds :: TypeEnv -> [Id]
- typeEnvPatSyns :: TypeEnv -> [PatSyn]
- typeEnvDataCons :: TypeEnv -> [DataCon]
- typeEnvCoAxioms :: TypeEnv -> [CoAxiom Branched]
- typeEnvClasses :: TypeEnv -> [Class]
- class Monad m => MonadThings m where
- lookupThing :: Name -> m TyThing
- lookupId :: Name -> m Id
- lookupDataCon :: Name -> m DataCon
- lookupTyCon :: Name -> m TyCon
- type WhetherHasOrphans = Bool
- type IsBootInterface = Bool
- data Usage
- = UsagePackageModule { }
- | UsageHomeModule { }
- | UsageFile { }
- data Dependencies = Deps {
- dep_mods :: [(ModuleName, IsBootInterface)]
- dep_pkgs :: [(PackageId, Bool)]
- dep_orphs :: [Module]
- dep_finsts :: [Module]
- noDependencies :: Dependencies
- data NameCache = NameCache {
- nsUniqs :: !UniqSupply
- nsNames :: !OrigNameCache
- type OrigNameCache = ModuleEnv (OccEnv Name)
- type IfaceExport = AvailInfo
- data Warnings
- = NoWarnings
- | WarnAll WarningTxt
- | WarnSome [(OccName, WarningTxt)]
- data WarningTxt
- plusWarns :: Warnings -> Warnings -> Warnings
- data Linkable = LM {}
- isObjectLinkable :: Linkable -> Bool
- linkableObjs :: Linkable -> [FilePath]
- data Unlinked
- data CompiledByteCode
- isObject :: Unlinked -> Bool
- nameOfObject :: Unlinked -> FilePath
- isInterpretable :: Unlinked -> Bool
- byteCodeOfObject :: Unlinked -> CompiledByteCode
- data HpcInfo
- emptyHpcInfo :: AnyHpcUsage -> HpcInfo
- isHpcUsed :: HpcInfo -> AnyHpcUsage
- type AnyHpcUsage = Bool
- data ModBreaks = ModBreaks {
- modBreaks_flags :: BreakArray
- modBreaks_locs :: !(Array BreakIndex SrcSpan)
- modBreaks_vars :: !(Array BreakIndex [OccName])
- modBreaks_decls :: !(Array BreakIndex [String])
- type BreakIndex = Int
- emptyModBreaks :: ModBreaks
- data VectInfo = VectInfo {}
- data IfaceVectInfo = IfaceVectInfo {}
- noVectInfo :: VectInfo
- plusVectInfo :: VectInfo -> VectInfo -> VectInfo
- noIfaceVectInfo :: IfaceVectInfo
- isNoIfaceVectInfo :: IfaceVectInfo -> Bool
- data IfaceTrustInfo
- getSafeMode :: IfaceTrustInfo -> SafeHaskellMode
- setSafeMode :: SafeHaskellMode -> IfaceTrustInfo
- noIfaceTrustInfo :: IfaceTrustInfo
- trustInfoToNum :: IfaceTrustInfo -> Word8
- numToTrustInfo :: Word8 -> IfaceTrustInfo
- type IsSafeImport = Bool
- data HsParsedModule = HsParsedModule {
- hpm_module :: Located (HsModule RdrName)
- hpm_src_files :: [FilePath]
- data SourceError
- data GhcApiError
- mkSrcErr :: ErrorMessages -> SourceError
- srcErrorMessages :: SourceError -> ErrorMessages
- mkApiErr :: DynFlags -> SDoc -> GhcApiError
- throwOneError :: MonadIO m => ErrMsg -> m ab
- handleSourceError :: ExceptionMonad m => (SourceError -> m a) -> m a -> m a
- handleFlagWarnings :: DynFlags -> [Located String] -> IO ()
- printOrThrowWarnings :: DynFlags -> Bag WarnMsg -> IO ()
compilation state
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.
HscEnv | |
|
hscEPS :: HscEnv -> IO ExternalPackageState Source
Retrieve the ExternalPackageState cache.
type FinderCache = ModuleNameEnv FindResult Source
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.
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 ModLocation Source
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.
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).
Target | |
|
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. |
pprTargetId :: TargetId -> SDoc Source
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.
Status of a compilation to hard-code
Hsc monad
Hsc (HscEnv -> WarningMessages -> IO (a, WarningMessages)) |
runInteractiveHsc :: HscEnv -> Hsc a -> IO a Source
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
.
ModDetails | |
|
emptyModDetails :: ModDetails Source
Constructs an empty ModDetails
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.
ModGuts | |
|
A restricted form of ModGuts
for code generation purposes
CgGuts | |
|
data ForeignStubs Source
Foreign export stubs
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 |
appendStubC :: ForeignStubs -> SDoc -> ForeignStubs Source
type ImportedMods = ModuleEnv [ImportedModsVal] Source
Records the modules directly imported by a module for extracting e.g. usage information
type ImportedModsVal = (ModuleName, Bool, SrcSpan, IsSafeImport) Source
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
ModSummary | |
|
ms_imps :: ModSummary -> [Located (ImportDecl RdrName)] Source
showModMsg :: DynFlags -> HscTarget -> Bool -> ModSummary -> String Source
isBootSummary :: ModSummary -> Bool Source
Did this ModSummary
originate from a hs-boot file?
msHsFilePath :: ModSummary -> FilePath Source
msHiFilePath :: ModSummary -> FilePath Source
data SourceModified Source
Indicates whether a given module's source has been modified since it was last compiled.
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
hscSourceString :: HscSource -> String Source
State relating to modules in this package
type HomePackageTable = ModuleNameEnv HomeModInfo Source
Helps us find information about modules in the home package
data HomeModInfo Source
Information about modules in the package being compiled
HomeModInfo | |
|
emptyHomePackageTable :: HomePackageTable Source
Constructs an empty HomePackageTable
hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [FamInst]) Source
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] Source
Get rules from modules "below" this one (in the dependency sense)
hptVectInfo :: HscEnv -> VectInfo Source
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.
pprHPT :: HomePackageTable -> SDoc Source
hptObjs :: HomePackageTable -> [FilePath] Source
State relating to known packages
data ExternalPackageState Source
Information about other packages that we have slurped in by reading their interface files
EPS | |
|
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
EpsStats | |
|
addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats Source
Add stats for one newly-read interface
type PackageTypeEnv = TypeEnv Source
type PackageIfaceTable = ModuleEnv ModIface Source
Helps us find information about modules in the imported packages
emptyPackageIfaceTable :: PackageIfaceTable Source
Constructs an empty PackageIfaceTable
lookupIfaceByModule :: DynFlags -> HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface Source
emptyModIface :: Module -> ModIface Source
Constructs an empty ModIface
type PackageInstEnv = InstEnv Source
type PackageFamInstEnv = FamInstEnv Source
type PackageRuleBase = RuleBase Source
mkHsSOName :: Platform -> FilePath -> FilePath Source
Annotations
prepareAnnotations :: HscEnv -> Maybe ModGuts -> IO AnnEnv Source
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.
InteractiveContext | |
|
emptyInteractiveContext :: DynFlags -> InteractiveContext Source
Constructs an empty InteractiveContext.
icPrintUnqual :: DynFlags -> InteractiveContext -> PrintUnqualified Source
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)
icExtendGblRdrEnv :: GlobalRdrEnv -> [TyThing] -> GlobalRdrEnv Source
Add TyThings to the GlobalRdrEnv, earlier ones in the list shadowing later ones, and shadowing existing entries in the GlobalRdrEnv.
extendInteractiveContext :: InteractiveContext -> [TyThing] -> InteractiveContext Source
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
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 Source
Creates some functions that work out the best ways to format names for the user according to a set of heuristics
Interfaces
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
.
ModIface | |
|
mkIfaceWarnCache :: Warnings -> Name -> Maybe WarningTxt Source
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
Fixity
Fixity information for an Name
. We keep the OccName in the range
so that we can generate an interface from it
lookupFixity :: FixityEnv -> Name -> Fixity Source
TyThings and type environments
A typecheckable-thing, essentially anything that has a name
tyThingAvailInfo :: TyThing -> AvailInfo Source
The Names that a TyThing should bring into scope. Used to build the GlobalRdrEnv for the InteractiveContext.
tyThingTyCon :: TyThing -> TyCon Source
tyThingDataCon :: TyThing -> DataCon Source
tyThingParent_maybe :: TyThing -> Maybe TyThing Source
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.
tyThingsTyVars :: [TyThing] -> TyVarSet Source
implicitTyThings :: TyThing -> [TyThing] Source
implicitTyConThings :: TyCon -> [TyThing] Source
implicitClassThings :: Class -> [TyThing] Source
isImplicitTyThing :: TyThing -> Bool Source
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.
lookupType :: DynFlags -> HomePackageTable -> PackageTypeEnv -> Name -> Maybe TyThing Source
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
mkTypeEnvWithImplicits :: [TyThing] -> TypeEnv Source
extendTypeEnv :: TypeEnv -> TyThing -> TypeEnv Source
extendTypeEnvList :: TypeEnv -> [TyThing] -> TypeEnv Source
extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv Source
typeEnvElts :: TypeEnv -> [TyThing] Source
typeEnvTyCons :: TypeEnv -> [TyCon] Source
typeEnvIds :: TypeEnv -> [Id] Source
typeEnvPatSyns :: TypeEnv -> [PatSyn] Source
typeEnvDataCons :: TypeEnv -> [DataCon] Source
typeEnvCoAxioms :: TypeEnv -> [CoAxiom Branched] Source
typeEnvClasses :: TypeEnv -> [Class] Source
MonadThings
class Monad m => MonadThings m where Source
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
Information on imports and exports
type WhetherHasOrphans = Bool Source
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 Source
Did this module originate from a *-boot file?
Records modules for which changes may force recompilation of this module See wiki: http:/ghc.haskell.orgtracghcwikiCommentaryCompiler/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
UsagePackageModule | Module from another package |
| |
UsageHomeModule | Module from the current package
| A file upon which the module depends, e.g. a CPP #include, or using TH's
|
| |
UsageFile | |
|
data Dependencies Source
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.
Deps | |
|
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.
NameCache | |
|
type OrigNameCache = ModuleEnv (OccEnv Name) Source
type IfaceExport = AvailInfo Source
The original names declared of a certain module that are exported
Warnings
Warning information for a module
NoWarnings | Nothing deprecated |
WarnAll WarningTxt | Whole module deprecated |
WarnSome [(OccName, WarningTxt)] | Some specific things deprecated |
data WarningTxt Source
Linker stuff
Information we can use to dynamically link modules into the compiler
LM | |
|
isObjectLinkable :: Linkable -> Bool Source
linkableObjs :: Linkable -> [FilePath] Source
Objects which have yet to be linked by the compiler
nameOfObject :: Unlinked -> FilePath Source
Retrieve the filename of the linkable if possible. Panic if it is a byte-code object
isInterpretable :: Unlinked -> Bool Source
Is this a bytecode linkable with no file on disk?
byteCodeOfObject :: Unlinked -> CompiledByteCode Source
Retrieve the compiled byte-code if possible. Panic if it is a file-based linkable
Program coverage
Information about a modules use of Haskell Program Coverage
HpcInfo | |
| |
NoHpcInfo | |
|
emptyHpcInfo :: AnyHpcUsage -> HpcInfo Source
isHpcUsed :: HpcInfo -> AnyHpcUsage Source
Find out if HPC is used by this module or any of the modules it depends upon
type AnyHpcUsage = Bool Source
This is used to signal if one of my imports used HPC instrumentation even if there is no module-local HPC usage
Breakpoints
All the information about the breakpoints for a given module
ModBreaks | |
|
type BreakIndex = Int Source
Breakpoint index
emptyModBreaks :: ModBreaks Source
Construct an empty ModBreaks
Vectorisation information
Vectorisation information for ModGuts
, ModDetails
and ExternalPackageState
; see also
documentation at GlobalEnv
.
NB: The following tables may also include Var
s, TyCon
s and DataCon
s from imported modules,
which have been subsequently vectorised in the current module.
VectInfo | |
|
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).
IfaceVectInfo | |
|
plusVectInfo :: VectInfo -> VectInfo -> VectInfo Source
Safe Haskell information
data IfaceTrustInfo Source
Safe Haskell information for ModIface
Simply a wrapper around SafeHaskellMode to sepperate iface and flags
type IsSafeImport = Bool Source
Is an import a safe import?
result of the parser
data HsParsedModule Source
HsParsedModule | |
|
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 SourceError
s 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.
mkApiErr :: DynFlags -> SDoc -> GhcApiError Source
throwOneError :: MonadIO m => ErrMsg -> m ab Source
:: 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.