Skip to content

Commit 02e4381

Browse files
committed
Rename fields in SourcePackage
Also remove specific field for PackageId, as it is in GPD.
1 parent a6915fe commit 02e4381

20 files changed

+88
-92
lines changed

cabal-install/Distribution/Client/BuildReports/Storage.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -148,7 +148,7 @@ fromPlanPackage (Platform arch os) comp
148148
buildResult
149149
, extractRepo srcPkg)
150150
where
151-
extractRepo (SourcePackage { packageSource = RepoTarballPackage repo _ _ })
151+
extractRepo (SourcePackage { srcpkgSource = RepoTarballPackage repo _ _ })
152152
= Just repo
153153
extractRepo _ = Nothing
154154

cabal-install/Distribution/Client/CmdInstall.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -443,11 +443,11 @@ getSpecsAndTargetSelectors verbosity reducedVerbosity pkgDb targetSelectors loca
443443
planMap = InstallPlan.toMap elaboratedPlan
444444
targetIds = Map.keys targets
445445

446-
sdistize (SpecificSourcePackage spkg@SourcePackage{..}) =
446+
sdistize (SpecificSourcePackage spkg) =
447447
SpecificSourcePackage spkg'
448448
where
449-
sdistPath = distSdistFile localDistDirLayout packageInfoId
450-
spkg' = spkg { packageSource = LocalTarballPackage sdistPath }
449+
sdistPath = distSdistFile localDistDirLayout (packageId spkg)
450+
spkg' = spkg { srcpkgSource = LocalTarballPackage sdistPath }
451451
sdistize named = named
452452

453453
local = sdistize <$> localPackages localBaseCtx

cabal-install/Distribution/Client/CmdRepl.hs

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -360,10 +360,9 @@ withoutProject config verbosity extraArgs = do
360360
-- We need to create a dummy package that lives in our dummy project.
361361
let
362362
sourcePackage = SourcePackage
363-
{ packageInfoId = pkgId
364-
, packageDescription = genericPackageDescription
365-
, packageSource = LocalUnpackedPackage tempDir
366-
, packageDescrOverride = Nothing
363+
{ srcpkgDescription = genericPackageDescription
364+
, srcpkgSource = LocalUnpackedPackage tempDir
365+
, srcpkgDescrOverride = Nothing
367366
}
368367
genericPackageDescription = emptyGenericPackageDescription
369368
& L.packageDescription .~ packageDescription
@@ -414,8 +413,8 @@ addDepsToProjectTarget deps pkgId ctx =
414413
addDeps (SpecificSourcePackage pkg)
415414
| packageId pkg /= pkgId = SpecificSourcePackage pkg
416415
| SourcePackage{..} <- pkg =
417-
SpecificSourcePackage $ pkg { packageDescription =
418-
packageDescription & (\f -> L.allCondTrees $ traverseCondTreeC f)
416+
SpecificSourcePackage $ pkg { srcpkgDescription =
417+
srcpkgDescription & (\f -> L.allCondTrees $ traverseCondTreeC f)
419418
%~ (deps ++)
420419
}
421420
addDeps spec = spec

cabal-install/Distribution/Client/CmdRun.hs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -406,10 +406,9 @@ handleScriptCase verbosity pol baseCtx tmpDir scriptContents = do
406406
LiterateHaskell -> "Main.lhs"
407407

408408
sourcePackage = SourcePackage
409-
{ packageInfoId = pkgId
410-
, SP.packageDescription = genericPackageDescription
411-
, packageSource = LocalUnpackedPackage tmpDir
412-
, packageDescrOverride = Nothing
409+
{ srcpkgDescription = genericPackageDescription
410+
, srcpkgSource = LocalUnpackedPackage tmpDir
411+
, srcpkgDescrOverride = Nothing
413412
}
414413
genericPackageDescription = emptyGenericPackageDescription
415414
{ GPD.packageDescription = packageDescription

cabal-install/Distribution/Client/CmdSdist.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -228,7 +228,7 @@ data OutputFormat = SourceList Char
228228
packageToSdist :: Verbosity -> FilePath -> OutputFormat -> FilePath -> UnresolvedSourcePackage -> IO ()
229229
packageToSdist verbosity projectRootDir format outputFile pkg = do
230230
let death = die' verbosity ("The impossible happened: a local package isn't local" <> (show pkg))
231-
dir0 <- case packageSource pkg of
231+
dir0 <- case srcpkgSource pkg of
232232
LocalUnpackedPackage path -> pure (Right path)
233233
RemoteSourceRepoPackage _ (Just path) -> pure (Right path)
234234
RemoteSourceRepoPackage {} -> death
@@ -256,7 +256,7 @@ packageToSdist verbosity projectRootDir format outputFile pkg = do
256256
_ -> die' verbosity ("cannot convert tarball package to " ++ show format)
257257

258258
Right dir -> do
259-
files' <- listPackageSources verbosity dir (flattenPackageDescription $ packageDescription pkg) knownSuffixHandlers
259+
files' <- listPackageSources verbosity dir (flattenPackageDescription $ srcpkgDescription pkg) knownSuffixHandlers
260260
let files = nub $ sort $ map normalise files'
261261

262262
case format of

cabal-install/Distribution/Client/Configure.hs

Lines changed: 6 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -140,7 +140,7 @@ configure verbosity packageDBs repoCtxt comp platform progdb
140140
let installPlan = InstallPlan.configureInstallPlan configFlags installPlan0
141141
in case fst (InstallPlan.ready installPlan) of
142142
[pkg@(ReadyPackage
143-
(ConfiguredPackage _ (SourcePackage _ _ (LocalUnpackedPackage _) _)
143+
(ConfiguredPackage _ (SourcePackage _ (LocalUnpackedPackage _) _)
144144
_ _ _))] -> do
145145
configurePackage verbosity
146146
platform (compilerInfo comp)
@@ -238,7 +238,7 @@ configureSetupScript packageDBs
238238
maybeSetupBuildInfo :: Maybe PkgDesc.SetupBuildInfo
239239
maybeSetupBuildInfo = do
240240
ReadyPackage cpkg <- mpkg
241-
let gpkg = packageDescription (confPkgSource cpkg)
241+
let gpkg = srcpkgDescription (confPkgSource cpkg)
242242
PkgDesc.setupBuildInfo (PkgDesc.packageDescription gpkg)
243243

244244
-- Was a default 'custom-setup' stanza added by 'cabal-install' itself? If
@@ -305,10 +305,9 @@ planLocalPackage verbosity comp platform configFlags configExFlags
305305

306306
let -- We create a local package and ask to resolve a dependency on it
307307
localPkg = SourcePackage {
308-
packageInfoId = packageId pkg,
309-
packageDescription = pkg,
310-
packageSource = LocalUnpackedPackage ".",
311-
packageDescrOverride = Nothing
308+
srcpkgDescription = pkg,
309+
srcpkgSource = LocalUnpackedPackage ".",
310+
srcpkgDescrOverride = Nothing
312311
}
313312

314313
testsEnabled = fromFlagOrDefault False $ configTests configFlags
@@ -392,7 +391,7 @@ configurePackage verbosity platform comp scriptOptions configFlags
392391
scriptOptions (Just pkg) configureCommand configureFlags (const extraArgs)
393392

394393
where
395-
gpkg = packageDescription spkg
394+
gpkg = srcpkgDescription spkg
396395
configureFlags = filterConfigureFlags configFlags {
397396
configIPID = if isJust (flagToMaybe (configIPID configFlags))
398397
-- Make sure cabal configure --ipid works.

cabal-install/Distribution/Client/Dependency.hs

Lines changed: 8 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -466,9 +466,8 @@ removeBounds relKind relDeps params =
466466
sourcePkgIndex' = fmap relaxDeps $ depResolverSourcePkgIndex params
467467

468468
relaxDeps :: UnresolvedSourcePackage -> UnresolvedSourcePackage
469-
relaxDeps srcPkg = srcPkg {
470-
packageDescription = relaxPackageDeps relKind relDeps
471-
(packageDescription srcPkg)
469+
relaxDeps srcPkg = srcPkg
470+
{ srcpkgDescription = relaxPackageDeps relKind relDeps (srcpkgDescription srcPkg)
472471
}
473472

474473
-- | Relax the dependencies of this package if needed.
@@ -543,7 +542,7 @@ addDefaultSetupDependencies defaultSetupDeps params =
543542
applyDefaultSetupDeps :: UnresolvedSourcePackage -> UnresolvedSourcePackage
544543
applyDefaultSetupDeps srcpkg =
545544
srcpkg {
546-
packageDescription = gpkgdesc {
545+
srcpkgDescription = gpkgdesc {
547546
PD.packageDescription = pkgdesc {
548547
PD.setupBuildInfo =
549548
case PD.setupBuildInfo pkgdesc of
@@ -560,7 +559,7 @@ addDefaultSetupDependencies defaultSetupDeps params =
560559
}
561560
where
562561
isCustom = PD.buildType pkgdesc == PD.Custom
563-
gpkgdesc = packageDescription srcpkg
562+
gpkgdesc = srcpkgDescription srcpkg
564563
pkgdesc = PD.packageDescription gpkgdesc
565564

566565
-- | If a package has a custom setup then we need to add a setup-depends
@@ -656,7 +655,7 @@ standardInstallPolicy installedPkgIndex sourcePkgDb pkgSpecifiers
656655
Just [Dependency (mkPackageName "Cabal") (orLaterVersion $ mkVersion [1,24]) mainLibSet]
657656
| otherwise = Nothing
658657
where
659-
gpkgdesc = packageDescription srcpkg
658+
gpkgdesc = srcpkgDescription srcpkg
660659
pkgdesc = PD.packageDescription gpkgdesc
661660
bt = PD.buildType pkgdesc
662661
affected = bt == PD.Custom && hasBuildableFalse gpkgdesc
@@ -902,7 +901,7 @@ configuredPackageProblems platform cinfo
902901
, not (packageSatisfiesDependency pkgid dep) ]
903902
-- TODO: sanity tests on executable deps
904903
where
905-
thisPkgName = packageName (packageDescription pkg)
904+
thisPkgName = packageName (srcpkgDescription pkg)
906905

907906
specifiedDeps1 :: ComponentDeps [PackageId]
908907
specifiedDeps1 = fmap (map solverSrcId) specifiedDeps0
@@ -911,7 +910,7 @@ configuredPackageProblems platform cinfo
911910
specifiedDeps = CD.flatDeps specifiedDeps1
912911

913912
mergedFlags = mergeBy compare
914-
(sort $ map PD.flagName (PD.genPackageFlags (packageDescription pkg)))
913+
(sort $ map PD.flagName (PD.genPackageFlags (srcpkgDescription pkg)))
915914
(sort $ map fst (PD.unFlagAssignment specifiedFlags)) -- TODO
916915

917916
packageSatisfiesDependency
@@ -948,7 +947,7 @@ configuredPackageProblems platform cinfo
948947
(const True)
949948
platform cinfo
950949
[]
951-
(packageDescription pkg) of
950+
(srcpkgDescription pkg) of
952951
Right (resolvedPkg, _) ->
953952
-- we filter self/internal dependencies. They are still there.
954953
-- This is INCORRECT.

cabal-install/Distribution/Client/Fetch.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -95,7 +95,7 @@ fetch verbosity packageDBs repoCtxt comp platform progdb
9595
verbosity comp platform fetchFlags
9696
installedPkgIndex sourcePkgDb pkgConfigDb pkgSpecifiers
9797

98-
pkgs' <- filterM (fmap not . isFetched . packageSource) pkgs
98+
pkgs' <- filterM (fmap not . isFetched . srcpkgSource) pkgs
9999
if null pkgs'
100100
--TODO: when we add support for remote tarballs then this message
101101
-- will need to be changed because for remote tarballs we fetch them
@@ -108,7 +108,7 @@ fetch verbosity packageDBs repoCtxt comp platform progdb
108108
"The following packages would be fetched:"
109109
: map (prettyShow . packageId) pkgs'
110110

111-
else traverse_ (fetchPackage verbosity repoCtxt . packageSource) pkgs'
111+
else traverse_ (fetchPackage verbosity repoCtxt . srcpkgSource) pkgs'
112112

113113
where
114114
dryRun = fromFlag (fetchDryRun fetchFlags)

cabal-install/Distribution/Client/Get.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -114,15 +114,15 @@ get verbosity repoCtxt globalFlags getFlags userTargets = do
114114
packageSourceRepos :: SourcePackage loc -> [PD.SourceRepo]
115115
packageSourceRepos = PD.sourceRepos
116116
. PD.packageDescription
117-
. packageDescription
117+
. srcpkgDescription
118118

119119
unpack :: [UnresolvedSourcePackage] -> IO ()
120120
unpack pkgs = do
121121
for_ pkgs $ \pkg -> do
122-
location <- fetchPackage verbosity repoCtxt (packageSource pkg)
122+
location <- fetchPackage verbosity repoCtxt (srcpkgSource pkg)
123123
let pkgid = packageId pkg
124124
descOverride | usePristine = Nothing
125-
| otherwise = packageDescrOverride pkg
125+
| otherwise = srcpkgDescrOverride pkg
126126
case location of
127127
LocalTarballPackage tarballPath ->
128128
unpackPackage verbosity prefix pkgid descOverride tarballPath

cabal-install/Distribution/Client/IndexUtils.hs

Lines changed: 7 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -364,19 +364,18 @@ readRepoIndex verbosity repoCtxt repo idxState =
364364
idxState
365365

366366
where
367-
mkAvailablePackage pkgEntry =
368-
SourcePackage {
369-
packageInfoId = pkgid,
370-
packageDescription = packageDesc pkgEntry,
371-
packageSource = case pkgEntry of
367+
mkAvailablePackage pkgEntry = SourcePackage
368+
{ srcpkgDescription = pkgdesc
369+
, srcpkgSource = case pkgEntry of
372370
NormalPackage _ _ _ _ -> RepoTarballPackage repo pkgid Nothing
373-
BuildTreeRef _ _ _ path _ -> LocalUnpackedPackage path,
374-
packageDescrOverride = case pkgEntry of
371+
BuildTreeRef _ _ _ path _ -> LocalUnpackedPackage path
372+
, srcpkgDescrOverride = case pkgEntry of
375373
NormalPackage _ _ pkgtxt _ -> Just pkgtxt
376374
_ -> Nothing
377375
}
378376
where
379-
pkgid = packageId pkgEntry
377+
pkgdesc = packageDesc pkgEntry
378+
pkgid = packageId pkgdesc
380379

381380
handleNotFound action = catchIO action $ \e -> if isDoesNotExistError e
382381
then do

cabal-install/Distribution/Client/Init/Heuristics.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ import Language.Haskell.Extension ( Extension )
3737
import Distribution.Solver.Types.PackageIndex
3838
( allPackagesByName )
3939
import Distribution.Solver.Types.SourcePackage
40-
( packageDescription )
40+
( srcpkgDescription )
4141

4242
import Distribution.Client.Types ( SourcePackageDb(..) )
4343
import Data.Char ( isLower )
@@ -344,7 +344,7 @@ maybeReadFile f = do
344344
knownCategories :: SourcePackageDb -> [String]
345345
knownCategories (SourcePackageDb sourcePkgIndex _) = nubSet
346346
[ cat | pkg <- maybeToList . safeHead =<< (allPackagesByName sourcePkgIndex)
347-
, let catList = (PD.category . PD.packageDescription . packageDescription) pkg
347+
, let catList = (PD.category . PD.packageDescription . srcpkgDescription) pkg
348348
, cat <- splitString ',' $ ShortText.fromShortText catList
349349
]
350350

cabal-install/Distribution/Client/Install.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -572,8 +572,8 @@ checkPrintPlan verbosity installed installPlan sourcePkgDb
572572
when offline $ do
573573
let pkgs = [ confPkgSource cpkg
574574
| InstallPlan.Configured cpkg <- InstallPlan.toList installPlan ]
575-
notFetched <- fmap (map packageInfoId)
576-
. filterM (fmap isNothing . checkFetched . packageSource)
575+
notFetched <- fmap (map packageId)
576+
. filterM (fmap isNothing . checkFetched . srcpkgSource)
577577
$ pkgs
578578
unless (null notFetched) $
579579
die' verbosity $ "Can't download packages in offline mode. "
@@ -692,7 +692,7 @@ printPlan dryRun verbosity plan sourcePkgDb = case plan of
692692
nonDefaultFlags cpkg =
693693
let defaultAssignment =
694694
toFlagAssignment
695-
(genPackageFlags (SourcePackage.packageDescription $
695+
(genPackageFlags (SourcePackage.srcpkgDescription $
696696
confPkgSource cpkg))
697697
in confPkgFlags cpkg `diffFlagAssignment` defaultAssignment
698698

@@ -1189,7 +1189,7 @@ installReadyPackage :: Platform -> CompilerInfo
11891189
-> a
11901190
installReadyPackage platform cinfo configFlags
11911191
(ReadyPackage (ConfiguredPackage ipid
1192-
(SourcePackage _ gpkg source pkgoverride)
1192+
(SourcePackage gpkg source pkgoverride)
11931193
flags stanzas deps))
11941194
installPkg =
11951195
installPkg configFlags {

cabal-install/Distribution/Client/InstallSymlink.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -134,11 +134,11 @@ symlinkBinaries platform comp overwritePolicy
134134
, exe <- PackageDescription.executables pkg
135135
, PackageDescription.buildable (PackageDescription.buildInfo exe) ]
136136

137-
pkgDescription (ConfiguredPackage _ (SourcePackage _ pkg _ _)
137+
pkgDescription (ConfiguredPackage _ (SourcePackage gpd _ _)
138138
flags stanzas _) =
139139
case finalizePD flags (enableStanzas stanzas)
140140
(const True)
141-
platform cinfo [] pkg of
141+
platform cinfo [] gpd of
142142
Left _ -> error "finalizePD ReadyPackage failed"
143143
Right (desc, _) -> desc
144144

cabal-install/Distribution/Client/List.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -507,7 +507,7 @@ mergePackageInfo versionPref installedPkgs sourcePkgs selectedPkg showVer =
507507
sourceSelected
508508
| isJust selectedPkg = selectedPkg
509509
| otherwise = latestWithPref versionPref sourcePkgs
510-
sourceGeneric = fmap packageDescription sourceSelected
510+
sourceGeneric = fmap srcpkgDescription sourceSelected
511511
source = fmap flattenPackageDescription sourceGeneric
512512

513513
uncons :: b -> (a -> b) -> [a] -> b
@@ -521,7 +521,7 @@ mergePackageInfo versionPref installedPkgs sourcePkgs selectedPkg showVer =
521521
--
522522
updateFileSystemPackageDetails :: PackageDisplayInfo -> IO PackageDisplayInfo
523523
updateFileSystemPackageDetails pkginfo = do
524-
fetched <- maybe (return False) (isFetched . packageSource)
524+
fetched <- maybe (return False) (isFetched . srcpkgSource)
525525
(selectedSourcePkg pkginfo)
526526
docsExist <- doesDirectoryExist (haddockHtml pkginfo)
527527
return pkginfo {

cabal-install/Distribution/Client/ProjectConfig.hs

Lines changed: 7 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -88,7 +88,7 @@ import Distribution.Solver.Types.PackageConstraint
8888
( PackageProperty(..) )
8989

9090
import Distribution.Package
91-
( PackageName, PackageId, packageId, UnitId )
91+
( PackageName, PackageId, UnitId )
9292
import Distribution.Types.PackageVersionConstraint
9393
( PackageVersionConstraint(..) )
9494
import Distribution.System
@@ -1234,13 +1234,12 @@ mkSpecificSourcePackage :: PackageLocation FilePath
12341234
-> PackageSpecifier
12351235
(SourcePackage (PackageLocation (Maybe FilePath)))
12361236
mkSpecificSourcePackage location pkg =
1237-
SpecificSourcePackage SourcePackage {
1238-
packageInfoId = packageId pkg,
1239-
packageDescription = pkg,
1240-
--TODO: it is silly that we still have to use a Maybe FilePath here
1241-
packageSource = fmap Just location,
1242-
packageDescrOverride = Nothing
1243-
}
1237+
SpecificSourcePackage SourcePackage
1238+
{ srcpkgDescription = pkg
1239+
--TODO: it is silly that we still have to use a Maybe FilePath here
1240+
, srcpkgSource = fmap Just location
1241+
, srcpkgDescrOverride = Nothing
1242+
}
12441243

12451244

12461245
-- | Errors reported upon failing to parse a @.cabal@ file.

0 commit comments

Comments
 (0)