Safe Haskell | None |
---|---|
Language | Haskell2010 |
- tcLookupImported_maybe :: Name -> TcM (MaybeErr MsgDoc TyThing)
- importDecl :: Name -> IfM lcl (MaybeErr MsgDoc TyThing)
- checkWiredInTyCon :: TyCon -> TcM ()
- ifCheckWiredInThing :: TyThing -> IfL ()
- loadModuleInterface :: SDoc -> Module -> TcM ModIface
- loadModuleInterfaces :: SDoc -> [Module] -> TcM ()
- loadSrcInterface :: SDoc -> ModuleName -> IsBootInterface -> Maybe FastString -> RnM [ModIface]
- loadSrcInterface_maybe :: SDoc -> ModuleName -> IsBootInterface -> Maybe FastString -> RnM (MaybeErr MsgDoc [ModIface])
- loadInterfaceForName :: SDoc -> Name -> TcRn ModIface
- loadInterfaceForModule :: SDoc -> Module -> TcRn ModIface
- loadInterface :: SDoc -> Module -> WhereFrom -> IfM lcl (MaybeErr MsgDoc ModIface)
- loadWiredInHomeIface :: Name -> IfM lcl ()
- loadSysInterface :: SDoc -> Module -> IfM lcl ModIface
- loadUserInterface :: Bool -> SDoc -> Module -> IfM lcl ModIface
- loadPluginInterface :: SDoc -> Module -> IfM lcl ModIface
- findAndReadIface :: SDoc -> Module -> IsBootInterface -> TcRnIf gbl lcl (MaybeErr MsgDoc (ModIface, FilePath))
- readIface :: Module -> FilePath -> TcRnIf gbl lcl (MaybeErr MsgDoc ModIface)
- loadDecls :: Bool -> [(Fingerprint, IfaceDecl)] -> IfL [(Name, TyThing)]
- initExternalPackageState :: ExternalPackageState
- ifaceStats :: ExternalPackageState -> SDoc
- pprModIface :: ModIface -> SDoc
- showIface :: HscEnv -> FilePath -> IO ()
Documentation
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 -> Maybe FastString -> 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.
See Note [Un-ambiguous multiple interfaces] for why the return type
is [ModIface]
loadSrcInterface_maybe :: SDoc -> ModuleName -> IsBootInterface -> Maybe FastString -> RnM (MaybeErr MsgDoc [ModIface]) Source
Like loadSrcInterface
, but returns a MaybeErr
. See also
Note [Un-ambiguous multiple interfaces]
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.
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] in TcIface
loadSysInterface :: SDoc -> Module -> IfM lcl ModIface Source
Loads a system interface and throws an exception if it fails
loadUserInterface :: Bool -> 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
findAndReadIface :: SDoc -> Module -> IsBootInterface -> TcRnIf gbl lcl (MaybeErr MsgDoc (ModIface, FilePath)) Source
pprModIface :: ModIface -> SDoc Source