Safe Haskell | None |
---|---|
Language | Haskell2010 |
Info about installed units (compiled libraries)
Synopsis
- data GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod = GenericUnitInfo {
- unitId :: uid
- unitInstanceOf :: compid
- unitInstantiations :: [(modulename, mod)]
- unitPackageId :: srcpkgid
- unitPackageName :: srcpkgname
- unitPackageVersion :: Version
- unitComponentName :: Maybe srcpkgname
- unitAbiHash :: String
- unitDepends :: [uid]
- unitAbiDepends :: [(uid, String)]
- unitImportDirs :: [FilePath]
- unitLibraries :: [String]
- unitExtDepLibsSys :: [String]
- unitExtDepLibsGhc :: [String]
- unitLibraryDirs :: [FilePath]
- unitLibraryDynDirs :: [FilePath]
- unitExtDepFrameworks :: [String]
- unitExtDepFrameworkDirs :: [FilePath]
- unitLinkerOptions :: [String]
- unitCcOptions :: [String]
- unitIncludes :: [String]
- unitIncludeDirs :: [FilePath]
- unitHaddockInterfaces :: [FilePath]
- unitHaddockHTMLs :: [FilePath]
- unitExposedModules :: [(modulename, Maybe mod)]
- unitHiddenModules :: [modulename]
- unitIsIndefinite :: Bool
- unitIsExposed :: Bool
- unitIsTrusted :: Bool
- type GenUnitInfo unit = GenericUnitInfo (Indefinite unit) PackageId PackageName unit ModuleName (GenModule (GenUnit unit))
- type UnitInfo = GenUnitInfo UnitId
- newtype UnitKey = UnitKey FastString
- type UnitKeyInfo = GenUnitInfo UnitKey
- mkUnitKeyInfo :: DbUnitInfo -> UnitKeyInfo
- mapUnitInfo :: (u -> v) -> (v -> FastString) -> GenUnitInfo u -> GenUnitInfo v
- mkUnitPprInfo :: 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
Documentation
data GenericUnitInfo compid 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 # | |
(Eq uid, Eq compid, Eq modulename, Eq mod, Eq srcpkgid, Eq srcpkgname) => Eq (GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod) | |
Defined in GHC.Unit.Database (==) :: GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> Bool # (/=) :: GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod -> Bool # | |
(Show uid, Show compid, Show modulename, Show mod, Show srcpkgid, Show srcpkgname) => Show (GenericUnitInfo compid srcpkgid srcpkgname uid modulename mod) | |
Defined in GHC.Unit.Database |
type GenUnitInfo unit = GenericUnitInfo (Indefinite unit) 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)
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 :: (u -> v) -> (v -> FastString) -> GenUnitInfo u -> GenUnitInfo v Source #
Map over the unit parameter
mkUnitPprInfo :: 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
Eq PackageName # | |
Defined in GHC.Unit.Info (==) :: PackageName -> PackageName -> Bool # (/=) :: PackageName -> PackageName -> Bool # | |
Ord PackageName # | |
Defined in GHC.Unit.Info compare :: PackageName -> PackageName -> Ordering # (<) :: PackageName -> PackageName -> Bool # (<=) :: PackageName -> PackageName -> Bool # (>) :: PackageName -> PackageName -> Bool # (>=) :: PackageName -> PackageName -> Bool # max :: PackageName -> PackageName -> PackageName # min :: PackageName -> PackageName -> PackageName # | |
Outputable PackageName # | |
Defined in GHC.Unit.Info | |
Uniquable PackageName # | |
Defined in GHC.Unit.Info getUnique :: PackageName -> Unique Source # |
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
IsList Version | Since: base-4.8.0.0 |
Eq Version | Since: base-2.1 |
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 # | |
Ord Version | Since: base-2.1 |
Read Version | Since: base-2.1 |
Show Version | Since: base-2.1 |
Generic Version | Since: base-4.9.0.0 |
Binary Version | Since: binary-0.8.0.0 |
NFData Version | Since: deepseq-1.3.0.0 |
Defined in Control.DeepSeq | |
type Rep Version | |
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 | |
unitPackageNameString :: GenUnitInfo u -> String Source #
unitPackageIdString :: GenUnitInfo u -> String Source #
pprUnitInfo :: UnitInfo -> SDoc Source #