Cabal-2.2.0.0: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Types.UnitId

Synopsis

Documentation

data UnitId Source #

A unit identifier identifies a (possibly instantiated) package/component that can be installed the installed package database. There are several types of components that can be installed:

  • A traditional library with no holes, so that unitIdHash is Nothing. In the absence of Backpack, UnitId is the same as a ComponentId.
  • An indefinite, Backpack library with holes. In this case, unitIdHash is still Nothing, but in the install, there are only interfaces, no compiled objects.
  • An instantiated Backpack library with all the holes filled in. unitIdHash is a Just a hash of the instantiating mapping.

A unit is a component plus the additional information on how the holes are filled in. Thus there is a one to many relationship: for a particular component there are many different ways of filling in the holes, and each different combination is a unit (and has a separate UnitId).

UnitId is distinct from OpenUnitId, in that it is always installed, whereas OpenUnitId are intermediate unit identities that arise during mixin linking, and don't necessarily correspond to any actually installed unit. Since the mapping is not actually recorded in a UnitId, you can't actually substitute over them (but you can substitute over OpenUnitId). See also Distribution.Backpack.FullUnitId for a mechanism for expanding an instantiated UnitId to retrieve its mapping.

Backwards compatibility note: if you need to get the string representation of a UnitId to pass, e.g., as a -package-id flag, use the display function, which will work on all versions of Cabal.

Instances
Eq UnitId Source # 
Instance details

Methods

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

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

Data UnitId Source # 
Instance details

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 :: (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 #

Ord UnitId Source # 
Instance details
Read UnitId Source # 
Instance details
Show UnitId Source # 
Instance details
IsString UnitId Source #

mkUnitId

Since: 2.0.0.2

Instance details

Methods

fromString :: String -> UnitId #

Generic UnitId Source # 
Instance details

Associated Types

type Rep UnitId :: * -> * #

Methods

from :: UnitId -> Rep UnitId x #

to :: Rep UnitId x -> UnitId #

Binary UnitId Source # 
Instance details

Methods

put :: UnitId -> Put #

get :: Get UnitId #

putList :: [UnitId] -> Put #

NFData UnitId Source # 
Instance details

Methods

rnf :: UnitId -> () #

Pretty UnitId Source #

The textual format for UnitId coincides with the format GHC accepts for -package-id.

Instance details

Methods

pretty :: UnitId -> Doc Source #

Parsec UnitId Source #

The textual format for UnitId coincides with the format GHC accepts for -package-id.

Instance details

Methods

parsec :: CabalParsing m => m UnitId Source #

Text UnitId Source # 
Instance details
type Rep UnitId Source # 
Instance details
type Rep UnitId = D1 (MetaData "UnitId" "Distribution.Types.UnitId" "Cabal-2.2.0.0-inplace" True) (C1 (MetaCons "UnitId" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ShortText)))

unUnitId :: UnitId -> String Source #

If you need backwards compatibility, consider using display instead, which is supported by all versions of Cabal.

data DefUnitId Source #

A UnitId for a definite package. The DefUnitId invariant says that a UnitId identified this way is definite; i.e., it has no unfilled holes.

Instances
Eq DefUnitId Source # 
Instance details
Data DefUnitId Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DefUnitId -> c DefUnitId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DefUnitId #

toConstr :: DefUnitId -> Constr #

dataTypeOf :: DefUnitId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DefUnitId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DefUnitId) #

gmapT :: (forall b. Data b => b -> b) -> DefUnitId -> DefUnitId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DefUnitId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DefUnitId -> r #

gmapQ :: (forall d. Data d => d -> u) -> DefUnitId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DefUnitId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DefUnitId -> m DefUnitId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DefUnitId -> m DefUnitId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DefUnitId -> m DefUnitId #

Ord DefUnitId Source # 
Instance details
Read DefUnitId Source # 
Instance details
Show DefUnitId Source # 
Instance details
Generic DefUnitId Source # 
Instance details

Associated Types

type Rep DefUnitId :: * -> * #

Binary DefUnitId Source # 
Instance details
NFData DefUnitId Source # 
Instance details

Methods

rnf :: DefUnitId -> () #

Pretty DefUnitId Source # 
Instance details

Methods

pretty :: DefUnitId -> Doc Source #

Parsec DefUnitId Source # 
Instance details
Text DefUnitId Source # 
Instance details
type Rep DefUnitId Source # 
Instance details
type Rep DefUnitId = D1 (MetaData "DefUnitId" "Distribution.Types.UnitId" "Cabal-2.2.0.0-inplace" True) (C1 (MetaCons "DefUnitId" PrefixI True) (S1 (MetaSel (Just "unDefUnitId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UnitId)))

unsafeMkDefUnitId :: UnitId -> DefUnitId Source #

Unsafely create a DefUnitId from a UnitId. Your responsibility is to ensure that the DefUnitId invariant holds.

newSimpleUnitId :: ComponentId -> UnitId Source #

Create a unit identity with no associated hash directly from a ComponentId.

mkLegacyUnitId :: PackageId -> UnitId Source #

Make an old-style UnitId from a package identifier. Assumed to be for the public library

getHSLibraryName :: UnitId -> String Source #

Returns library name prefixed with HS, suitable for filenames

type InstalledPackageId = UnitId Source #

Deprecated: Use UnitId instead. This symbol will be removed in Cabal-3.0 (est. Oct 2018).