Skip to content

Commit 402f3ea

Browse files
committed
Change MungedPackageName to be non-opaque type.
i.e. strict pair of PackageName and LibraryName the legacy conversion is done via Pretty/Parsec instances. Change of `Maybe UnqualComponentName` to `LibraryName` caused a cascade of other changes, but they all seem to be good changes. In the sense, they made many comments not-so-necessary. Add Distribution.Types.PackageName.Magic for special package names. Updates in cabal-install are mostly trivial type error driven changes. I removed few (deprecated) `Text` instances: `MungedPackageId`, `MungedPackageName` and `LibraryName`. Turns out only a `Pretty` part was used, so it was easy to update. Note: `LibraryName` doesn't have `Pretty` / `Parsec` instances as it's either parsed/printed as a `ComponentName` or `UnqualComponentName`, never stand alone.
1 parent b043757 commit 402f3ea

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

74 files changed

+477
-424
lines changed

Cabal/Cabal.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -370,6 +370,7 @@ library
370370
Distribution.Types.LibraryName
371371
Distribution.Types.MungedPackageName
372372
Distribution.Types.PackageName
373+
Distribution.Types.PackageName.Magic
373374
Distribution.Types.PkgconfigName
374375
Distribution.Types.UnqualComponentName
375376
Distribution.Types.IncludeRenaming

Cabal/Distribution/Backpack/ComponentsGraph.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -73,8 +73,9 @@ mkComponentsGraph enabled pkg_descr =
7373
where
7474
bi = componentBuildInfo component
7575
internalPkgDeps = map (conv . libName) (allLibraries pkg_descr)
76-
conv Nothing = packageNameToUnqualComponentName $ packageName pkg_descr
77-
conv (Just s) = s
76+
77+
conv LMainLibName = packageNameToUnqualComponentName $ packageName pkg_descr
78+
conv (LSubLibName s) = s
7879

7980
-- | Given the package description and a 'PackageDescription' (used
8081
-- to determine if a package name is internal or not), sort the

Cabal/Distribution/Backpack/Configure.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,7 @@ import Distribution.Simple.LocalBuildInfo
4141
import Distribution.Types.AnnotatedId
4242
import Distribution.Types.ComponentRequestedSpec
4343
import Distribution.Types.ComponentInclude
44+
import Distribution.Types.MungedPackageName
4445
import Distribution.Verbosity
4546
import qualified Distribution.Compat.Graph as Graph
4647
import Distribution.Compat.Graph (Graph, IsNode(..))
@@ -277,7 +278,7 @@ mkLinkedComponentsLocalBuildInfo comp rcs = map go rcs
277278
Right instc -> [ (m, OpenModule (DefiniteUnitId uid') m')
278279
| (m, Module uid' m') <- instc_insts instc ]
279280

280-
compat_name = computeCompatPackageName (packageName rc) (libName lib)
281+
compat_name = MungedPackageName (packageName rc) (libName lib)
281282
compat_key = computeCompatPackageKey comp compat_name (packageVersion rc) this_uid
282283

283284
in LibComponentLocalBuildInfo {

Cabal/Distribution/Backpack/ConfiguredComponent.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -315,4 +315,4 @@ fixFakePkgName pkg_descr pn =
315315
else (pn, CLibName LMainLibName )
316316
where
317317
subLibName = packageNameToUnqualComponentName pn
318-
internalLibraries = mapMaybe libName (allLibraries pkg_descr)
318+
internalLibraries = mapMaybe (libraryNameString . libName) (allLibraries pkg_descr)

Cabal/Distribution/Backpack/Id.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,6 @@
55
module Distribution.Backpack.Id(
66
computeComponentId,
77
computeCompatPackageKey,
8-
computeCompatPackageName,
98
) where
109

1110
import Prelude ()

Cabal/Distribution/Backpack/PreExistingComponent.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,7 @@ ipiToPreExistingComponent :: InstalledPackageInfo -> PreExistingComponent
4646
ipiToPreExistingComponent ipi =
4747
PreExistingComponent {
4848
pc_pkgname = packageName ipi,
49-
pc_compname = libraryComponentName $ Installed.sourceLibName ipi,
49+
pc_compname = CLibName $ Installed.sourceLibName ipi,
5050
pc_munged_id = mungedId ipi,
5151
pc_uid = Installed.installedUnitId ipi,
5252
pc_cid = Installed.installedComponentId ipi,

Cabal/Distribution/Backpack/ReadyComponent.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -25,14 +25,15 @@ import Distribution.Types.Component
2525
import Distribution.Types.ComponentInclude
2626
import Distribution.Types.ComponentId
2727
import Distribution.Types.ComponentName
28-
import Distribution.Types.LibraryName
2928
import Distribution.Types.PackageId
29+
import Distribution.Types.PackageName.Magic
3030
import Distribution.Types.UnitId
3131
import Distribution.Compat.Graph (IsNode(..))
3232
import Distribution.Types.Module
3333
import Distribution.Types.MungedPackageId
3434
import Distribution.Types.MungedPackageName
3535
import Distribution.Types.Library
36+
import Distribution.Types.LibraryName
3637

3738
import Distribution.ModuleName
3839
import Distribution.Package
@@ -140,8 +141,7 @@ rc_depends rc = ordNub $
140141
computeCompatPackageId
141142
(ci_pkgid ci)
142143
(case ci_cname ci of
143-
CLibName LMainLibName -> Nothing
144-
CLibName (LSubLibName uqn) -> Just uqn
144+
CLibName name -> name
145145
_ -> error $ prettyShow (rc_cid rc) ++
146146
" depends on non-library " ++ prettyShow (ci_id ci))
147147

@@ -275,7 +275,7 @@ toReadyComponents pid_map subst0 comps
275275
fmap rc_munged_id (join (Map.lookup dep_uid s)))]
276276
where
277277
err_pid = MungedPackageId
278-
(mkMungedPackageName "nonexistent-package-this-is-a-cabal-bug")
278+
(MungedPackageName nonExistentPackageThisIsCabalBug LMainLibName)
279279
(mkVersion [0])
280280
instc = InstantiatedComponent {
281281
instc_insts = Map.toList insts,

Cabal/Distribution/InstalledPackageInfo.hs

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -52,7 +52,6 @@ import Distribution.FieldGrammar.FieldDescrs
5252
import Distribution.ModuleName
5353
import Distribution.Package hiding (installedPackageId, installedUnitId)
5454
import Distribution.Types.ComponentName
55-
import Distribution.Types.LibraryName
5655
import Distribution.Utils.Generic (toUTF8BS)
5756

5857
import qualified Data.Map as Map
@@ -97,10 +96,7 @@ installedPackageId = installedUnitId
9796
-- Munging
9897

9998
sourceComponentName :: InstalledPackageInfo -> ComponentName
100-
sourceComponentName ipi =
101-
case sourceLibName ipi of
102-
Nothing -> CLibName LMainLibName
103-
Just qn -> CLibName $ LSubLibName qn
99+
sourceComponentName = CLibName . sourceLibName
104100

105101
-- -----------------------------------------------------------------------------
106102
-- Parsing

Cabal/Distribution/PackageDescription/Check.hs

Lines changed: 5 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -54,6 +54,7 @@ import Distribution.System
5454
import Distribution.Types.ComponentRequestedSpec
5555
import Distribution.Types.CondTree
5656
import Distribution.Types.ExeDependency
57+
import Distribution.Types.LibraryName
5758
import Distribution.Types.UnqualComponentName
5859
import Distribution.Utils.Generic (isAscii)
5960
import Distribution.Verbosity
@@ -195,7 +196,7 @@ checkSanity pkg =
195196
PackageBuildImpossible
196197
"No executables, libraries, tests, or benchmarks found. Nothing to do."
197198

198-
, check (any isNothing (map libName $ subLibraries pkg)) $
199+
, check (any (== LMainLibName) (map libName $ subLibraries pkg)) $
199200
PackageBuildImpossible $ "Found one or more unnamed internal libraries. "
200201
++ "Only the non-internal library can have the same name as the package."
201202

@@ -236,7 +237,7 @@ checkSanity pkg =
236237
-- The public 'library' gets special dispensation, because it
237238
-- is common practice to export a library and name the executable
238239
-- the same as the package.
239-
subLibNames = catMaybes . map libName $ subLibraries pkg
240+
subLibNames = mapMaybe (libraryNameString . libName) $ subLibraries pkg
240241
exeNames = map exeName $ executables pkg
241242
testNames = map testName $ testSuites pkg
242243
bmNames = map benchmarkName $ benchmarks pkg
@@ -254,10 +255,7 @@ checkLibrary pkg lib =
254255
-- TODO: This check is bogus if a required-signature was passed through
255256
, check (null (explicitLibModules lib) && null (reexportedModules lib)) $
256257
PackageDistSuspiciousWarn $
257-
"Library " ++ (case libName lib of
258-
Nothing -> ""
259-
Just n -> prettyShow n
260-
) ++ "does not expose any modules"
258+
showLibraryName (libName lib) ++ " does not expose any modules"
261259

262260
-- check use of signatures sections
263261
, checkVersion [1,25] (not (null (signatures lib))) $
@@ -589,7 +587,7 @@ checkFields pkg =
589587
, isNoVersion vr ]
590588

591589
internalLibraries =
592-
map (maybe (packageName pkg) (unqualComponentNameToPackageName) . libName)
590+
map (maybe (packageName pkg) (unqualComponentNameToPackageName) . libraryNameString . libName)
593591
(allLibraries pkg)
594592

595593
internalExecutables = map exeName $ executables pkg

Cabal/Distribution/PackageDescription/Configuration.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -455,7 +455,7 @@ finalizePD userflags enabled satisfyDep
455455
(mb_lib, comps) = flattenTaggedTargets targetSet
456456
mb_lib' = fmap libFillInDefaults mb_lib
457457
comps' = flip map comps $ \(n,c) -> foldComponent
458-
(\l -> CLib (libFillInDefaults l) { libName = Just n
458+
(\l -> CLib (libFillInDefaults l) { libName = LSubLibName n
459459
, libExposed = False })
460460
(\l -> CFLib (flibFillInDefaults l) { foreignLibName = n })
461461
(\e -> CExe (exeFillInDefaults e) { exeName = n })
@@ -541,14 +541,14 @@ flattenPackageDescription
541541
}
542542
where
543543
mlib = f <$> mlib0
544-
where f lib = (libFillInDefaults . fst . ignoreConditions $ lib) { libName = Nothing }
544+
where f lib = (libFillInDefaults . fst . ignoreConditions $ lib) { libName = LMainLibName }
545545
sub_libs = flattenLib <$> sub_libs0
546546
flibs = flattenFLib <$> flibs0
547547
exes = flattenExe <$> exes0
548548
tests = flattenTst <$> tests0
549549
bms = flattenBm <$> bms0
550550
flattenLib (n, t) = libFillInDefaults $ (fst $ ignoreConditions t)
551-
{ libName = Just n, libExposed = False }
551+
{ libName = LSubLibName n, libExposed = False }
552552
flattenFLib (n, t) = flibFillInDefaults $ (fst $ ignoreConditions t)
553553
{ foreignLibName = n }
554554
flattenExe (n, t) = exeFillInDefaults $ (fst $ ignoreConditions t)

Cabal/Distribution/PackageDescription/FieldGrammar.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -123,7 +123,7 @@ packageDescriptionFieldGrammar = PackageDescription
123123

124124
libraryFieldGrammar
125125
:: (FieldGrammar g, Applicative (g Library), Applicative (g BuildInfo))
126-
=> Maybe UnqualComponentName
126+
=> LibraryName
127127
-> g Library Library
128128
libraryFieldGrammar n = Library n
129129
<$> monoidalFieldAla "exposed-modules" (alaList' VCat MQuoted) L.exposedModules
@@ -134,16 +134,16 @@ libraryFieldGrammar n = Library n
134134
<*> visibilityField
135135
<*> blurFieldGrammar L.libBuildInfo buildInfoFieldGrammar
136136
where
137-
visibilityField
137+
visibilityField = case n of
138138
-- nameless/"main" libraries are public
139-
| isNothing n = pure LibraryVisibilityPublic
139+
LMainLibName -> pure LibraryVisibilityPublic
140140
-- named libraries have the field
141-
| otherwise =
141+
LSubLibName _ ->
142142
optionalFieldDef "visibility" L.libVisibility LibraryVisibilityPrivate
143143
^^^ availableSince CabalSpecV3_0 LibraryVisibilityPrivate
144144

145-
{-# SPECIALIZE libraryFieldGrammar :: Maybe UnqualComponentName -> ParsecFieldGrammar' Library #-}
146-
{-# SPECIALIZE libraryFieldGrammar :: Maybe UnqualComponentName -> PrettyFieldGrammar' Library #-}
145+
{-# SPECIALIZE libraryFieldGrammar :: LibraryName -> ParsecFieldGrammar' Library #-}
146+
{-# SPECIALIZE libraryFieldGrammar :: LibraryName -> PrettyFieldGrammar' Library #-}
147147

148148
-------------------------------------------------------------------------------
149149
-- Foreign library

Cabal/Distribution/PackageDescription/Parsec.hs

Lines changed: 10 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -267,16 +267,18 @@ goSections specVer = traverse_ process
267267
"Multiple main libraries; have you forgotten to specify a name for an internal library?"
268268

269269
commonStanzas <- use stateCommonStanzas
270-
lib <- lift $ parseCondTree' (libraryFieldGrammar Nothing) (libraryFromBuildInfo Nothing) commonStanzas fields
271-
270+
let name'' = LMainLibName
271+
lib <- lift $ parseCondTree' (libraryFieldGrammar name'') (libraryFromBuildInfo name'') commonStanzas fields
272+
--
273+
-- TODO check that not set
272274
stateGpd . L.condLibrary ?= lib
273275

274276
-- Sublibraries
275277
-- TODO: check cabal-version
276278
| name == "library" = do
277279
commonStanzas <- use stateCommonStanzas
278280
name' <- parseUnqualComponentName pos args
279-
let name'' = Just name'
281+
let name'' = LSubLibName name'
280282
lib <- lift $ parseCondTree' (libraryFieldGrammar name'') (libraryFromBuildInfo name'') commonStanzas fields
281283
-- TODO check duplicate name here?
282284
stateGpd . L.condSubLibraries %= snoc (name', lib)
@@ -545,10 +547,12 @@ type CondTreeBuildInfo = CondTree ConfVar [Dependency] BuildInfo
545547
class L.HasBuildInfo a => FromBuildInfo a where
546548
fromBuildInfo' :: BuildInfo -> a
547549

548-
libraryFromBuildInfo :: Maybe UnqualComponentName -> BuildInfo -> Library
550+
libraryFromBuildInfo :: LibraryName -> BuildInfo -> Library
549551
libraryFromBuildInfo n bi = emptyLibrary
550552
{ libName = n
551-
, libVisibility = if isNothing n then LibraryVisibilityPublic else LibraryVisibilityPrivate
553+
, libVisibility = case n of
554+
LMainLibName -> LibraryVisibilityPublic
555+
LSubLibName _ -> LibraryVisibilityPrivate
552556
, libBuildInfo = bi
553557
}
554558

@@ -726,7 +730,7 @@ data Syntax = OldSyntax | NewSyntax
726730

727731
-- TODO:
728732
libFieldNames :: [FieldName]
729-
libFieldNames = fieldGrammarKnownFieldList (libraryFieldGrammar Nothing)
733+
libFieldNames = fieldGrammarKnownFieldList (libraryFieldGrammar LMainLibName)
730734

731735
-------------------------------------------------------------------------------
732736
-- Suplementary build information

Cabal/Distribution/PackageDescription/PrettyPrint.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -34,6 +34,7 @@ import Prelude ()
3434
import Distribution.Types.CondTree
3535
import Distribution.Types.Dependency
3636
import Distribution.Types.ForeignLib (ForeignLib (foreignLibName))
37+
import Distribution.Types.LibraryName
3738
import Distribution.Types.UnqualComponentName
3839

3940
import Distribution.PackageDescription
@@ -133,12 +134,12 @@ ppCondTree2 grammar = go
133134
ppCondLibrary :: Maybe (CondTree ConfVar [Dependency] Library) -> [PrettyField]
134135
ppCondLibrary Nothing = mempty
135136
ppCondLibrary (Just condTree) = pure $ PrettySection "library" [] $
136-
ppCondTree2 (libraryFieldGrammar Nothing) condTree
137+
ppCondTree2 (libraryFieldGrammar LMainLibName) condTree
137138

138139
ppCondSubLibraries :: [(UnqualComponentName, CondTree ConfVar [Dependency] Library)] -> [PrettyField]
139140
ppCondSubLibraries libs =
140141
[ PrettySection "library" [pretty n]
141-
$ ppCondTree2 (libraryFieldGrammar $ Just n) condTree
142+
$ ppCondTree2 (libraryFieldGrammar $ LSubLibName n) condTree
142143
| (n, condTree) <- libs
143144
]
144145

@@ -216,7 +217,7 @@ pdToGpd pd = GenericPackageDescription
216217
-- We set CondTree's [Dependency] to an empty list, as it
217218
-- is not pretty printed anyway.
218219
mkCondTree x = CondNode x [] []
219-
mkCondTreeL l = (fromMaybe (mkUnqualComponentName "") (libName l), CondNode l [] [])
220+
mkCondTreeL l = (fromMaybe (mkUnqualComponentName "") (libraryNameString (libName l)), CondNode l [] [])
220221

221222
mkCondTree'
222223
:: (a -> UnqualComponentName)

Cabal/Distribution/Simple/Build.hs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -454,7 +454,7 @@ testSuiteLibV09AsLibAndExe pkg_descr
454454
where
455455
bi = testBuildInfo test
456456
lib = Library {
457-
libName = Nothing,
457+
libName = LMainLibName,
458458
exposedModules = [ m ],
459459
reexportedModules = [],
460460
signatures = [],
@@ -465,7 +465,8 @@ testSuiteLibV09AsLibAndExe pkg_descr
465465
-- This is, like, the one place where we use a CTestName for a library.
466466
-- Should NOT use library name, since that could conflict!
467467
PackageIdentifier pkg_name pkg_ver = package pkg_descr
468-
compat_name = computeCompatPackageName pkg_name (Just (testName test))
468+
-- Note: we do make internal library from the test!
469+
compat_name = MungedPackageName pkg_name (LSubLibName (testName test))
469470
compat_key = computeCompatPackageKey (compiler lbi) compat_name pkg_ver (componentUnitId clbi)
470471
libClbi = LibComponentLocalBuildInfo
471472
{ componentPackageDeps = componentPackageDeps clbi
@@ -483,7 +484,7 @@ testSuiteLibV09AsLibAndExe pkg_descr
483484
, componentExposedModules = [IPI.ExposedModule m Nothing]
484485
}
485486
pkg = pkg_descr {
486-
package = (package pkg_descr) { pkgName = mkPackageName $ unMungedPackageName compat_name }
487+
package = (package pkg_descr) { pkgName = mkPackageName $ prettyShow compat_name }
487488
, executables = []
488489
, testSuites = []
489490
, subLibraries = [lib]
@@ -505,7 +506,7 @@ testSuiteLibV09AsLibAndExe pkg_descr
505506
-- | The stub executable needs a new 'ComponentLocalBuildInfo'
506507
-- that exposes the relevant test suite library.
507508
deps = (IPI.installedUnitId ipi, mungedId ipi)
508-
: (filter (\(_, x) -> let name = unMungedPackageName $ mungedName x
509+
: (filter (\(_, x) -> let name = prettyShow $ mungedName x
509510
in name == "Cabal" || name == "base")
510511
(componentPackageDeps clbi))
511512
exeClbi = ExeComponentLocalBuildInfo {

Cabal/Distribution/Simple/Build/Macros.hs

Lines changed: 3 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -82,13 +82,11 @@ generate pkg_descr lbi clbi =
8282
generateComponentIdMacro lbi clbi ++
8383
generateCurrentPackageVersion pkg_descr
8484
where
85-
getPid (_, MungedPackageId mpn v) =
86-
PackageIdentifier pn v
87-
where
88-
-- NB: Drop the component name! We're just reporting package versions.
85+
getPid (_, MungedPackageId (MungedPackageName pn _) v) =
86+
-- NB: Drop the library name! We're just reporting package versions.
8987
-- This would have to be revisited if you are allowed to depend
9088
-- on different versions of the same package
91-
pn = fst (decodeCompatPackageName mpn)
89+
PackageIdentifier pn v
9290

9391
-- | Helper function that generates just the @VERSION_pkg@ and @MIN_VERSION_pkg@
9492
-- macros for a list of package ids (usually used with the specific deps of

0 commit comments

Comments
 (0)