| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Packages
Contents
Description
Package manipulation
Synopsis
- module PackageConfig
- data PackageState
- data PackageConfigMap
- emptyPackageState :: PackageState
- initPackages :: DynFlags -> IO (DynFlags, [PreloadUnitId])
- readPackageConfigs :: DynFlags -> IO [(FilePath, [PackageConfig])]
- getPackageConfRefs :: DynFlags -> IO [PkgConfRef]
- resolvePackageConfig :: DynFlags -> PkgConfRef -> IO (Maybe FilePath)
- readPackageConfig :: DynFlags -> FilePath -> IO (FilePath, [PackageConfig])
- listPackageConfigMap :: DynFlags -> [PackageConfig]
- lookupPackage :: DynFlags -> UnitId -> Maybe PackageConfig
- lookupPackage' :: Bool -> PackageConfigMap -> UnitId -> Maybe PackageConfig
- lookupInstalledPackage :: DynFlags -> InstalledUnitId -> Maybe PackageConfig
- lookupPackageName :: DynFlags -> PackageName -> Maybe ComponentId
- improveUnitId :: PackageConfigMap -> UnitId -> UnitId
- searchPackageId :: DynFlags -> SourcePackageId -> [PackageConfig]
- getPackageDetails :: DynFlags -> UnitId -> PackageConfig
- getInstalledPackageDetails :: DynFlags -> InstalledUnitId -> PackageConfig
- componentIdString :: DynFlags -> ComponentId -> Maybe String
- displayInstalledUnitId :: DynFlags -> InstalledUnitId -> Maybe String
- listVisibleModuleNames :: DynFlags -> [ModuleName]
- lookupModuleInAllPackages :: DynFlags -> ModuleName -> [(Module, PackageConfig)]
- lookupModuleWithSuggestions :: DynFlags -> ModuleName -> Maybe FastString -> LookupResult
- lookupPluginModuleWithSuggestions :: DynFlags -> ModuleName -> Maybe FastString -> LookupResult
- data LookupResult- = LookupFound Module PackageConfig
- | LookupMultiple [(Module, ModuleOrigin)]
- | LookupHidden [(Module, ModuleOrigin)] [(Module, ModuleOrigin)]
- | LookupUnusable [(Module, ModuleOrigin)]
- | LookupNotFound [ModuleSuggestion]
 
- data ModuleSuggestion
- data ModuleOrigin
- data UnusablePackageReason
- pprReason :: SDoc -> UnusablePackageReason -> SDoc
- getPackageIncludePath :: DynFlags -> [PreloadUnitId] -> IO [String]
- getPackageLibraryPath :: DynFlags -> [PreloadUnitId] -> IO [String]
- getPackageLinkOpts :: DynFlags -> [PreloadUnitId] -> IO ([String], [String], [String])
- getPackageExtraCcOpts :: DynFlags -> [PreloadUnitId] -> IO [String]
- getPackageFrameworkPath :: DynFlags -> [PreloadUnitId] -> IO [String]
- getPackageFrameworks :: DynFlags -> [PreloadUnitId] -> IO [String]
- getPackageConfigMap :: DynFlags -> PackageConfigMap
- getPreloadPackagesAnd :: DynFlags -> [PreloadUnitId] -> IO [PackageConfig]
- collectArchives :: DynFlags -> PackageConfig -> IO [FilePath]
- collectIncludeDirs :: [PackageConfig] -> [FilePath]
- collectLibraryPaths :: DynFlags -> [PackageConfig] -> [FilePath]
- collectLinkOpts :: DynFlags -> [PackageConfig] -> ([String], [String], [String])
- packageHsLibs :: DynFlags -> PackageConfig -> [String]
- getLibs :: DynFlags -> [PreloadUnitId] -> IO [(String, String)]
- unwireUnitId :: DynFlags -> UnitId -> UnitId
- pprFlag :: PackageFlag -> SDoc
- pprPackages :: DynFlags -> SDoc
- pprPackagesSimple :: DynFlags -> SDoc
- pprModuleMap :: ModuleToPkgConfAll -> SDoc
- isDllName :: DynFlags -> Module -> Name -> Bool
Documentation
module PackageConfig
Reading the package config, and processing cmdline args
data PackageState Source #
data PackageConfigMap Source #
UniqFM map from UnitId to PackageConfig, plus
 the transitive closure of preload packages.
initPackages :: DynFlags -> IO (DynFlags, [PreloadUnitId]) Source #
Call this after parseDynFlags.  It reads the package
 database files, and sets up various internal tables of package
 information, according to the package-related flags on the
 command-line (-package, -hide-package etc.)
Returns a list of packages to link in if we're doing dynamic linking.
 This list contains the packages that the user explicitly mentioned with
 -package flags.
initPackages can be called again subsequently after updating the
 packageFlags field of the DynFlags, and it will update the
 pkgState in DynFlags and return a list of packages to
 link in.
readPackageConfigs :: DynFlags -> IO [(FilePath, [PackageConfig])] Source #
getPackageConfRefs :: DynFlags -> IO [PkgConfRef] Source #
resolvePackageConfig :: DynFlags -> PkgConfRef -> IO (Maybe FilePath) Source #
readPackageConfig :: DynFlags -> FilePath -> IO (FilePath, [PackageConfig]) Source #
listPackageConfigMap :: DynFlags -> [PackageConfig] Source #
Get a list of entries from the package database. NB: be careful with this function, although all packages in this map are "visible", this does not imply that the exposed-modules of the package are available (they may have been thinned or renamed).
Querying the package config
lookupPackage :: DynFlags -> UnitId -> Maybe PackageConfig Source #
Find the package we know about with the given unit id, if any
lookupPackage' :: Bool -> PackageConfigMap -> UnitId -> Maybe PackageConfig Source #
A more specialized interface, which takes a boolean specifying
 whether or not to look for on-the-fly renamed interfaces, and
 just a PackageConfigMap rather than a DynFlags (so it can
 be used while we're initializing DynFlags
lookupPackageName :: DynFlags -> PackageName -> Maybe ComponentId Source #
Find the package we know about with the given package name (e.g. foo), if any
 (NB: there might be a locally defined unit name which overrides this)
improveUnitId :: PackageConfigMap -> UnitId -> UnitId Source #
Given a fully instantiated UnitId, improve it into a
 InstalledUnitId if we can find it in the package database.
searchPackageId :: DynFlags -> SourcePackageId -> [PackageConfig] Source #
Search for packages with a given package ID (e.g. "foo-0.1")
getPackageDetails :: DynFlags -> UnitId -> PackageConfig Source #
Looks up the package with the given id in the package state, panicing if it is not found
componentIdString :: DynFlags -> ComponentId -> Maybe String Source #
listVisibleModuleNames :: DynFlags -> [ModuleName] Source #
lookupModuleInAllPackages :: DynFlags -> ModuleName -> [(Module, PackageConfig)] Source #
Takes a ModuleName, and if the module is in any package returns
 list of modules which take that name.
lookupPluginModuleWithSuggestions :: DynFlags -> ModuleName -> Maybe FastString -> LookupResult Source #
data LookupResult Source #
The result of performing a lookup
Constructors
| LookupFound Module PackageConfig | Found the module uniquely, nothing else to do | 
| LookupMultiple [(Module, ModuleOrigin)] | Multiple modules with the same name in scope | 
| LookupHidden [(Module, ModuleOrigin)] [(Module, ModuleOrigin)] | No modules found, but there were some hidden ones with an exact name match. First is due to package hidden, second is due to module being hidden | 
| LookupUnusable [(Module, ModuleOrigin)] | No modules found, but there were some unusable ones with an exact name match | 
| LookupNotFound [ModuleSuggestion] | Nothing found, here are some suggested different names | 
data ModuleSuggestion Source #
data ModuleOrigin Source #
Package state is all stored in DynFlags, including the details of
 all packages, which packages are exposed, and which modules they
 provide.
The package state is computed by initPackages, and kept in DynFlags.
 It is influenced by various package flags:
- -package pkgand- -package-id pkgcause- pkgto become exposed. If- -hide-all-packageswas not specified, these commands also cause all other packages with the same name to become hidden.
- -hide-package pkgcauses- pkgto become hidden.
- (there are a few more flags, check below for their semantics)
The package state has the following properties.
- Let exposedPackagesbe the set of packages thus exposed. LetdepExposedPackagesbe the transitive closure fromexposedPackagesof their dependencies.
- When searching for a module from a preload import declaration,
     only the exposed modules in exposedPackagesare valid.
- When searching for a module from an implicit import, all modules
     from depExposedPackagesare valid.
- When linking in a compilation manager mode, we link in packages the
     program depends on (the compiler knows this list by the
     time it gets to the link step).  Also, we link in all packages
     which were mentioned with preload -packageflags on the command-line, or are a transitive dependency of same, or are "base"/"rts". The reason for this is that we might need packages which don't contain any Haskell modules, and therefore won't be discovered by the normal mechanism of dependency tracking.
Given a module name, there may be multiple ways it came into scope, possibly simultaneously. This data type tracks all the possible ways it could have come into scope. Warning: don't use the record functions, they're partial!
Constructors
| ModHidden | Module is hidden, and thus never will be available for import. (But maybe the user didn't realize), so we'll still keep track of these modules.) | 
| ModUnusable UnusablePackageReason | Module is unavailable because the package is unusable. | 
| ModOrigin | Module is public, and could have come from some places. | 
| Fields 
 | |
Instances
| Semigroup ModuleOrigin Source # | |
| Defined in Packages Methods (<>) :: ModuleOrigin -> ModuleOrigin -> ModuleOrigin # sconcat :: NonEmpty ModuleOrigin -> ModuleOrigin # stimes :: Integral b => b -> ModuleOrigin -> ModuleOrigin # | |
| Monoid ModuleOrigin Source # | |
| Defined in Packages Methods mempty :: ModuleOrigin # mappend :: ModuleOrigin -> ModuleOrigin -> ModuleOrigin # mconcat :: [ModuleOrigin] -> ModuleOrigin # | |
| Outputable ModuleOrigin Source # | |
data UnusablePackageReason Source #
The reason why a package is unusable.
Constructors
| IgnoredWithFlag | We ignored it explicitly using  | 
| BrokenDependencies [InstalledUnitId] | This package transitively depends on a package that was never present in any of the provided databases. | 
| CyclicDependencies [InstalledUnitId] | This package transitively depends on a package involved in a cycle.
 Note that the list of  | 
| IgnoredDependencies [InstalledUnitId] | This package transitively depends on a package which was ignored. | 
| ShadowedDependencies [InstalledUnitId] | This package transitively depends on a package which was shadowed by an ABI-incompatible package. | 
Instances
| Outputable UnusablePackageReason Source # | |
Inspecting the set of packages in scope
getPackageIncludePath :: DynFlags -> [PreloadUnitId] -> IO [String] Source #
Find all the include directories in these and the preload packages
getPackageLibraryPath :: DynFlags -> [PreloadUnitId] -> IO [String] Source #
Find all the library paths in these and the preload packages
getPackageLinkOpts :: DynFlags -> [PreloadUnitId] -> IO ([String], [String], [String]) Source #
Find all the link options in these and the preload packages, returning (package hs lib options, extra library options, other flags)
getPackageExtraCcOpts :: DynFlags -> [PreloadUnitId] -> IO [String] Source #
Find all the C-compiler options in these and the preload packages
getPackageFrameworkPath :: DynFlags -> [PreloadUnitId] -> IO [String] Source #
Find all the package framework paths in these and the preload packages
getPackageFrameworks :: DynFlags -> [PreloadUnitId] -> IO [String] Source #
Find all the package frameworks in these and the preload packages
getPackageConfigMap :: DynFlags -> PackageConfigMap Source #
Retrieve the PackageConfigMap from DynFlags; used
 in the hs-boot loop-breaker.
getPreloadPackagesAnd :: DynFlags -> [PreloadUnitId] -> IO [PackageConfig] Source #
Find all the PackageConfig in both the preload packages from DynFlags and corresponding to the list of
 PackageConfigs
collectArchives :: DynFlags -> PackageConfig -> IO [FilePath] Source #
collectIncludeDirs :: [PackageConfig] -> [FilePath] Source #
collectLibraryPaths :: DynFlags -> [PackageConfig] -> [FilePath] Source #
collectLinkOpts :: DynFlags -> [PackageConfig] -> ([String], [String], [String]) Source #
packageHsLibs :: DynFlags -> PackageConfig -> [String] Source #
Utils
pprFlag :: PackageFlag -> SDoc Source #
pprPackages :: DynFlags -> SDoc Source #
Show (very verbose) package info
pprPackagesSimple :: DynFlags -> SDoc Source #
Show simplified package info.
The idea is to only print package id, and any information that might be different from the package databases (exposure, trust)
pprModuleMap :: ModuleToPkgConfAll -> SDoc Source #
Show the mapping of modules to where they come from.