Skip to content

Commit d19bba9

Browse files
committed
Change dist-newstyle layout from build/pid to build/ipkgid.
Sorry, all you folks who have finger-macroed dist-newstyle/build/pkg-1.0; the format will now be dist-newstyle/build/pkg-1.0-inplace (or perhaps even further mangled.) Although "inplace" is seemingly redundant, it won't be when we build components individually (build/pkg-1.0-inplace-exename) where each component needs a separate dist-directory. If we change our inplace identifiers to be more detailed (see haskell#3343) then it permits inplace builds to handle all situations where package identifiers do not sufficiently disambiguate. Signed-off-by: Edward Z. Yang <[email protected]>
1 parent 535c8bb commit d19bba9

File tree

2 files changed

+30
-27
lines changed

2 files changed

+30
-27
lines changed

cabal-install/Distribution/Client/DistDirLayout.hs

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ module Distribution.Client.DistDirLayout where
99

1010
import System.FilePath
1111
import Distribution.Package
12-
( PackageId )
12+
( PackageId, UnitId )
1313
import Distribution.Compiler
1414
import Distribution.Simple.Compiler (PackageDB(..))
1515
import Distribution.Text
@@ -31,11 +31,11 @@ data DistDirLayout = DistDirLayout {
3131
-- | The directory under dist where we keep the build artifacts for a
3232
-- package we're building from a local directory.
3333
--
34-
-- This uses a 'PackageId' not just a 'PackageName' because technically
34+
-- This uses a 'UnitId' not just a 'PackageName' because technically
3535
-- we can have multiple instances of the same package in a solution
3636
-- (e.g. setup deps).
3737
--
38-
distBuildDirectory :: PackageId -> FilePath,
38+
distBuildDirectory :: UnitId -> FilePath,
3939
distBuildRootDirectory :: FilePath,
4040

4141
-- | The directory under dist where we put the unpacked sources of
@@ -55,8 +55,8 @@ data DistDirLayout = DistDirLayout {
5555
-- | The location for package-specific cache files (e.g. state used in
5656
-- incremental rebuilds).
5757
--
58-
distPackageCacheFile :: PackageId -> String -> FilePath,
59-
distPackageCacheDirectory :: PackageId -> FilePath,
58+
distPackageCacheFile :: UnitId -> String -> FilePath,
59+
distPackageCacheDirectory :: UnitId -> FilePath,
6060

6161
distTempDirectory :: FilePath,
6262
distBinDirectory :: FilePath,
@@ -88,7 +88,7 @@ defaultDistDirLayout projectRootDirectory =
8888
--TODO: switch to just dist at some point, or some other new name
8989

9090
distBuildRootDirectory = distDirectory </> "build"
91-
distBuildDirectory pkgid = distBuildRootDirectory </> display pkgid
91+
distBuildDirectory uid = distBuildRootDirectory </> display uid
9292

9393
distUnpackedSrcRootDirectory = distDirectory </> "src"
9494
distUnpackedSrcDirectory pkgid = distUnpackedSrcRootDirectory
@@ -97,8 +97,8 @@ defaultDistDirLayout projectRootDirectory =
9797
distProjectCacheDirectory = distDirectory </> "cache"
9898
distProjectCacheFile name = distProjectCacheDirectory </> name
9999

100-
distPackageCacheDirectory pkgid = distBuildDirectory pkgid </> "cache"
101-
distPackageCacheFile pkgid name = distPackageCacheDirectory pkgid </> name
100+
distPackageCacheDirectory uid = distBuildDirectory uid </> "cache"
101+
distPackageCacheFile uid name = distPackageCacheDirectory uid </> name
102102

103103
distTempDirectory = distDirectory </> "tmp"
104104

cabal-install/Distribution/Client/ProjectBuilding.hs

Lines changed: 22 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -303,7 +303,7 @@ rebuildTargetsDryRun distDirLayout@DistDirLayout{..} = \installPlan -> do
303303
return (BuildStatusUpToDate buildSuccess)
304304
where
305305
packageFileMonitor =
306-
newPackageFileMonitor distDirLayout (packageId pkg)
306+
newPackageFileMonitor distDirLayout (installedUnitId pkg)
307307

308308

309309
-- | A specialised traversal over the packages in an install plan.
@@ -393,22 +393,22 @@ data PackageFileMonitor = PackageFileMonitor {
393393
--
394394
type BuildSuccessMisc = (DocsResult, TestsResult)
395395

396-
newPackageFileMonitor :: DistDirLayout -> PackageId -> PackageFileMonitor
397-
newPackageFileMonitor DistDirLayout{distPackageCacheFile} pkgid =
396+
newPackageFileMonitor :: DistDirLayout -> UnitId -> PackageFileMonitor
397+
newPackageFileMonitor DistDirLayout{distPackageCacheFile} ipkgid =
398398
PackageFileMonitor {
399399
pkgFileMonitorConfig =
400-
newFileMonitor (distPackageCacheFile pkgid "config"),
400+
newFileMonitor (distPackageCacheFile ipkgid "config"),
401401

402402
pkgFileMonitorBuild =
403403
FileMonitor {
404-
fileMonitorCacheFile = distPackageCacheFile pkgid "build",
404+
fileMonitorCacheFile = distPackageCacheFile ipkgid "build",
405405
fileMonitorKeyValid = \componentsToBuild componentsAlreadyBuilt ->
406406
componentsToBuild `Set.isSubsetOf` componentsAlreadyBuilt,
407407
fileMonitorCheckIfOnlyValueChanged = True
408408
},
409409

410410
pkgFileMonitorReg =
411-
newFileMonitor (distPackageCacheFile pkgid "registration")
411+
newFileMonitor (distPackageCacheFile ipkgid "registration")
412412
}
413413

414414
-- | Helper function for 'checkPackageFileMonitorChanged',
@@ -686,7 +686,7 @@ rebuildTarget verbosity
686686
unpackTarballPhase tarball =
687687
withTarballLocalDirectory
688688
verbosity distDirLayout tarball
689-
(packageId pkg) (pkgBuildStyle pkg)
689+
(packageId pkg) (installedPackageId pkg) (pkgBuildStyle pkg)
690690
(pkgDescriptionOverride pkg) $
691691

692692
case pkgBuildStyle pkg of
@@ -704,7 +704,7 @@ rebuildTarget verbosity
704704

705705
buildInplace buildStatus srcdir builddir
706706
where
707-
builddir = distBuildDirectory (packageId pkg)
707+
builddir = distBuildDirectory (installedUnitId pkg)
708708

709709
buildAndInstall srcdir builddir =
710710
buildAndInstallUnpackedPackage
@@ -790,19 +790,22 @@ downloadedSourceLocation pkgloc =
790790

791791

792792
-- | Ensure that the package is unpacked in an appropriate directory, either
793-
-- a temporary one or a persistent one under the shared dist directory.
793+
-- a temporary one or a persistent one under the shared dist directory.
794794
--
795795
withTarballLocalDirectory
796796
:: Verbosity
797797
-> DistDirLayout
798798
-> FilePath
799799
-> PackageId
800+
-> UnitId
800801
-> BuildStyle
801802
-> Maybe CabalFileText
802-
-> (FilePath -> FilePath -> IO a)
803+
-> (FilePath -> -- Source directory
804+
FilePath -> -- Build directory
805+
IO a)
803806
-> IO a
804807
withTarballLocalDirectory verbosity distDirLayout@DistDirLayout{..}
805-
tarball pkgid buildstyle pkgTextOverride
808+
tarball pkgid ipkgid buildstyle pkgTextOverride
806809
buildPkg =
807810
case buildstyle of
808811
-- In this case we make a temp dir, unpack the tarball to there and
@@ -822,15 +825,15 @@ withTarballLocalDirectory verbosity distDirLayout@DistDirLayout{..}
822825
BuildInplaceOnly -> do
823826
let srcrootdir = distUnpackedSrcRootDirectory
824827
srcdir = distUnpackedSrcDirectory pkgid
825-
builddir = distBuildDirectory pkgid
828+
builddir = distBuildDirectory ipkgid
826829
-- TODO: [nice to have] use a proper file monitor rather than this dir exists test
827830
exists <- doesDirectoryExist srcdir
828831
unless exists $ do
829832
createDirectoryIfMissingVerbose verbosity False srcrootdir
830833
unpackPackageTarball verbosity tarball srcrootdir
831834
pkgid pkgTextOverride
832835
moveTarballShippedDistDirectory verbosity distDirLayout
833-
srcrootdir pkgid
836+
srcrootdir pkgid ipkgid
834837
buildPkg srcdir builddir
835838

836839

@@ -876,9 +879,9 @@ unpackPackageTarball verbosity tarball parentdir pkgid pkgTextOverride =
876879
-- system, though we'll still need to keep this hack for older packages.
877880
--
878881
moveTarballShippedDistDirectory :: Verbosity -> DistDirLayout
879-
-> FilePath -> PackageId -> IO ()
882+
-> FilePath -> PackageId -> UnitId -> IO ()
880883
moveTarballShippedDistDirectory verbosity DistDirLayout{distBuildDirectory}
881-
parentdir pkgid = do
884+
parentdir pkgid uid = do
882885
distDirExists <- doesDirectoryExist tarballDistDir
883886
when distDirExists $ do
884887
debug verbosity $ "Moving '" ++ tarballDistDir ++ "' to '"
@@ -887,7 +890,7 @@ moveTarballShippedDistDirectory verbosity DistDirLayout{distBuildDirectory}
887890
renameDirectory tarballDistDir targetDistDir
888891
where
889892
tarballDistDir = parentdir </> display pkgid </> "dist"
890-
targetDistDir = distBuildDirectory pkgid
893+
targetDistDir = distBuildDirectory uid
891894

892895

893896
buildAndInstallUnpackedPackage :: Verbosity
@@ -1065,8 +1068,9 @@ buildInplaceUnpackedPackage verbosity
10651068

10661069
--TODO: [code cleanup] there is duplication between the distdirlayout and the builddir here
10671070
-- builddir is not enough, we also need the per-package cachedir
1071+
let uid = installedUnitId pkg
10681072
createDirectoryIfMissingVerbose verbosity False builddir
1069-
createDirectoryIfMissingVerbose verbosity False (distPackageCacheDirectory pkgid)
1073+
createDirectoryIfMissingVerbose verbosity False (distPackageCacheDirectory uid)
10701074

10711075
-- Configure phase
10721076
--
@@ -1132,12 +1136,11 @@ buildInplaceUnpackedPackage verbosity
11321136
return (BuildOk docsResult testsResult mipkg)
11331137

11341138
where
1135-
pkgid = packageId rpkg
11361139
ipkgid = installedPackageId rpkg
11371140

11381141
isParallelBuild = buildSettingNumJobs >= 2
11391142

1140-
packageFileMonitor = newPackageFileMonitor distDirLayout pkgid
1143+
packageFileMonitor = newPackageFileMonitor distDirLayout ipkgid
11411144

11421145
whenReConfigure action = case buildStatus of
11431146
BuildStatusConfigure _ -> action

0 commit comments

Comments
 (0)