Safe Haskell | None |
---|---|
Language | Haskell2010 |
- flushFinderCaches :: HscEnv -> IO ()
- data FindResult
- = Found ModLocation Module
- | NoPackage PackageKey
- | FoundMultiple [(Module, ModuleOrigin)]
- | NotFound {
- fr_paths :: [FilePath]
- fr_pkg :: Maybe PackageKey
- fr_mods_hidden :: [PackageKey]
- fr_pkgs_hidden :: [PackageKey]
- fr_suggestions :: [ModuleSuggestion]
- findImportedModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
- findExactModule :: HscEnv -> Module -> IO FindResult
- findHomeModule :: HscEnv -> ModuleName -> IO FindResult
- findExposedPackageModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult
- mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO ModLocation
- mkHomeModLocation2 :: DynFlags -> ModuleName -> FilePath -> String -> IO ModLocation
- mkHiOnlyModLocation :: DynFlags -> Suffix -> FilePath -> String -> IO ModLocation
- addHomeModuleToFinder :: HscEnv -> ModuleName -> ModLocation -> IO Module
- uncacheModule :: HscEnv -> ModuleName -> IO ()
- mkStubPaths :: DynFlags -> ModuleName -> ModLocation -> FilePath
- findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable)
- findObjectLinkable :: Module -> FilePath -> UTCTime -> IO Linkable
- cannotFindModule :: DynFlags -> ModuleName -> FindResult -> SDoc
- cannotFindInterface :: DynFlags -> ModuleName -> FindResult -> SDoc
Documentation
flushFinderCaches :: HscEnv -> IO () Source
data FindResult Source
The result of searching for an imported module.
Found ModLocation Module | The module was found |
NoPackage PackageKey | The requested package was not found |
FoundMultiple [(Module, ModuleOrigin)] | _Error_: both in multiple packages |
NotFound | Not found |
|
findImportedModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult Source
Locate a module that was imported by the user. We have the module's name, and possibly a package name. Without a package name, this function will use the search path and the known exposed packages to find the module, if a package is specified then only that package is searched for the module.
findExactModule :: HscEnv -> Module -> IO FindResult Source
Locate a specific Module
. The purpose of this function is to
create a ModLocation
for a given Module
, that is to find out
where the files associated with this module live. It is used when
reading the interface for a module mentioned by another interface,
for example (a "system import").
findHomeModule :: HscEnv -> ModuleName -> IO FindResult Source
Implements the search for a module name in the home package only. Calling this function directly is usually *not* what you want; currently, it's used as a building block for the following operations:
- When you do a normal package lookup, we first check if the module is available in the home module, before looking it up in the package database.
- When you have a package qualified import with package name "this", we shortcut to the home module.
- When we look up an exact
Module
, if the package key associated with the module is the current home module do a look up in the home module. - Some special-case code in GHCi (ToDo: Figure out why that needs to call this.)
findExposedPackageModule :: HscEnv -> ModuleName -> Maybe FastString -> IO FindResult Source
mkHomeModLocation :: DynFlags -> ModuleName -> FilePath -> IO ModLocation Source
mkHomeModLocation2 :: DynFlags -> ModuleName -> FilePath -> String -> IO ModLocation Source
mkHiOnlyModLocation :: DynFlags -> Suffix -> FilePath -> String -> IO ModLocation Source
addHomeModuleToFinder :: HscEnv -> ModuleName -> ModLocation -> IO Module Source
uncacheModule :: HscEnv -> ModuleName -> IO () Source
mkStubPaths :: DynFlags -> ModuleName -> ModLocation -> FilePath Source
findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable) Source
cannotFindModule :: DynFlags -> ModuleName -> FindResult -> SDoc Source
cannotFindInterface :: DynFlags -> ModuleName -> FindResult -> SDoc Source