Safe Haskell | None |
---|---|
Language | GHC2021 |
Loading interface files
Synopsis
- tcLookupImported_maybe :: Name -> TcM (MaybeErr IfaceMessage TyThing)
- importDecl :: Name -> IfM lcl (MaybeErr IfaceMessage TyThing)
- checkWiredInTyCon :: TyCon -> TcM ()
- ifCheckWiredInThing :: TyThing -> IfL ()
- loadModuleInterface :: SDoc -> Module -> TcM ModIface
- loadModuleInterfaces :: SDoc -> [Module] -> TcM ()
- loadSrcInterface :: SDoc -> ModuleName -> IsBootInterface -> PkgQual -> RnM ModIface
- loadSrcInterface_maybe :: SDoc -> ModuleName -> IsBootInterface -> PkgQual -> RnM (MaybeErr MissingInterfaceError ModIface)
- loadInterfaceForName :: SDoc -> Name -> TcRn ModIface
- loadInterfaceForModule :: SDoc -> Module -> TcRn ModIface
- loadInterface :: SDoc -> Module -> WhereFrom -> IfM lcl (MaybeErr MissingInterfaceError ModIface)
- loadSysInterface :: SDoc -> Module -> IfM lcl ModIface
- loadUserInterface :: IsBootInterface -> SDoc -> Module -> IfM lcl ModIface
- loadPluginInterface :: SDoc -> Module -> IfM lcl ModIface
- loadExternalGraphBelow :: (Module -> SDoc) -> Maybe HomeUnit -> Set ExternalKey -> [Module] -> IfM lcl (Set ExternalKey)
- findAndReadIface :: HscEnv -> SDoc -> InstalledModule -> Module -> IsBootInterface -> IO (MaybeErr MissingInterfaceError (ModIface, ModLocation))
- readIface :: DynFlags -> NameCache -> Module -> FilePath -> IO (MaybeErr ReadInterfaceError ModIface)
- writeIface :: Logger -> Profile -> CompressionIFace -> FilePath -> ModIface -> IO ()
- flagsToIfCompression :: DynFlags -> CompressionIFace
- moduleFreeHolesPrecise :: SDoc -> Module -> TcRnIf gbl lcl (MaybeErr MissingInterfaceError (UniqDSet ModuleName))
- needWiredInHomeIface :: TyThing -> Bool
- loadWiredInHomeIface :: Name -> IfM lcl ()
- data WhereFrom
- pprModIfaceSimple :: UnitState -> ModIface -> SDoc
- ifaceStats :: ExternalPackageState -> SDoc
- pprModIface :: UnitState -> ModIface -> SDoc
- showIface :: Logger -> DynFlags -> UnitState -> NameCache -> FilePath -> IO ()
- getGhcPrimIface :: HscEnv -> ModIface
- module GHC.Iface.Errors
Documentation
importDecl :: Name -> IfM lcl (MaybeErr IfaceMessage TyThing) Source #
checkWiredInTyCon :: TyCon -> TcM () Source #
ifCheckWiredInThing :: TyThing -> IfL () Source #
loadModuleInterface :: SDoc -> Module -> TcM ModIface Source #
Load interface directly for a fully qualified Module
. (This is a fairly
rare operation, but in particular it is used to load orphan modules
in order to pull their instances into the global package table and to
handle some operations in GHCi).
loadModuleInterfaces :: SDoc -> [Module] -> TcM () Source #
Load interfaces for a collection of modules.
loadSrcInterface :: SDoc -> ModuleName -> IsBootInterface -> PkgQual -> RnM ModIface Source #
Load the interface corresponding to an import
directive in
source code. On a failure, fail in the monad with an error message.
loadSrcInterface_maybe :: SDoc -> ModuleName -> IsBootInterface -> PkgQual -> RnM (MaybeErr MissingInterfaceError ModIface) Source #
Like loadSrcInterface
, but returns a MaybeErr
.
loadInterfaceForName :: SDoc -> Name -> TcRn ModIface Source #
Loads the interface for a given Name. Should only be called for an imported name; otherwise loadSysInterface may not find the interface
loadInterfaceForModule :: SDoc -> Module -> TcRn ModIface Source #
Loads the interface for a given Module.
loadInterface :: SDoc -> Module -> WhereFrom -> IfM lcl (MaybeErr MissingInterfaceError ModIface) Source #
loadSysInterface :: SDoc -> Module -> IfM lcl ModIface Source #
Loads a system interface and throws an exception if it fails
loadUserInterface :: IsBootInterface -> SDoc -> Module -> IfM lcl ModIface Source #
Loads a user interface and throws an exception if it fails. The first parameter indicates whether we should import the boot variant of the module
loadExternalGraphBelow Source #
:: (Module -> SDoc) | |
-> Maybe HomeUnit | The current home unit |
-> Set ExternalKey | |
-> [Module] | |
-> IfM lcl (Set ExternalKey) |
Load the part of the external module graph which is transitively reachable from the given modules.
This operation is used just before TH splices are run (in getLinkDeps
).
A field in the EPS tracks which home modules are already fully loaded, which we use here to avoid trying to load them a second time.
The function takes a set of keys which are currently in the process of being loaded. This is used to avoid duplicating work by loading keys twice if they appear along multiple paths in the transitive closure. Once the interface and all its dependencies are loaded, the key is added to the "fully loaded" set, so we know that it and it's transitive closure are present in the graph.
Note that being "in progress" is different from being "fully loaded", consider if there
is an exception during loadExternalGraphBelow
, then an "in progress" item may fail
to become fully loaded.
:: HscEnv | |
-> SDoc | Reason for loading the iface (used for tracing) |
-> InstalledModule | The unique identifier of the on-disk module we're looking for |
-> Module | The *actual* module we're looking for. We use this to check the consistency of the requirements of the module we read out. |
-> IsBootInterface | Looking for .hi-boot or .hi file |
-> IO (MaybeErr MissingInterfaceError (ModIface, ModLocation)) |
readIface :: DynFlags -> NameCache -> Module -> FilePath -> IO (MaybeErr ReadInterfaceError ModIface) Source #
writeIface :: Logger -> Profile -> CompressionIFace -> FilePath -> ModIface -> IO () Source #
Write interface file
moduleFreeHolesPrecise :: SDoc -> Module -> TcRnIf gbl lcl (MaybeErr MissingInterfaceError (UniqDSet ModuleName)) Source #
Compute the signatures which must be compiled in order to
load the interface for a Module
. The output of this function
is always a subset of moduleFreeHoles
; it is more precise
because in signature p[A=<A>,B=<B>]:B
, although the free holes
are A and B, B might not depend on A at all!
If this is invoked on a signature, this does NOT include the
signature itself; e.g. precise free module holes of
p[A=<A>,B=<B>]:B
never includes B.
needWiredInHomeIface :: TyThing -> Bool Source #
loadWiredInHomeIface :: Name -> IfM lcl () Source #
An IfM
function to load the home interface for a wired-in thing,
so that we're sure that we see its instance declarations and rules
See Note [Loading instances for wired-in things]
Reason for loading an interface file
Used to figure out whether we want to consider loading hi-boot files or not.
Instances
pprModIfaceSimple :: UnitState -> ModIface -> SDoc Source #
Show a ModIface but don't display details; suitable for ModIfaces stored in the EPT.
pprModIface :: UnitState -> ModIface -> SDoc Source #
Show a ModIface
The UnitState is used to pretty-print units
showIface :: Logger -> DynFlags -> UnitState -> NameCache -> FilePath -> IO () Source #
Read binary interface, and print it out
getGhcPrimIface :: HscEnv -> ModIface Source #
Get gHC_PRIM interface file
This is a helper function that takes into account the hook allowing ghc-prim interface to be extended via the ghc-api. Afaik it was introduced for GHCJS so that it can add its own primitive types.
module GHC.Iface.Errors