Safe Haskell | None |
---|---|
Language | Haskell2010 |
- compilation state
- ModuleGraph
- Hsc monad
- Information about modules
- Information about the module being compiled
- State relating to modules in this package
- State relating to known packages
- Metaprogramming
- Annotations
- Interactive context
- Interfaces
- Fixity
- TyThings and type environments
- MonadThings
- Information on imports and exports
- Warnings
- Linker stuff
- Program coverage
- Breakpoints
- Safe Haskell information
- result of the parser
- Compilation errors and warnings
- COMPLETE signature
Types for the per-module compiler
Synopsis
- 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_type_env_var :: Maybe (Module, IORef TypeEnv)
- hsc_iserv :: MVar (Maybe IServ)
- hsc_dynLinker :: DynLinker
- hscEPS :: HscEnv -> IO ExternalPackageState
- type FinderCache = InstalledModuleEnv InstalledFindResult
- data FindResult
- = Found ModLocation Module
- | NoPackage UnitId
- | FoundMultiple [(Module, ModuleOrigin)]
- | NotFound {
- fr_paths :: [FilePath]
- fr_pkg :: Maybe UnitId
- fr_mods_hidden :: [UnitId]
- fr_pkgs_hidden :: [UnitId]
- fr_unusables :: [(UnitId, UnusablePackageReason)]
- fr_suggestions :: [ModuleSuggestion]
- data InstalledFindResult
- data Target = Target {}
- data TargetId
- type InputFileBuffer = StringBuffer
- pprTarget :: Target -> SDoc
- pprTargetId :: TargetId -> SDoc
- data HscStatus
- data IServ = IServ {
- iservPipe :: Pipe
- iservProcess :: ProcessHandle
- iservLookupSymbolCache :: IORef (UniqFM (Ptr ()))
- iservPendingFrees :: [HValueRef]
- data ModuleGraph
- emptyMG :: ModuleGraph
- mkModuleGraph :: [ModSummary] -> ModuleGraph
- extendMG :: ModuleGraph -> ModSummary -> ModuleGraph
- mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph
- mgModSummaries :: ModuleGraph -> [ModSummary]
- mgElemModule :: ModuleGraph -> Module -> Bool
- mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary
- needsTemplateHaskellOrQQ :: ModuleGraph -> Bool
- mgBootModules :: ModuleGraph -> ModuleSet
- newtype Hsc a = Hsc (HscEnv -> WarningMessages -> IO (a, WarningMessages))
- runHsc :: HscEnv -> Hsc a -> IO a
- mkInteractiveHscEnv :: HscEnv -> HscEnv
- 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_complete_sigs :: [CompleteMatch]
- emptyModDetails :: ModDetails
- data ModGuts = ModGuts {
- mg_module :: !Module
- mg_hsc_src :: HscSource
- mg_loc :: SrcSpan
- mg_exports :: ![AvailInfo]
- mg_deps :: !Dependencies
- mg_usages :: ![Usage]
- 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_foreign_files :: ![(ForeignSrcLang, FilePath)]
- mg_warns :: !Warnings
- mg_anns :: [Annotation]
- mg_complete_sigs :: [CompleteMatch]
- mg_hpc_info :: !HpcInfo
- mg_modBreaks :: !(Maybe ModBreaks)
- mg_inst_env :: InstEnv
- mg_fam_inst_env :: FamInstEnv
- mg_safe_haskell :: SafeHaskellMode
- mg_trust_pkg :: Bool
- mg_doc_hdr :: !(Maybe HsDocString)
- mg_decl_docs :: !DeclDocMap
- mg_arg_docs :: !ArgDocMap
- data CgGuts = CgGuts {
- cg_module :: !Module
- cg_tycons :: [TyCon]
- cg_binds :: CoreProgram
- cg_foreign :: !ForeignStubs
- cg_foreign_files :: ![(ForeignSrcLang, FilePath)]
- cg_dep_pkgs :: ![InstalledUnitId]
- cg_hpc_info :: !HpcInfo
- cg_modBreaks :: !(Maybe ModBreaks)
- cg_spt_entries :: [SptEntry]
- data ForeignStubs
- appendStubC :: ForeignStubs -> SDoc -> ForeignStubs
- type ImportedMods = ModuleEnv [ImportedBy]
- data ImportedBy
- importedByUser :: [ImportedBy] -> [ImportedModsVal]
- data ImportedModsVal = ImportedModsVal {}
- data SptEntry = SptEntry Id Fingerprint
- data ForeignSrcLang
- phaseForeignLanguage :: Phase -> Maybe ForeignSrcLang
- data ModSummary = ModSummary {
- ms_mod :: Module
- ms_hsc_src :: HscSource
- ms_location :: ModLocation
- ms_hs_date :: UTCTime
- ms_obj_date :: Maybe UTCTime
- ms_iface_date :: Maybe UTCTime
- ms_hie_date :: Maybe UTCTime
- ms_srcimps :: [(Maybe FastString, Located ModuleName)]
- ms_textual_imps :: [(Maybe FastString, Located ModuleName)]
- ms_parsed_mod :: Maybe HsParsedModule
- ms_hspp_file :: FilePath
- ms_hspp_opts :: DynFlags
- ms_hspp_buf :: Maybe StringBuffer
- ms_imps :: ModSummary -> [(Maybe FastString, Located ModuleName)]
- ms_installed_mod :: ModSummary -> InstalledModule
- ms_mod_name :: ModSummary -> ModuleName
- ms_home_imps :: ModSummary -> [Located ModuleName]
- home_imps :: [(Maybe FastString, Located ModuleName)] -> [Located ModuleName]
- ms_home_allimps :: ModSummary -> [ModuleName]
- ms_home_srcimps :: ModSummary -> [Located ModuleName]
- showModMsg :: DynFlags -> HscTarget -> Bool -> ModSummary -> String
- isBootSummary :: ModSummary -> Bool
- msHsFilePath :: ModSummary -> FilePath
- msHiFilePath :: ModSummary -> FilePath
- msObjFilePath :: ModSummary -> FilePath
- data SourceModified
- isTemplateHaskellOrQQNonBoot :: ModSummary -> Bool
- data HscSource
- isHsBootOrSig :: HscSource -> Bool
- isHsigFile :: HscSource -> Bool
- hscSourceString :: HscSource -> String
- type HomePackageTable = DModuleNameEnv HomeModInfo
- data HomeModInfo = HomeModInfo {
- hm_iface :: !ModIface
- hm_details :: !ModDetails
- hm_linkable :: !(Maybe Linkable)
- emptyHomePackageTable :: HomePackageTable
- lookupHpt :: HomePackageTable -> ModuleName -> Maybe HomeModInfo
- eltsHpt :: HomePackageTable -> [HomeModInfo]
- filterHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> HomePackageTable
- allHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> Bool
- mapHpt :: (HomeModInfo -> HomeModInfo) -> HomePackageTable -> HomePackageTable
- delFromHpt :: HomePackageTable -> ModuleName -> HomePackageTable
- addToHpt :: HomePackageTable -> ModuleName -> HomeModInfo -> HomePackageTable
- addListToHpt :: HomePackageTable -> [(ModuleName, HomeModInfo)] -> HomePackageTable
- lookupHptDirectly :: HomePackageTable -> Unique -> Maybe HomeModInfo
- listToHpt :: [(ModuleName, HomeModInfo)] -> HomePackageTable
- hptCompleteSigs :: HscEnv -> [CompleteMatch]
- hptInstances :: HscEnv -> (ModuleName -> Bool) -> ([ClsInst], [FamInst])
- hptRules :: HscEnv -> [(ModuleName, IsBootInterface)] -> [CoreRule]
- pprHPT :: HomePackageTable -> SDoc
- data ExternalPackageState = EPS {
- eps_is_boot :: !(ModuleNameEnv (ModuleName, IsBootInterface))
- eps_PIT :: !PackageIfaceTable
- eps_free_holes :: InstalledModuleEnv (UniqDSet ModuleName)
- eps_PTE :: !PackageTypeEnv
- eps_inst_env :: !PackageInstEnv
- eps_fam_inst_env :: !PackageFamInstEnv
- eps_rule_base :: !PackageRuleBase
- eps_ann_env :: !PackageAnnEnv
- eps_complete_matches :: !PackageCompleteMatchMap
- eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv)
- eps_stats :: !EpsStats
- data EpsStats = EpsStats {}
- addEpsInStats :: EpsStats -> Int -> Int -> Int -> EpsStats
- type PackageTypeEnv = TypeEnv
- type PackageIfaceTable = ModuleEnv ModIface
- emptyPackageIfaceTable :: PackageIfaceTable
- lookupIfaceByModule :: HomePackageTable -> PackageIfaceTable -> Module -> Maybe ModIface
- emptyPartialModIface :: Module -> PartialModIface
- emptyFullModIface :: Module -> ModIface
- lookupHptByModule :: HomePackageTable -> Module -> Maybe HomeModInfo
- type PackageInstEnv = InstEnv
- type PackageFamInstEnv = FamInstEnv
- type PackageRuleBase = RuleBase
- type PackageCompleteMatchMap = CompleteMatchMap
- mkSOName :: Platform -> FilePath -> FilePath
- mkHsSOName :: Platform -> FilePath -> FilePath
- soExt :: Platform -> FilePath
- data MetaRequest
- = MetaE (LHsExpr GhcPs -> MetaResult)
- | MetaP (LPat GhcPs -> MetaResult)
- | MetaT (LHsType GhcPs -> MetaResult)
- | MetaD ([LHsDecl GhcPs] -> MetaResult)
- | MetaAW (Serialized -> MetaResult)
- data MetaResult
- metaRequestE :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LHsExpr GhcPs)
- metaRequestP :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LPat GhcPs)
- metaRequestT :: Functor f => MetaHook f -> LHsExpr GhcTc -> f (LHsType GhcPs)
- metaRequestD :: Functor f => MetaHook f -> LHsExpr GhcTc -> f [LHsDecl GhcPs]
- metaRequestAW :: Functor f => MetaHook f -> LHsExpr GhcTc -> f Serialized
- type MetaHook f = MetaRequest -> LHsExpr GhcTc -> f MetaResult
- 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] -> [ClsInst] -> [FamInst] -> Maybe [Type] -> FixityEnv -> InteractiveContext
- extendInteractiveContextWithIds :: InteractiveContext -> [Id] -> InteractiveContext
- substInteractiveContext :: InteractiveContext -> TCvSubst -> InteractiveContext
- setInteractivePrintName :: InteractiveContext -> Name -> InteractiveContext
- icInteractiveModule :: InteractiveContext -> Module
- data InteractiveImport
- setInteractivePackage :: HscEnv -> HscEnv
- mkPrintUnqualified :: DynFlags -> GlobalRdrEnv -> PrintUnqualified
- pprModulePrefix :: PprStyle -> Module -> OccName -> SDoc
- mkQualPackage :: DynFlags -> QueryQualifyPackage
- mkQualModule :: DynFlags -> QueryQualifyModule
- pkgQual :: DynFlags -> PrintUnqualified
- type ModIface = ModIface_ 'ModIfaceFinal
- type PartialModIface = ModIface_ 'ModIfaceCore
- data ModIface_ (phase :: ModIfacePhase) = ModIface {
- mi_module :: !Module
- mi_sig_of :: !(Maybe Module)
- mi_hsc_src :: !HscSource
- mi_deps :: Dependencies
- mi_usages :: [Usage]
- mi_exports :: ![IfaceExport]
- mi_used_th :: !Bool
- mi_fixities :: [(OccName, Fixity)]
- mi_warns :: Warnings
- mi_anns :: [IfaceAnnotation]
- mi_decls :: [IfaceDeclExts phase]
- mi_globals :: !(Maybe GlobalRdrEnv)
- mi_insts :: [IfaceClsInst]
- mi_fam_insts :: [IfaceFamInst]
- mi_rules :: [IfaceRule]
- mi_hpc :: !AnyHpcUsage
- mi_trust :: !IfaceTrustInfo
- mi_trust_pkg :: !Bool
- mi_complete_sigs :: [IfaceCompleteMatch]
- mi_doc_hdr :: Maybe HsDocString
- mi_decl_docs :: DeclDocMap
- mi_arg_docs :: ArgDocMap
- mi_final_exts :: !(IfaceBackendExts phase)
- data ModIfaceBackend = ModIfaceBackend {
- mi_iface_hash :: !Fingerprint
- mi_mod_hash :: !Fingerprint
- mi_flag_hash :: !Fingerprint
- mi_opt_hash :: !Fingerprint
- mi_hpc_hash :: !Fingerprint
- mi_plugin_hash :: !Fingerprint
- mi_orphan :: !WhetherHasOrphans
- mi_finsts :: !WhetherHasFamInst
- mi_exp_hash :: !Fingerprint
- mi_orphan_hash :: !Fingerprint
- mi_warn_fn :: !(OccName -> Maybe WarningTxt)
- mi_fix_fn :: !(OccName -> Maybe Fixity)
- mi_hash_fn :: !(OccName -> Maybe (OccName, Fingerprint))
- mkIfaceWarnCache :: Warnings -> OccName -> Maybe WarningTxt
- mkIfaceHashCache :: [(Fingerprint, IfaceDecl)] -> OccName -> Maybe (OccName, Fingerprint)
- mkIfaceFixCache :: [(OccName, Fixity)] -> OccName -> Maybe Fixity
- emptyIfaceWarnCache :: OccName -> Maybe WarningTxt
- mi_boot :: ModIface -> Bool
- mi_fix :: ModIface -> OccName -> Fixity
- mi_semantic_module :: ModIface_ a -> Module
- mi_free_holes :: ModIface -> UniqDSet ModuleName
- renameFreeHoles :: UniqDSet ModuleName -> [(ModuleName, Module)] -> UniqDSet ModuleName
- 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
- tyThingConLike :: TyThing -> ConLike
- tyThingId :: TyThing -> Id
- tyThingCoAxiom :: TyThing -> CoAxiom Branched
- tyThingParent_maybe :: TyThing -> Maybe TyThing
- tyThingsTyCoVars :: [TyThing] -> TyCoVarSet
- 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
- plusTypeEnv :: TypeEnv -> TypeEnv -> 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 { }
- | UsageMergedRequirement { }
- data Dependencies = Deps {
- dep_mods :: [(ModuleName, IsBootInterface)]
- dep_pkgs :: [(InstalledUnitId, Bool)]
- dep_orphs :: [Module]
- dep_finsts :: [Module]
- dep_plgins :: [ModuleName]
- noDependencies :: Dependencies
- updNameCache :: IORef NameCache -> (NameCache -> (NameCache, c)) -> IO c
- 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 {}
- emptyModBreaks :: ModBreaks
- data IfaceTrustInfo
- getSafeMode :: IfaceTrustInfo -> SafeHaskellMode
- setSafeMode :: SafeHaskellMode -> IfaceTrustInfo
- noIfaceTrustInfo :: IfaceTrustInfo
- trustInfoToNum :: IfaceTrustInfo -> Word8
- numToTrustInfo :: Word8 -> IfaceTrustInfo
- type IsSafeImport = Bool
- data HsParsedModule = HsParsedModule {}
- data SourceError
- data GhcApiError
- mkSrcErr :: ErrorMessages -> SourceError
- srcErrorMessages :: SourceError -> ErrorMessages
- mkApiErr :: DynFlags -> SDoc -> GhcApiError
- throwOneError :: MonadIO io => ErrMsg -> io a
- throwErrors :: MonadIO io => ErrorMessages -> io a
- handleSourceError :: ExceptionMonad m => (SourceError -> m a) -> m a -> m a
- handleFlagWarnings :: DynFlags -> [Warn] -> IO ()
- printOrThrowWarnings :: DynFlags -> Bag WarnMsg -> IO ()
- data CompleteMatch = CompleteMatch {}
- type CompleteMatchMap = UniqFM [CompleteMatch]
- mkCompleteMatchMap :: [CompleteMatch] -> CompleteMatchMap
- extendCompleteMatchMap :: CompleteMatchMap -> [CompleteMatch] -> CompleteMatchMap
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--. It's also used
to store the dynamic linker state to allow for multiple linkers in the
same address space.
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 | |
|
type FinderCache = InstalledModuleEnv InstalledFindResult Source #
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 Source #
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
).
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 InstalledFindResult Source #
A compilation target.
A target may be supplied with the actual text of the module. If so, use this instead of the file contents (this is for use in an IDE where the file hasn't been saved by the user yet).
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. |
type InputFileBuffer = StringBuffer Source #
pprTargetId :: TargetId -> SDoc Source #
Status of a compilation to hard-code
HscNotGeneratingCode ModIface | Nothing to do. |
HscUpToDate ModIface | Nothing to do because code already exists. |
HscUpdateBoot ModIface | Update boot file result. |
HscUpdateSig ModIface | Generate signature file (backpack) |
HscRecomp | Recompile this module. |
|
IServ | |
|
ModuleGraph
data ModuleGraph 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.
mkModuleGraph :: [ModSummary] -> ModuleGraph Source #
extendMG :: ModuleGraph -> ModSummary -> ModuleGraph Source #
Add a ModSummary to ModuleGraph. Assumes that the new ModSummary is not an element of the ModuleGraph.
mapMG :: (ModSummary -> ModSummary) -> ModuleGraph -> ModuleGraph Source #
Map a function f
over all the ModSummaries
.
To preserve invariants f
can't change the isBoot status.
mgModSummaries :: ModuleGraph -> [ModSummary] Source #
mgElemModule :: ModuleGraph -> Module -> Bool Source #
mgLookupModule :: ModuleGraph -> Module -> Maybe ModSummary Source #
Look up a ModSummary in the ModuleGraph
needsTemplateHaskellOrQQ :: ModuleGraph -> Bool Source #
Determines whether a set of modules requires Template Haskell or Quasi Quotes
Note that if the session's DynFlags
enabled Template Haskell when
depanal
was called, then each module in the returned module graph will
have Template Haskell enabled whether it is actually needed or not.
mgBootModules :: ModuleGraph -> ModuleSet Source #
Hsc monad
Hsc (HscEnv -> WarningMessages -> IO (a, WarningMessages)) |
mkInteractiveHscEnv :: HscEnv -> HscEnv 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 [ImportedBy] Source #
Records the modules directly imported by a module for extracting e.g. usage information, and also to give better error message
data ImportedBy Source #
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.
importedByUser :: [ImportedBy] -> [ImportedModsVal] Source #
data ImportedModsVal Source #
ImportedModsVal | |
|
An entry to be inserted into a module's static pointer table. See Note [Grand plan for static forms] in StaticPtrTable.
data ForeignSrcLang Source #
Foreign formats supported by GHC via TH
LangC | C |
LangCxx | C++ |
LangObjc | Objective C |
LangObjcxx | Objective C++ |
LangAsm | Assembly language (.s) |
RawObject | Object (.o) |
Instances
Eq ForeignSrcLang | |
Defined in GHC.ForeignSrcLang.Type (==) :: ForeignSrcLang -> ForeignSrcLang -> Bool # (/=) :: ForeignSrcLang -> ForeignSrcLang -> Bool # | |
Show ForeignSrcLang | |
Defined in GHC.ForeignSrcLang.Type | |
Generic ForeignSrcLang | |
Defined in GHC.ForeignSrcLang.Type from :: ForeignSrcLang -> Rep ForeignSrcLang x Source # to :: Rep ForeignSrcLang x -> ForeignSrcLang Source # | |
type Rep ForeignSrcLang | |
Defined in GHC.ForeignSrcLang.Type type Rep ForeignSrcLang = D1 ('MetaData "ForeignSrcLang" "GHC.ForeignSrcLang.Type" "ghc-boot-th-8.10.3" 'False) ((C1 ('MetaCons "LangC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LangCxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LangObjc" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "LangObjcxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LangAsm" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RawObject" 'PrefixI 'False) (U1 :: Type -> Type)))) |
phaseForeignLanguage :: Phase -> Maybe ForeignSrcLang Source #
Foreign language of the phase if the phase deals with a foreign code
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
ModSummary | |
|
Instances
ms_imps :: ModSummary -> [(Maybe FastString, Located ModuleName)] Source #
ms_mod_name :: ModSummary -> ModuleName Source #
ms_home_imps :: ModSummary -> [Located ModuleName] Source #
All of the (possibly) home module imports from a
ModSummary
; that is to say, each of these module names
could be a home import if an appropriately named file
existed. (This is in contrast to package qualified
imports, which are guaranteed not to be home imports.)
home_imps :: [(Maybe FastString, Located ModuleName)] -> [Located ModuleName] Source #
ms_home_allimps :: ModSummary -> [ModuleName] Source #
ms_home_srcimps :: ModSummary -> [Located ModuleName] Source #
Like ms_home_imps
, but for SOURCE imports.
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 #
msObjFilePath :: 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
isHsBootOrSig :: HscSource -> Bool Source #
isHsigFile :: HscSource -> Bool Source #
hscSourceString :: HscSource -> String Source #
State relating to modules in this package
type HomePackageTable = DModuleNameEnv 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
lookupHpt :: HomePackageTable -> ModuleName -> Maybe HomeModInfo Source #
eltsHpt :: HomePackageTable -> [HomeModInfo] Source #
filterHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> HomePackageTable Source #
allHpt :: (HomeModInfo -> Bool) -> HomePackageTable -> Bool Source #
mapHpt :: (HomeModInfo -> HomeModInfo) -> HomePackageTable -> HomePackageTable Source #
addToHpt :: HomePackageTable -> ModuleName -> HomeModInfo -> HomePackageTable Source #
addListToHpt :: HomePackageTable -> [(ModuleName, HomeModInfo)] -> HomePackageTable Source #
listToHpt :: [(ModuleName, HomeModInfo)] -> HomePackageTable Source #
hptCompleteSigs :: HscEnv -> [CompleteMatch] Source #
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)
pprHPT :: HomePackageTable -> SDoc 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
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
emptyFullModIface :: Module -> ModIface Source #
type PackageInstEnv = InstEnv Source #
type PackageFamInstEnv = FamInstEnv Source #
type PackageRuleBase = RuleBase Source #
Metaprogramming
data MetaRequest Source #
The supported metaprogramming result types
MetaE (LHsExpr GhcPs -> MetaResult) | |
MetaP (LPat GhcPs -> MetaResult) | |
MetaT (LHsType GhcPs -> MetaResult) | |
MetaD ([LHsDecl GhcPs] -> MetaResult) | |
MetaAW (Serialized -> MetaResult) |
data MetaResult Source #
data constructors not exported to ensure correct result type
metaRequestAW :: Functor f => MetaHook f -> LHsExpr GhcTc -> f Serialized Source #
type MetaHook f = MetaRequest -> LHsExpr GhcTc -> f MetaResult 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 GHCi 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] -> [ClsInst] -> [FamInst] -> Maybe [Type] -> FixityEnv -> InteractiveContext Source #
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 Source #
IIDecl (ImportDecl GhcPs) | 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. |
Instances
setInteractivePackage :: HscEnv -> HscEnv Source #
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.
mkQualPackage :: DynFlags -> QueryQualifyPackage Source #
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 Source #
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 Source #
A function which only qualifies package names if necessary; but qualifies all other identifiers.
Interfaces
type PartialModIface = ModIface_ 'ModIfaceCore Source #
data ModIface_ (phase :: ModIfacePhase) Source #
A ModIface
plus a ModDetails
summarises everything we know
about a compiled module. The ModIface
is the stuff *before* linking,
and can be written out to an interface file. The 'ModDetails is after
linking and can be completely recovered from just the ModIface
.
When we read an interface file, we also construct a ModIface
from it,
except that we explicitly make the mi_decls
and a few other fields empty;
as when reading we consolidate the declarations etc. into a number of indexed
maps and environments in the ExternalPackageState
.
ModIface | |
|
data ModIfaceBackend Source #
Extends a PartialModIface with information which is either: * Computed after codegen * Or computed just before writing the iface to disk. (Hashes) In order to fully instantiate it.
ModIfaceBackend | |
|
mkIfaceWarnCache :: Warnings -> OccName -> 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
mi_boot :: ModIface -> Bool Source #
Old-style accessor for whether or not the ModIface came from an hs-boot file.
mi_fix :: ModIface -> OccName -> Fixity Source #
Lookups up a (possibly cached) fixity from a ModIface
. If one cannot be
found, defaultFixity
is returned instead.
mi_semantic_module :: ModIface_ a -> Module Source #
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 Source #
The "precise" free holes, e.g., the signatures that this
ModIface
depends on.
renameFreeHoles :: UniqDSet ModuleName -> [(ModuleName, Module)] -> UniqDSet ModuleName Source #
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
Fixity information for an Name
. We keep the OccName in the range
so that we can generate an interface from it
TyThings and type environments
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 #
tyThingConLike :: TyThing -> ConLike Source #
tyThingParent_maybe :: TyThing -> Maybe TyThing Source #
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.
tyThingsTyCoVars :: [TyThing] -> TyCoVarSet 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 #
typeEnvElts :: TypeEnv -> [TyThing] Source #
typeEnvTyCons :: TypeEnv -> [TyCon] Source #
typeEnvIds :: TypeEnv -> [Id] Source #
typeEnvPatSyns :: TypeEnv -> [PatSyn] Source #
typeEnvDataCons :: TypeEnv -> [DataCon] 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
lookupThing :: Name -> m TyThing Source #
lookupId :: Name -> m Id Source #
lookupDataCon :: Name -> m DataCon Source #
lookupTyCon :: Name -> m TyCon Source #
Instances
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
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: https://gitlab.haskell.org/ghc/ghc/wikis/commentary/compiler/recompilation-avoidance
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 | |
| |
UsageMergedRequirement | A requirement which was merged into this one. |
|
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 | |
|
Instances
Eq Dependencies # | |
Defined in HscTypes (==) :: Dependencies -> Dependencies -> Bool # (/=) :: Dependencies -> Dependencies -> Bool # | |
Binary Dependencies # | |
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 #
Warning Text
reason/explanation from a WARNING or DEPRECATED pragma
WarningTxt (Located SourceText) [Located StringLiteral] | |
DeprecatedTxt (Located SourceText) [Located StringLiteral] |
Instances
Eq WarningTxt # | |
Defined in BasicTypes (==) :: WarningTxt -> WarningTxt -> Bool # (/=) :: WarningTxt -> WarningTxt -> Bool # | |
Data WarningTxt # | |
Defined in BasicTypes 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 :: forall r r'. (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 # | |
Defined in BasicTypes | |
Binary WarningTxt # | |
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
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. |
data CompiledByteCode Source #
Instances
Outputable CompiledByteCode # | |
Defined in ByteCodeTypes |
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 module
ModBreaks | |
|
emptyModBreaks :: ModBreaks Source #
Construct an empty ModBreaks
Safe Haskell information
data IfaceTrustInfo Source #
Safe Haskell information for ModIface
Simply a wrapper around SafeHaskellMode to sepperate iface and flags
Instances
trustInfoToNum :: IfaceTrustInfo -> Word8 Source #
numToTrustInfo :: Word8 -> IfaceTrustInfo Source #
type IsSafeImport = Bool Source #
Is an import a safe import?
result of the parser
data HsParsedModule Source #
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.
Instances
Show SourceError # | |
Exception SourceError # | |
Defined in HscTypes |
data GhcApiError Source #
An error thrown if the GHC API is used in an incorrect fashion.
Instances
Show GhcApiError # | |
Exception GhcApiError # | |
Defined in HscTypes |
mkSrcErr :: ErrorMessages -> SourceError Source #
throwOneError :: MonadIO io => ErrMsg -> io a Source #
throwErrors :: MonadIO io => ErrorMessages -> io a 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.
printOrThrowWarnings :: DynFlags -> Bag WarnMsg -> IO () Source #
Given a bag of warnings, turn them into an exception if -Werror is enabled, or print them out otherwise.
COMPLETE signature
data CompleteMatch Source #
A list of conlikes which represents a complete pattern match.
These arise from COMPLETE
signatures.
CompleteMatch | |
|
Instances
type CompleteMatchMap = UniqFM [CompleteMatch] Source #
A map keyed by the completeMatchTyCon
.