Safe Haskell | None |
---|---|
Language | GHC2021 |
Info about installed units (compiled libraries)
Synopsis
- data GenericUnitInfo srcpkgid srcpkgname uid modulename mod = GenericUnitInfo {
- unitId :: uid
- unitInstanceOf :: uid
- unitInstantiations :: [(modulename, mod)]
- unitPackageId :: srcpkgid
- unitPackageName :: srcpkgname
- unitPackageVersion :: Version
- unitComponentName :: Maybe srcpkgname
- unitAbiHash :: ShortText
- unitDepends :: [uid]
- unitAbiDepends :: [(uid, ShortText)]
- unitImportDirs :: [FilePathST]
- unitLibraries :: [ShortText]
- unitExtDepLibsSys :: [ShortText]
- unitExtDepLibsGhc :: [ShortText]
- unitLibraryDirs :: [FilePathST]
- unitLibraryDynDirs :: [FilePathST]
- unitExtDepFrameworks :: [ShortText]
- unitExtDepFrameworkDirs :: [FilePathST]
- unitLinkerOptions :: [ShortText]
- unitCcOptions :: [ShortText]
- unitIncludes :: [ShortText]
- unitIncludeDirs :: [FilePathST]
- unitHaddockInterfaces :: [FilePathST]
- unitHaddockHTMLs :: [FilePathST]
- unitExposedModules :: [(modulename, Maybe mod)]
- unitHiddenModules :: [modulename]
- unitIsIndefinite :: Bool
- unitIsExposed :: Bool
- unitIsTrusted :: Bool
- type GenUnitInfo unit = GenericUnitInfo PackageId PackageName unit ModuleName (GenModule (GenUnit unit))
- type UnitInfo = GenUnitInfo UnitId
- newtype UnitKey = UnitKey FastString
- type UnitKeyInfo = GenUnitInfo UnitKey
- mkUnitKeyInfo :: DbUnitInfo -> UnitKeyInfo
- mapUnitInfo :: IsUnitId v => (u -> v) -> GenUnitInfo u -> GenUnitInfo v
- mkUnitPprInfo :: (u -> FastString) -> GenUnitInfo u -> UnitPprInfo
- mkUnit :: UnitInfo -> Unit
- newtype PackageId = PackageId FastString
- newtype PackageName = PackageName {}
- data Version = Version {
- versionBranch :: [Int]
- versionTags :: [String]
- unitPackageNameString :: GenUnitInfo u -> String
- unitPackageIdString :: GenUnitInfo u -> String
- pprUnitInfo :: UnitInfo -> SDoc
- collectIncludeDirs :: [UnitInfo] -> [FilePath]
- collectExtraCcOpts :: [UnitInfo] -> [String]
- collectLibraryDirs :: Ways -> [UnitInfo] -> [FilePath]
- collectFrameworks :: [UnitInfo] -> [String]
- collectFrameworksDirs :: [UnitInfo] -> [String]
- unitHsLibs :: GhcNameVersion -> Ways -> UnitInfo -> [String]
Documentation
data GenericUnitInfo srcpkgid srcpkgname uid modulename mod Source #
Information about an unit (a unit is an installed module library).
This is a subset of Cabal's InstalledPackageInfo
, with just the bits
that GHC is interested in.
Some types are left as parameters to be instantiated differently in ghc-pkg and in ghc itself.
GenericUnitInfo | |
|
Instances
Binary DbUnitInfo | |
Defined in GHC.Unit.Database put :: DbUnitInfo -> Put Source # get :: Get DbUnitInfo Source # putList :: [DbUnitInfo] -> Put Source # | |
(Show uid, Show modulename, Show mod, Show srcpkgid, Show srcpkgname) => Show (GenericUnitInfo srcpkgid srcpkgname uid modulename mod) | |
Defined in GHC.Unit.Database showsPrec :: Int -> GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> ShowS # show :: GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> String # showList :: [GenericUnitInfo srcpkgid srcpkgname uid modulename mod] -> ShowS # | |
(Eq uid, Eq modulename, Eq mod, Eq srcpkgid, Eq srcpkgname) => Eq (GenericUnitInfo srcpkgid srcpkgname uid modulename mod) | |
Defined in GHC.Unit.Database (==) :: GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> Bool # (/=) :: GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> GenericUnitInfo srcpkgid srcpkgname uid modulename mod -> Bool # |
type GenUnitInfo unit = GenericUnitInfo PackageId PackageName unit ModuleName (GenModule (GenUnit unit)) Source #
Information about an installed unit
We parameterize on the unit identifier:
* UnitKey: identifier used in the database (cf UnitKeyInfo
)
* UnitId: identifier used to generate code (cf UnitInfo
)
These two identifiers are different for wired-in packages. See Note [About units] in GHC.Unit
type UnitInfo = GenUnitInfo UnitId Source #
Information about an installed unit (units are identified by their internal UnitId)
A unit key in the database
Instances
IsUnitId UnitKey Source # | |
Defined in GHC.Unit.Types unitFS :: UnitKey -> FastString Source # |
type UnitKeyInfo = GenUnitInfo UnitKey Source #
Information about an installed unit (units are identified by their database UnitKey)
mkUnitKeyInfo :: DbUnitInfo -> UnitKeyInfo Source #
Convert a DbUnitInfo (read from a package database) into UnitKeyInfo
mapUnitInfo :: IsUnitId v => (u -> v) -> GenUnitInfo u -> GenUnitInfo v Source #
Map over the unit parameter
mkUnitPprInfo :: (u -> FastString) -> GenUnitInfo u -> UnitPprInfo Source #
Create a UnitPprInfo from a UnitInfo
mkUnit :: UnitInfo -> Unit 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).
newtype PackageName Source #
Instances
Uniquable PackageName Source # | |
Defined in GHC.Unit.Info getUnique :: PackageName -> Unique Source # | |
Outputable PackageName Source # | |
Defined in GHC.Unit.Info ppr :: PackageName -> SDoc Source # | |
Eq PackageName Source # | |
Defined in GHC.Unit.Info (==) :: PackageName -> PackageName -> Bool # (/=) :: PackageName -> PackageName -> Bool # |
Version | |
|
Instances
Binary Version | Since: binary-0.8.0.0 | ||||
NFData Version | Since: deepseq-1.3.0.0 | ||||
Defined in Control.DeepSeq | |||||
Data Version | |||||
Defined in GHC.Internal.Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Version -> c Version # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Version # toConstr :: Version -> Constr # dataTypeOf :: Version -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Version) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version) # gmapT :: (forall b. Data b => b -> b) -> Version -> Version # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r # gmapQ :: (forall d. Data d => d -> u) -> Version -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version # | |||||
Generic Version | |||||
Defined in GHC.Internal.Data.Version
| |||||
IsList Version | |||||
Read Version | |||||
Show Version | |||||
Eq Version | |||||
Ord Version | |||||
type Rep Version | |||||
Defined in GHC.Internal.Data.Version type Rep Version = D1 ('MetaData "Version" "GHC.Internal.Data.Version" "ghc-internal" 'False) (C1 ('MetaCons "Version" 'PrefixI 'True) (S1 ('MetaSel ('Just "versionBranch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Int]) :*: S1 ('MetaSel ('Just "versionTags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]))) | |||||
type Item Version | |||||
Defined in GHC.Internal.IsList |
unitPackageNameString :: GenUnitInfo u -> String Source #
unitPackageIdString :: GenUnitInfo u -> String Source #
pprUnitInfo :: UnitInfo -> SDoc Source #
collectIncludeDirs :: [UnitInfo] -> [FilePath] Source #
Find all the include directories in the given units
collectExtraCcOpts :: [UnitInfo] -> [String] Source #
Find all the C-compiler options in the given units
collectLibraryDirs :: Ways -> [UnitInfo] -> [FilePath] Source #
Find all the library directories in the given units for the given ways
collectFrameworks :: [UnitInfo] -> [String] Source #
Find all the frameworks in the given units
collectFrameworksDirs :: [UnitInfo] -> [String] Source #
Find all the package framework paths in these and the preload packages
unitHsLibs :: GhcNameVersion -> Ways -> UnitInfo -> [String] Source #