Cabal-3.6.3.0: A framework for packaging Haskell software
Safe HaskellSafe-Inferred
LanguageHaskell2010

Distribution.Types.MungedPackageName

Synopsis

Documentation

data MungedPackageName Source #

A combination of a package and component name used in various legacy interfaces, chiefly bundled with a version as MungedPackageId. It's generally better to use a UnitId to opaquely refer to some compilation/packing unit, but that doesn't always work, e.g. where a "name" is needed, in which case this can be used as a fallback.

Use mkMungedPackageName and unMungedPackageName to convert from/to a String.

In 3.0.0.0 representation was changed from opaque (string) to semantic representation.

Since: Cabal-2.0.0.2

Instances

Instances details
Parsec MungedPackageName Source #
>>> simpleParsec "servant" :: Maybe MungedPackageName
Just (MungedPackageName (PackageName "servant") LMainLibName)
>>> simpleParsec "z-servant-z-lackey" :: Maybe MungedPackageName
Just (MungedPackageName (PackageName "servant") (LSubLibName (UnqualComponentName "lackey")))
>>> simpleParsec "z-servant-zz" :: Maybe MungedPackageName
Just (MungedPackageName (PackageName "z-servant-zz") LMainLibName)
Instance details

Defined in Distribution.Types.MungedPackageName

Pretty MungedPackageName Source #

Computes the package name for a library. If this is the public library, it will just be the original package name; otherwise, it will be a munged package name recording the original package name as well as the name of the internal library.

A lot of tooling in the Haskell ecosystem assumes that if something is installed to the package database with the package name foo, then it actually is an entry for the (only public) library in package foo. With internal packages, this is not necessarily true: a public library as well as arbitrarily many internal libraries may come from the same package. To prevent tools from getting confused in this case, the package name of these internal libraries is munged so that they do not conflict the public library proper. A particular case where this matters is ghc-pkg: if we don't munge the package name, the inplace registration will OVERRIDE a different internal library.

We munge into a reserved namespace, "z-", and encode both the component name and the package name of an internal library using the following format:

compat-pkg-name ::= "z-" package-name "-z-" library-name

where package-name and library-name have "-" ( "z" + ) "-" segments encoded by adding an extra "z".

When we have the public library, the compat-pkg-name is just the package-name, no surprises there!

>>> prettyShow $ MungedPackageName "servant" LMainLibName
"servant"
>>> prettyShow $ MungedPackageName "servant" (LSubLibName "lackey")
"z-servant-z-lackey"
Instance details

Defined in Distribution.Types.MungedPackageName

Structured MungedPackageName Source # 
Instance details

Defined in Distribution.Types.MungedPackageName

Data MungedPackageName Source # 
Instance details

Defined in Distribution.Types.MungedPackageName

Methods

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

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

toConstr :: MungedPackageName -> Constr Source #

dataTypeOf :: MungedPackageName -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Generic MungedPackageName Source # 
Instance details

Defined in Distribution.Types.MungedPackageName

Associated Types

type Rep MungedPackageName :: Type -> Type Source #

Read MungedPackageName Source # 
Instance details

Defined in Distribution.Types.MungedPackageName

Show MungedPackageName Source # 
Instance details

Defined in Distribution.Types.MungedPackageName

Binary MungedPackageName Source # 
Instance details

Defined in Distribution.Types.MungedPackageName

NFData MungedPackageName Source # 
Instance details

Defined in Distribution.Types.MungedPackageName

Methods

rnf :: MungedPackageName -> () Source #

Eq MungedPackageName Source # 
Instance details

Defined in Distribution.Types.MungedPackageName

Ord MungedPackageName Source # 
Instance details

Defined in Distribution.Types.MungedPackageName

type Rep MungedPackageName Source # 
Instance details

Defined in Distribution.Types.MungedPackageName

type Rep MungedPackageName = D1 ('MetaData "MungedPackageName" "Distribution.Types.MungedPackageName" "Cabal-3.6.3.0" 'False) (C1 ('MetaCons "MungedPackageName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PackageName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LibraryName)))

decodeCompatPackageName :: PackageName -> MungedPackageName Source #

Intended for internal use only

>>> decodeCompatPackageName "z-servant-z-lackey"
MungedPackageName (PackageName "servant") (LSubLibName (UnqualComponentName "lackey"))

encodeCompatPackageName :: MungedPackageName -> PackageName Source #

Intended for internal use only

>>> encodeCompatPackageName $ MungedPackageName "servant" (LSubLibName "lackey")
PackageName "z-servant-z-lackey"

This is used in cabal-install in the Solver. May become obsolete as solver moves to per-component solving.