ghcide-2.7.0.0: The core of an IDE
Safe HaskellSafe-Inferred
LanguageGHC2021

Development.IDE.GHC.Compat.Units

Description

Compat module for UnitState and UnitInfo.

Synopsis

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

preloadClosureUs :: HscEnv -> PreloadUnitClosure 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

UnitInfoMap

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

mkUnit :: UnitInfo -> Unit #

Make a Unit from a UnitInfo

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).

unitPackageVersion :: GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> Version #

Source package version

UnitId helpers

data UnitId #

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

Instances details
Data Unit 
Instance details

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 #

toConstr :: Unit -> Constr #

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 
Instance details

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 # 
Instance details

Defined in Development.IDE.GHC.Orphans

Show Unit 
Instance details

Defined in GHC.Unit.Types

Methods

showsPrec :: Int -> Unit -> ShowS #

show :: Unit -> String #

showList :: [Unit] -> ShowS #

Show UnitId Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

NFData Unit 
Instance details

Defined in GHC.Unit.Types

Methods

rnf :: Unit -> () #

NFData UnitId Source # 
Instance details

Defined in Development.IDE.GHC.Orphans

Methods

rnf :: UnitId -> () #

Uniquable Module 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: Module -> Unique #

Uniquable UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

getUnique :: UnitId -> Unique #

IsUnitId UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

unitFS :: UnitId -> FastString #

Binary InstantiatedUnit 
Instance details

Defined in GHC.Unit.Types

Binary Unit 
Instance details

Defined in GHC.Unit.Types

Methods

put_ :: BinHandle -> Unit -> IO () #

put :: BinHandle -> Unit -> IO (Bin Unit) #

get :: BinHandle -> IO Unit #

Binary UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

put_ :: BinHandle -> UnitId -> IO () #

put :: BinHandle -> UnitId -> IO (Bin UnitId) #

get :: BinHandle -> IO UnitId #

Outputable InstalledModule 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: InstalledModule -> SDoc #

Outputable InstantiatedModule 
Instance details

Defined in GHC.Unit.Types

Outputable InstantiatedUnit 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: InstantiatedUnit -> SDoc #

Outputable Module 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Module -> SDoc #

Outputable Unit 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: Unit -> SDoc #

Outputable UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

ppr :: UnitId -> SDoc #

Eq UnitId 
Instance details

Defined in GHC.Unit.Types

Methods

(==) :: UnitId -> UnitId -> Bool #

(/=) :: UnitId -> UnitId -> Bool #

Ord Unit 
Instance details

Defined in GHC.Unit.Types

Methods

compare :: Unit -> Unit -> Ordering #

(<) :: Unit -> Unit -> Bool #

(<=) :: Unit -> Unit -> Bool #

(>) :: Unit -> Unit -> Bool #

(>=) :: Unit -> Unit -> Bool #

max :: Unit -> Unit -> Unit #

min :: Unit -> Unit -> Unit #

Ord UnitId 
Instance details

Defined in GHC.Unit.Types

defUnitId :: unit -> Definite unit Source #

Module

toUnitId :: Unit -> UnitId #

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.

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