| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | GHC2021 | 
Development.IDE.GHC.Compat.Units
Synopsis
- data UnitState
- initUnits :: [DynFlags] -> HscEnv -> IO HscEnv
- oldInitUnits :: DynFlags -> IO DynFlags
- unitState :: HscEnv -> UnitState
- getUnitName :: HscEnv -> UnitId -> Maybe PackageName
- explicitUnits :: UnitState -> [Unit]
- preloadClosureUs :: HscEnv -> PreloadUnitClosure
- listVisibleModuleNames :: HscEnv -> [ModuleName]
- data LookupResult- = LookupFound Module (UnitInfo, ModuleOrigin)
- | LookupMultiple [(Module, ModuleOrigin)]
- | LookupHidden [(Module, ModuleOrigin)] [(Module, ModuleOrigin)]
- | LookupUnusable [(Module, ModuleOrigin)]
- | LookupNotFound [ModuleSuggestion]
 
- lookupModuleWithSuggestions :: HscEnv -> ModuleName -> PkgQual -> LookupResult
- type UnitInfoMap = Map UnitId UnitInfo
- getUnitInfoMap :: HscEnv -> UnitInfoMap
- lookupUnit :: HscEnv -> Unit -> Maybe UnitInfo
- lookupUnit' :: Bool -> UnitInfoMap -> PreloadUnitClosure -> Unit -> Maybe UnitInfo
- type UnitInfo = GenUnitInfo UnitId
- unitExposedModules :: GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> [(modulename, Maybe mod)]
- unitDepends :: GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> [uid]
- unitHaddockInterfaces :: UnitInfo -> [FilePath]
- mkUnit :: UnitInfo -> Unit
- unitPackageNameString :: GenUnitInfo u -> String
- unitPackageVersion :: GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> Version
- data UnitId
- type Unit = GenUnit UnitId
- unitString :: IsUnitId u => u -> String
- stringToUnit :: String -> Unit
- definiteUnitId :: Definite uid -> GenUnit uid
- defUnitId :: unit -> Definite unit
- installedModule :: unit -> ModuleName -> GenModule unit
- toUnitId :: Unit -> UnitId
- moduleUnitId :: Module -> UnitId
- moduleUnit :: GenModule unit -> unit
- data ExternalPackageState = EPS {- eps_is_boot :: !(InstalledModuleEnv ModuleNameWithIsBoot)
- 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 :: !PackageCompleteMatches
- eps_mod_fam_inst_env :: !(ModuleEnv FamInstEnv)
- eps_stats :: !EpsStats
 
- filterInplaceUnits :: [UnitId] -> [PackageFlag] -> ([UnitId], [PackageFlag])
- data FinderCache
- showSDocForUser' :: HscEnv -> PrintUnqualified -> SDoc -> String
- findImportedModule :: HscEnv -> ModuleName -> IO (Maybe Module)
UnitState
oldInitUnits :: DynFlags -> IO DynFlags Source #
oldInitUnits only needs to modify DynFlags for GHC <9.2 For GHC >= 9.2, we need to set the hsc_unit_env also, that is done later by initUnits
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
Constructors
| LookupFound Module (UnitInfo, ModuleOrigin) | 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 | 
lookupModuleWithSuggestions :: HscEnv -> ModuleName -> PkgQual -> LookupResult Source #
UnitInfoMap
type UnitInfoMap = Map UnitId UnitInfo #
getUnitInfoMap :: HscEnv -> UnitInfoMap Source #
lookupUnit' :: Bool -> UnitInfoMap -> PreloadUnitClosure -> Unit -> Maybe UnitInfo #
A more specialized interface, which doesn't require a UnitState (so it
 can be used while we're initializing DynFlags)
Parameters:
    * a boolean specifying whether or not to look for on-the-fly renamed interfaces
    * a UnitInfoMap
    * a PreloadUnitClosure
UnitInfo
type UnitInfo = GenUnitInfo UnitId #
Information about an installed unit (units are identified by their internal UnitId)
unitExposedModules :: GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> [(modulename, Maybe mod)] #
Modules exposed by the unit.
A module can be re-exported from another package. In this case, we indicate the module origin in the second parameter.
unitDepends :: GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> [uid] #
Identifiers of the units this one depends on
unitHaddockInterfaces :: UnitInfo -> [FilePath] Source #
If the unit is definite, make a RealUnit from unitId field.
If the unit is indefinite, make a VirtUnit from unitInstanceOf and
 unitInstantiations fields. Note that in this case we don't keep track of
 unitId. It can be retrieved later with "improvement", i.e. matching on
 `unitInstanceOf/unitInstantiations` fields (see Note [About units] in
 GHC.Unit).
unitPackageNameString :: GenUnitInfo u -> String #
unitPackageVersion :: GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> Version #
Source package version
UnitId helpers
A UnitId identifies a built library in a database and is used to generate unique symbols, etc. It's usually of the form:
pkgname-1.2:libname+hash
These UnitId are provided to us via the -this-unit-id flag.
The library in question may be definite or indefinite; if it is indefinite, none of the holes have been filled (we never install partially instantiated libraries as we can cheaply instantiate them on-the-fly, cf VirtUnit). Put another way, an installed unit id is either fully instantiated, or not instantiated at all.
Instances
| Data Unit | |
| Defined in GHC.Unit.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Unit -> c Unit # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Unit # dataTypeOf :: Unit -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Unit) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Unit) # gmapT :: (forall b. Data b => b -> b) -> Unit -> Unit # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Unit -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Unit -> r # gmapQ :: (forall d. Data d => d -> u) -> Unit -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Unit -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Unit -> m Unit # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Unit -> m Unit # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Unit -> m Unit # | |
| Data UnitId | |
| Defined in GHC.Unit.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnitId -> c UnitId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnitId # toConstr :: UnitId -> Constr # dataTypeOf :: UnitId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnitId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnitId) # gmapT :: (forall b. Data b => b -> b) -> UnitId -> UnitId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnitId -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnitId -> r # gmapQ :: (forall d. Data d => d -> u) -> UnitId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UnitId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnitId -> m UnitId # | |
| Show Module Source # | |
| Show Unit | |
| Show UnitId Source # | |
| NFData Unit | |
| Defined in GHC.Unit.Types | |
| NFData UnitId Source # | |
| Defined in Development.IDE.GHC.Orphans | |
| Uniquable Module | |
| Defined in GHC.Unit.Types | |
| Uniquable UnitId | |
| Defined in GHC.Unit.Types | |
| IsUnitId UnitId | |
| Defined in GHC.Unit.Types Methods unitFS :: UnitId -> FastString # | |
| Binary InstantiatedUnit | |
| Defined in GHC.Unit.Types Methods put_ :: BinHandle -> InstantiatedUnit -> IO () # put :: BinHandle -> InstantiatedUnit -> IO (Bin InstantiatedUnit) # get :: BinHandle -> IO InstantiatedUnit # | |
| Binary Unit | |
| Binary UnitId | |
| Outputable InstalledModule | |
| Defined in GHC.Unit.Types Methods ppr :: InstalledModule -> SDoc # | |
| Outputable InstantiatedModule | |
| Defined in GHC.Unit.Types Methods ppr :: InstantiatedModule -> SDoc # | |
| Outputable InstantiatedUnit | |
| Defined in GHC.Unit.Types Methods ppr :: InstantiatedUnit -> SDoc # | |
| Outputable Module | |
| Defined in GHC.Unit.Types | |
| Outputable Unit | |
| Defined in GHC.Unit.Types | |
| Outputable UnitId | |
| Defined in GHC.Unit.Types | |
| Eq UnitId | |
| Ord Unit | |
| Ord UnitId | |
unitString :: IsUnitId u => u -> String #
stringToUnit :: String -> Unit #
definiteUnitId :: Definite uid -> GenUnit uid Source #
installedModule :: unit -> ModuleName -> GenModule unit Source #
Module
Return the UnitId of the Unit. For on-the-fly instantiated units, return the UnitId of the indefinite unit this unit is an instance of.
moduleUnitId :: Module -> UnitId #
moduleUnit :: GenModule unit -> unit #
Unit the module belongs to
ExternalPackageState
data ExternalPackageState #
Information about other packages that we have slurped in by reading their interface files
Constructors
| EPS | |
| Fields 
 | |
Utils
filterInplaceUnits :: [UnitId] -> [PackageFlag] -> ([UnitId], [PackageFlag]) Source #
data FinderCache #
showSDocForUser' :: HscEnv -> PrintUnqualified -> SDoc -> String Source #
findImportedModule :: HscEnv -> ModuleName -> IO (Maybe Module) Source #