Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type UnitState = PackageState
- initUnits :: HscEnv -> IO HscEnv
- unitState :: HscEnv -> UnitState
- getUnitName :: HscEnv -> UnitId -> Maybe PackageName
- explicitUnits :: UnitState -> [Unit]
- preloadClosureUs :: HscEnv -> PreloadUnitClosure
- listVisibleModuleNames :: HscEnv -> [ModuleName]
- data LookupResult
- = LookupFound Module PackageConfig
- | LookupMultiple [(Module, ModuleOrigin)]
- | LookupHidden [(Module, ModuleOrigin)] [(Module, ModuleOrigin)]
- | LookupUnusable [(Module, ModuleOrigin)]
- | LookupNotFound [ModuleSuggestion]
- lookupModuleWithSuggestions :: HscEnv -> ModuleName -> Maybe FastString -> LookupResult
- type UnitInfoMap = PackageConfigMap
- getUnitInfoMap :: HscEnv -> UnitInfoMap
- lookupUnit :: HscEnv -> Unit -> Maybe UnitInfo
- lookupUnit' :: Bool -> UnitInfoMap -> PreloadUnitClosure -> Unit -> Maybe UnitInfo
- type UnitInfo = PackageConfig
- unitExposedModules :: UnitInfo -> [(ModuleName, Maybe Module)]
- unitDepends :: UnitInfo -> [UnitId]
- unitHaddockInterfaces :: UnitInfo -> [FilePath]
- unitInfoId :: UnitInfo -> Unit
- unitPackageNameString :: UnitInfo -> String
- unitPackageVersion :: UnitInfo -> Version
- data UnitId
- type Unit = UnitId
- unitString :: Unit -> String
- stringToUnit :: String -> Unit
- pattern RealUnit :: DefUnitId -> UnitId
- definiteUnitId :: DefUnitId -> UnitId
- defUnitId :: UnitId -> DefUnitId
- installedModule :: UnitId -> ModuleName -> InstalledModule
- toUnitId :: Unit -> UnitId
- moduleUnitId :: Module -> UnitId
- moduleUnit :: Module -> Unit
- data ExternalPackageState = EPS {
- eps_is_boot :: !(ModuleNameEnv (ModuleName, IsBootInterface))
- eps_PIT :: !PackageIfaceTable
- eps_free_holes :: InstalledModuleEnv (UniqDSet ModuleName)
- eps_PTE :: !PackageTypeEnv
- eps_inst_env :: !PackageInstEnv
- eps_fam_inst_env :: !PackageFamInstEnv
- eps_rule_base :: !PackageRuleBase
- eps_ann_env :: !PackageAnnEnv
- eps_complete_matches :: !PackageCompleteMatchMap
- eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv)
- eps_stats :: !EpsStats
- filterInplaceUnits :: [UnitId] -> [PackageFlag] -> ([UnitId], [PackageFlag])
- type FinderCache = InstalledModuleEnv InstalledFindResult
- showSDocForUser' :: HscEnv -> PrintUnqualified -> SDoc -> String
UnitState
type UnitState = PackageState Source #
getUnitName :: HscEnv -> UnitId -> Maybe PackageName Source #
explicitUnits :: UnitState -> [Unit] Source #
preloadClosureUs :: HscEnv -> PreloadUnitClosure Source #
listVisibleModuleNames :: HscEnv -> [ModuleName] Source #
data LookupResult #
The result of performing a lookup
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 |
UnitInfoMap
type UnitInfoMap = PackageConfigMap Source #
getUnitInfoMap :: HscEnv -> UnitInfoMap Source #
lookupUnit' :: Bool -> UnitInfoMap -> PreloadUnitClosure -> Unit -> Maybe UnitInfo Source #
UnitInfo
type UnitInfo = PackageConfig Source #
unitExposedModules :: UnitInfo -> [(ModuleName, Maybe Module)] Source #
unitDepends :: UnitInfo -> [UnitId] Source #
unitHaddockInterfaces :: UnitInfo -> [FilePath] Source #
unitInfoId :: UnitInfo -> Unit Source #
unitPackageVersion :: UnitInfo -> Version Source #
UnitId helpers
A unit identifier identifies a (possibly partially) instantiated
library. It is primarily used as part of Module
, which in turn
is used in Name
, which is used to give names to entities when
typechecking.
There are two possible forms for a UnitId
. It can be a
DefiniteUnitId
, in which case we just have a string that uniquely
identifies some fully compiled, installed library we have on disk.
However, when we are typechecking a library with missing holes,
we may need to instantiate a library on the fly (in which case
we don't have any on-disk representation.) In that case, you
have an IndefiniteUnitId
, which explicitly records the
instantiation, so that we can substitute over it.
Instances
unitString :: Unit -> String Source #
stringToUnit :: String -> Unit Source #
definiteUnitId :: DefUnitId -> UnitId Source #
installedModule :: UnitId -> ModuleName -> InstalledModule Source #
Module
moduleUnitId :: Module -> UnitId Source #
moduleUnit :: Module -> Unit Source #
ExternalPackageState
data ExternalPackageState #
Information about other packages that we have slurped in by reading their interface files
EPS | |
|
Utils
filterInplaceUnits :: [UnitId] -> [PackageFlag] -> ([UnitId], [PackageFlag]) Source #
type FinderCache = InstalledModuleEnv InstalledFindResult #
The FinderCache
maps modules to the result of
searching for that module. It records the results of searching for
modules along the search path. On :load
, we flush the entire
contents of this cache.
showSDocForUser' :: HscEnv -> PrintUnqualified -> SDoc -> String Source #