Safe Haskell | None |
---|---|
Language | GHC2021 |
Module finder
Synopsis
- data FindResult
- = Found ModLocation Module
- | NoPackage Unit
- | FoundMultiple [(Module, ModuleOrigin)]
- | NotFound {
- fr_paths :: [FilePath]
- fr_pkg :: Maybe Unit
- fr_mods_hidden :: [Unit]
- fr_pkgs_hidden :: [Unit]
- fr_unusables :: [UnusableUnit]
- fr_suggestions :: [ModuleSuggestion]
- data InstalledFindResult
- data FinderOpts = FinderOpts {
- finder_importPaths :: [OsPath]
- finder_lookupHomeInterfaces :: Bool
- finder_bypassHiFileCheck :: Bool
- finder_ways :: Ways
- finder_enableSuggestions :: Bool
- finder_workingDirectory :: Maybe OsPath
- finder_thisPackageName :: Maybe FastString
- finder_hiddenModules :: Set ModuleName
- finder_reexportedModules :: Map ModuleName ModuleName
- finder_hieDir :: Maybe OsPath
- finder_hieSuf :: OsString
- finder_hiDir :: Maybe OsPath
- finder_hiSuf :: OsString
- finder_dynHiSuf :: OsString
- finder_objectDir :: Maybe OsPath
- finder_objectSuf :: OsString
- finder_dynObjectSuf :: OsString
- finder_stubDir :: Maybe OsPath
- data FinderCache = FinderCache {}
- initFinderCache :: IO FinderCache
- findImportedModule :: HscEnv -> ModuleName -> PkgQual -> IO FindResult
- findPluginModule :: FinderCache -> FinderOpts -> UnitState -> Maybe HomeUnit -> ModuleName -> IO FindResult
- findExactModule :: FinderCache -> FinderOpts -> UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IO InstalledFindResult
- findHomeModule :: FinderCache -> FinderOpts -> HomeUnit -> ModuleName -> IO FindResult
- findExposedPackageModule :: FinderCache -> FinderOpts -> UnitState -> ModuleName -> PkgQual -> IO FindResult
- mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> ModLocation
- mkHomeModLocation2 :: FinderOpts -> ModuleName -> OsPath -> FileExt -> ModLocation
- mkHiOnlyModLocation :: FinderOpts -> FileExt -> FileExt -> OsPath -> OsPath -> ModLocation
- mkHiPath :: FinderOpts -> OsPath -> OsPath -> OsPath
- mkObjPath :: FinderOpts -> OsPath -> OsPath -> OsPath
- addModuleToFinder :: FinderCache -> ModuleWithIsBoot -> ModLocation -> IO ()
- addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleNameWithIsBoot -> ModLocation -> IO Module
- mkStubPaths :: FinderOpts -> ModuleName -> ModLocation -> Maybe OsPath
- findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable)
- findObjectLinkable :: Module -> FilePath -> UTCTime -> IO Linkable
Documentation
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 Unit | The requested unit was not found |
FoundMultiple [(Module, ModuleOrigin)] | _Error_: both in multiple packages |
NotFound | Not found |
|
data InstalledFindResult Source #
data FinderOpts Source #
Locations and information the finder cares about.
Should be taken from DynFlags
via initFinderOpts
.
FinderOpts | |
|
data FinderCache Source #
FinderCache | |
|
findImportedModule :: HscEnv -> ModuleName -> PkgQual -> 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.
findPluginModule :: FinderCache -> FinderOpts -> UnitState -> Maybe HomeUnit -> ModuleName -> IO FindResult Source #
Locate a plugin module requested by the user, for a compiler
plugin. This consults the same set of exposed packages as
findImportedModule
, unless -hide-all-plugin-packages
or
-plugin-package
are specified.
findExactModule :: FinderCache -> FinderOpts -> UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IO InstalledFindResult 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 :: FinderCache -> FinderOpts -> HomeUnit -> ModuleName -> IO FindResult Source #
findExposedPackageModule :: FinderCache -> FinderOpts -> UnitState -> ModuleName -> PkgQual -> IO FindResult Source #
mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> ModLocation Source #
mkHomeModLocation2 :: FinderOpts -> ModuleName -> OsPath -> FileExt -> ModLocation Source #
mkHiOnlyModLocation :: FinderOpts -> FileExt -> FileExt -> OsPath -> OsPath -> ModLocation Source #
mkHiPath :: FinderOpts -> OsPath -> OsPath -> OsPath Source #
Constructs the filename of a .hi file for a given source file. Does not check whether the .hi file exists
mkObjPath :: FinderOpts -> OsPath -> OsPath -> OsPath Source #
Constructs the filename of a .o file for a given source file. Does not check whether the .o file exists
addModuleToFinder :: FinderCache -> ModuleWithIsBoot -> ModLocation -> IO () Source #
addHomeModuleToFinder :: FinderCache -> HomeUnit -> ModuleNameWithIsBoot -> ModLocation -> IO Module Source #
mkStubPaths :: FinderOpts -> ModuleName -> ModLocation -> Maybe OsPath Source #
Compute the file name of a header file for foreign stubs, using either the
directory explicitly specified in the command line option -stubdir
, or the
directory of the module's source file.
When compiling bytecode from interface Core bindings, ModLocation
does not
contain a source file path, so the header isn't written.
This doesn't have an impact, since we cannot support headers importing
Haskell symbols defined in bytecode for TH whatsoever at the moment.
findObjectLinkableMaybe :: Module -> ModLocation -> IO (Maybe Linkable) Source #