Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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 | |
(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 # |
A Version
represents the version of a software entity.
An instance of Eq
is provided, which implements exact equality
modulo reordering of the tags in the versionTags
field.
An instance of Ord
is also provided, which gives lexicographic
ordering on the versionBranch
fields (i.e. 2.1 > 2.0, 1.2.3 > 1.2.2,
etc.). This is expected to be sufficient for many uses, but note that
you may need to use a more specific ordering for your versioning
scheme. For example, some versioning schemes may include pre-releases
which have tags "pre1"
, "pre2"
, and so on, and these would need to
be taken into account when determining ordering. In some cases, date
ordering may be more appropriate, so the application would have to
look for date
tags in the versionTags
field and compare those.
The bottom line is, don't always assume that compare
and other Ord
operations are the right thing for every Version
.
Similarly, concrete representations of versions may differ. One
possible concrete representation is provided (see showVersion
and
parseVersion
), but depending on the application a different concrete
representation may be more appropriate.
Version | |
|
Instances
Data Version | Since: base-4.7.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Version -> c Version Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Version Source # toConstr :: Version -> Constr Source # dataTypeOf :: Version -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Version) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version) Source # gmapT :: (forall b. Data b => b -> b) -> Version -> Version Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Version -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Version -> m Version Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version Source # | |
Generic Version | |
IsList Version | Since: base-4.8.0.0 |
Read Version | Since: base-2.1 |
Show Version | Since: base-2.1 |
Binary Version | Since: binary-0.8.0.0 |
NFData Version | Since: deepseq-1.3.0.0 |
Defined in Control.DeepSeq | |
Eq Version | Since: base-2.1 |
Ord Version | Since: base-2.1 |
type Rep Version | Since: base-4.9.0.0 |
Defined in Data.Version type Rep Version = D1 ('MetaData "Version" "Data.Version" "base" '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.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 #