Skip to content

Commit 1a8b93c

Browse files
authored
Merge pull request haskell#9618 from alt-romes/abi-tag-in-store-path
Include the GHC "Project Unit Id" in the cabal store path
2 parents 9712115 + dd19cfa commit 1a8b93c

File tree

12 files changed

+181
-135
lines changed

12 files changed

+181
-135
lines changed

Cabal/src/Distribution/Simple/GHC.hs

Lines changed: 10 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,7 @@
11
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE FlexibleContexts #-}
33
{-# LANGUAGE MultiWayIf #-}
4+
{-# LANGUAGE NamedFieldPuns #-}
45
{-# LANGUAGE RankNTypes #-}
56
{-# LANGUAGE TupleSections #-}
67

@@ -82,6 +83,7 @@ import Distribution.Compat.Prelude
8283
import Prelude ()
8384

8485
import Control.Monad (forM_)
86+
import Data.List (stripPrefix)
8587
import qualified Data.Map as Map
8688
import Distribution.CabalSpecVersion
8789
import Distribution.InstalledPackageInfo (InstalledPackageInfo)
@@ -236,10 +238,16 @@ configure verbosity hcPath hcPkgPath conf0 = do
236238

237239
filterExt ext = filter ((/= EnableExtension ext) . fst)
238240

241+
compilerId :: CompilerId
242+
compilerId = CompilerId GHC ghcVersion
243+
244+
compilerAbiTag :: AbiTag
245+
compilerAbiTag = maybe NoAbiTag AbiTag (Map.lookup "Project Unit Id" ghcInfoMap >>= stripPrefix (prettyShow compilerId <> "-"))
246+
239247
let comp =
240248
Compiler
241-
{ compilerId = CompilerId GHC ghcVersion
242-
, compilerAbiTag = NoAbiTag
249+
{ compilerId
250+
, compilerAbiTag
243251
, compilerCompat = []
244252
, compilerLanguages = languages
245253
, compilerExtensions = extensions

cabal-install/src/Distribution/Client/CmdHaddockProject.hs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -54,9 +54,6 @@ import Distribution.Client.TargetProblem (TargetProblem (..))
5454
import Distribution.Simple.Command
5555
( CommandUI (..)
5656
)
57-
import Distribution.Simple.Compiler
58-
( Compiler (..)
59-
)
6057
import Distribution.Simple.Flag
6158
( Flag (..)
6259
, fromFlag
@@ -319,7 +316,7 @@ haddockProjectAction flags _extraArgs globalFlags = do
319316
packageDir =
320317
storePackageDirectory
321318
(cabalStoreDirLayout cabalLayout)
322-
(compilerId (pkgConfigCompiler sharedConfig'))
319+
(pkgConfigCompiler sharedConfig')
323320
(elabUnitId package)
324321
docDir = packageDir </> "share" </> "doc" </> "html"
325322
destDir = outputDir </> packageName

cabal-install/src/Distribution/Client/CmdInstall.hs

Lines changed: 6 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -517,8 +517,7 @@ installAction flags@NixStyleFlags{extraFlags = clientInstallFlags', ..} targetSt
517517

518518
-- progDb is a program database with compiler tools configured properly
519519
( compiler@Compiler
520-
{ compilerId =
521-
compilerId@(CompilerId compilerFlavor compilerVersion)
520+
{ compilerId = CompilerId compilerFlavor compilerVersion
522521
}
523522
, platform
524523
, progDb
@@ -531,7 +530,7 @@ installAction flags@NixStyleFlags{extraFlags = clientInstallFlags', ..} targetSt
531530
envFile <- getEnvFile clientInstallFlags platform compilerVersion
532531
existingEnvEntries <-
533532
getExistingEnvEntries verbosity compilerFlavor supportsPkgEnvFiles envFile
534-
packageDbs <- getPackageDbStack compilerId projectConfigStoreDir projectConfigLogsDir
533+
packageDbs <- getPackageDbStack compiler projectConfigStoreDir projectConfigLogsDir
535534
installedIndex <- getInstalledPackages verbosity compiler packageDbs progDb
536535

537536
let
@@ -840,7 +839,7 @@ prepareExeInstall
840839
mkUnitBinDir :: UnitId -> FilePath
841840
mkUnitBinDir =
842841
InstallDirs.bindir
843-
. storePackageInstallDirs' storeDirLayout (compilerId compiler)
842+
. storePackageInstallDirs' storeDirLayout compiler
844843

845844
mkExeName :: UnqualComponentName -> FilePath
846845
mkExeName exe = unUnqualComponentName exe <.> exeExtension platform
@@ -1212,16 +1211,16 @@ getLocalEnv dir platform compilerVersion =
12121211
<> ghcPlatformAndVersionString platform compilerVersion
12131212

12141213
getPackageDbStack
1215-
:: CompilerId
1214+
:: Compiler
12161215
-> Flag FilePath
12171216
-> Flag FilePath
12181217
-> IO PackageDBStack
1219-
getPackageDbStack compilerId storeDirFlag logsDirFlag = do
1218+
getPackageDbStack compiler storeDirFlag logsDirFlag = do
12201219
mstoreDir <- traverse makeAbsolute $ flagToMaybe storeDirFlag
12211220
let
12221221
mlogsDir = flagToMaybe logsDirFlag
12231222
cabalLayout <- mkCabalDirLayout mstoreDir mlogsDir
1224-
pure $ storePackageDBStack (cabalStoreDirLayout cabalLayout) compilerId
1223+
pure $ storePackageDBStack (cabalStoreDirLayout cabalLayout) compiler
12251224

12261225
-- | This defines what a 'TargetSelector' means for the @bench@ command.
12271226
-- It selects the 'AvailableTarget's that the 'TargetSelector' refers to,

cabal-install/src/Distribution/Client/DistDirLayout.hs

Lines changed: 38 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,8 @@ import Distribution.Package
4141
, UnitId
4242
)
4343
import Distribution.Simple.Compiler
44-
( OptimisationLevel (..)
44+
( Compiler (..)
45+
, OptimisationLevel (..)
4546
, PackageDB (..)
4647
, PackageDBStack
4748
)
@@ -116,13 +117,13 @@ data DistDirLayout = DistDirLayout
116117

117118
-- | The layout of a cabal nix-style store.
118119
data StoreDirLayout = StoreDirLayout
119-
{ storeDirectory :: CompilerId -> FilePath
120-
, storePackageDirectory :: CompilerId -> UnitId -> FilePath
121-
, storePackageDBPath :: CompilerId -> FilePath
122-
, storePackageDB :: CompilerId -> PackageDB
123-
, storePackageDBStack :: CompilerId -> PackageDBStack
124-
, storeIncomingDirectory :: CompilerId -> FilePath
125-
, storeIncomingLock :: CompilerId -> UnitId -> FilePath
120+
{ storeDirectory :: Compiler -> FilePath
121+
, storePackageDirectory :: Compiler -> UnitId -> FilePath
122+
, storePackageDBPath :: Compiler -> FilePath
123+
, storePackageDB :: Compiler -> PackageDB
124+
, storePackageDBStack :: Compiler -> PackageDBStack
125+
, storeIncomingDirectory :: Compiler -> FilePath
126+
, storeIncomingLock :: Compiler -> UnitId -> FilePath
126127
}
127128

128129
-- TODO: move to another module, e.g. CabalDirLayout?
@@ -267,33 +268,35 @@ defaultStoreDirLayout :: FilePath -> StoreDirLayout
267268
defaultStoreDirLayout storeRoot =
268269
StoreDirLayout{..}
269270
where
270-
storeDirectory :: CompilerId -> FilePath
271-
storeDirectory compid =
272-
storeRoot </> prettyShow compid
273-
274-
storePackageDirectory :: CompilerId -> UnitId -> FilePath
275-
storePackageDirectory compid ipkgid =
276-
storeDirectory compid </> prettyShow ipkgid
277-
278-
storePackageDBPath :: CompilerId -> FilePath
279-
storePackageDBPath compid =
280-
storeDirectory compid </> "package.db"
281-
282-
storePackageDB :: CompilerId -> PackageDB
283-
storePackageDB compid =
284-
SpecificPackageDB (storePackageDBPath compid)
285-
286-
storePackageDBStack :: CompilerId -> PackageDBStack
287-
storePackageDBStack compid =
288-
[GlobalPackageDB, storePackageDB compid]
289-
290-
storeIncomingDirectory :: CompilerId -> FilePath
291-
storeIncomingDirectory compid =
292-
storeDirectory compid </> "incoming"
293-
294-
storeIncomingLock :: CompilerId -> UnitId -> FilePath
295-
storeIncomingLock compid unitid =
296-
storeIncomingDirectory compid </> prettyShow unitid <.> "lock"
271+
storeDirectory :: Compiler -> FilePath
272+
storeDirectory compiler =
273+
storeRoot </> case compilerAbiTag compiler of
274+
NoAbiTag -> prettyShow (compilerId compiler)
275+
AbiTag tag -> prettyShow (compilerId compiler) <> "-" <> tag
276+
277+
storePackageDirectory :: Compiler -> UnitId -> FilePath
278+
storePackageDirectory compiler ipkgid =
279+
storeDirectory compiler </> prettyShow ipkgid
280+
281+
storePackageDBPath :: Compiler -> FilePath
282+
storePackageDBPath compiler =
283+
storeDirectory compiler </> "package.db"
284+
285+
storePackageDB :: Compiler -> PackageDB
286+
storePackageDB compiler =
287+
SpecificPackageDB (storePackageDBPath compiler)
288+
289+
storePackageDBStack :: Compiler -> PackageDBStack
290+
storePackageDBStack compiler =
291+
[GlobalPackageDB, storePackageDB compiler]
292+
293+
storeIncomingDirectory :: Compiler -> FilePath
294+
storeIncomingDirectory compiler =
295+
storeDirectory compiler </> "incoming"
296+
297+
storeIncomingLock :: Compiler -> UnitId -> FilePath
298+
storeIncomingLock compiler unitid =
299+
storeIncomingDirectory compiler </> prettyShow unitid <.> "lock"
297300

298301
defaultCabalDirLayout :: IO CabalDirLayout
299302
defaultCabalDirLayout =

cabal-install/src/Distribution/Client/PackageHash.hs

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,8 @@
1010
-- * the package tarball
1111
-- * the ids of all the direct dependencies
1212
-- * other local configuration (flags, profiling, etc)
13+
--
14+
-- See 'PackageHashInputs' for a detailed list of what determines the hash.
1315
module Distribution.Client.PackageHash
1416
( -- * Calculating package hashes
1517
PackageHashInputs (..)
@@ -38,7 +40,8 @@ import Distribution.Package
3840
, mkComponentId
3941
)
4042
import Distribution.Simple.Compiler
41-
( CompilerId
43+
( AbiTag (..)
44+
, CompilerId
4245
, DebugInfoLevel (..)
4346
, OptimisationLevel (..)
4447
, PackageDB
@@ -191,6 +194,7 @@ type PackageSourceHash = HashValue
191194
-- package hash.
192195
data PackageHashConfigInputs = PackageHashConfigInputs
193196
{ pkgHashCompilerId :: CompilerId
197+
, pkgHashCompilerABI :: AbiTag
194198
, pkgHashPlatform :: Platform
195199
, pkgHashFlagAssignment :: FlagAssignment -- complete not partial
196200
, pkgHashConfigureScriptArgs :: [String] -- just ./configure for build-type Configure
@@ -301,6 +305,7 @@ renderPackageHashInputs
301305
pkgHashDirectDeps
302306
, -- and then all the config
303307
entry "compilerid" prettyShow pkgHashCompilerId
308+
, entry "compilerabi" prettyShow pkgHashCompilerABI
304309
, entry "platform" prettyShow pkgHashPlatform
305310
, opt "flags" mempty showFlagAssignment pkgHashFlagAssignment
306311
, opt "configure-script" [] unwords pkgHashConfigureScriptArgs

cabal-install/src/Distribution/Client/ProjectBuilding/UnpackedPackage.hs

Lines changed: 3 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -71,7 +71,6 @@ import Distribution.Simple.BuildPaths (haddockDirName)
7171
import Distribution.Simple.Command (CommandUI)
7272
import Distribution.Simple.Compiler
7373
( PackageDBStack
74-
, compilerId
7574
)
7675
import qualified Distribution.Simple.InstallDirs as InstallDirs
7776
import Distribution.Simple.LocalBuildInfo
@@ -681,12 +680,12 @@ buildAndInstallUnpackedPackage
681680
| otherwise = do
682681
assert
683682
( elabRegisterPackageDBStack pkg
684-
== storePackageDBStack compid
683+
== storePackageDBStack compiler
685684
)
686685
(return ())
687686
_ <-
688687
runRegister
689-
(storePackageDBStack compid)
688+
(storePackageDBStack compiler)
690689
Cabal.defaultRegisterOptions
691690
{ Cabal.registerMultiInstance = True
692691
, Cabal.registerSuppressFilesCheck = True
@@ -698,7 +697,7 @@ buildAndInstallUnpackedPackage
698697
newStoreEntry
699698
verbosity
700699
storeDirLayout
701-
compid
700+
compiler
702701
uid
703702
(copyPkgFiles verbosity pkgshared pkg runCopy)
704703
registerPkg
@@ -735,7 +734,6 @@ buildAndInstallUnpackedPackage
735734
where
736735
uid = installedUnitId rpkg
737736
pkgid = packageId rpkg
738-
compid = compilerId compiler
739737

740738
dispname :: String
741739
dispname = case elabPkgOrComp pkg of

cabal-install/src/Distribution/Client/ProjectPlanning.hs

Lines changed: 12 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -854,7 +854,7 @@ rebuildInstallPlan
854854
-> Rebuild ElaboratedInstallPlan
855855
phaseImprovePlan elaboratedPlan elaboratedShared = do
856856
liftIO $ debug verbosity "Improving the install plan..."
857-
storePkgIdSet <- getStoreEntries cabalStoreDirLayout compid
857+
storePkgIdSet <- getStoreEntries cabalStoreDirLayout compiler
858858
let improvedPlan =
859859
improveInstallPlanWithInstalledPackages
860860
storePkgIdSet
@@ -866,7 +866,7 @@ rebuildInstallPlan
866866
-- matches up as expected, e.g. no dangling deps, files deleted.
867867
return improvedPlan
868868
where
869-
compid = compilerId (pkgConfigCompiler elaboratedShared)
869+
compiler = pkgConfigCompiler elaboratedShared
870870

871871
-- | If a 'PackageSpecifier' refers to a single package, return Just that
872872
-- package.
@@ -2319,7 +2319,7 @@ elaborateInstallPlan
23192319

23202320
corePackageDbs =
23212321
applyPackageDbFlags
2322-
(storePackageDBStack (compilerId compiler))
2322+
(storePackageDBStack compiler)
23232323
(projectConfigPackageDBs sharedPackageConfig)
23242324

23252325
-- For this local build policy, every package that lives in a local source
@@ -3768,28 +3768,28 @@ userInstallDirTemplates compiler = do
37683768

37693769
storePackageInstallDirs
37703770
:: StoreDirLayout
3771-
-> CompilerId
3771+
-> Compiler
37723772
-> InstalledPackageId
37733773
-> InstallDirs.InstallDirs FilePath
3774-
storePackageInstallDirs storeDirLayout compid ipkgid =
3775-
storePackageInstallDirs' storeDirLayout compid $ newSimpleUnitId ipkgid
3774+
storePackageInstallDirs storeDirLayout compiler ipkgid =
3775+
storePackageInstallDirs' storeDirLayout compiler $ newSimpleUnitId ipkgid
37763776

37773777
storePackageInstallDirs'
37783778
:: StoreDirLayout
3779-
-> CompilerId
3779+
-> Compiler
37803780
-> UnitId
37813781
-> InstallDirs.InstallDirs FilePath
37823782
storePackageInstallDirs'
37833783
StoreDirLayout
37843784
{ storePackageDirectory
37853785
, storeDirectory
37863786
}
3787-
compid
3787+
compiler
37883788
unitid =
37893789
InstallDirs.InstallDirs{..}
37903790
where
3791-
store = storeDirectory compid
3792-
prefix = storePackageDirectory compid unitid
3791+
store = storeDirectory compiler
3792+
prefix = storePackageDirectory compiler unitid
37933793
bindir = prefix </> "bin"
37943794
libdir = prefix </> "lib"
37953795
libsubdir = ""
@@ -3839,7 +3839,7 @@ computeInstallDirs storeDirLayout defaultInstallDirs elaboratedShared elab
38393839
-- use special simplified install dirs
38403840
storePackageInstallDirs'
38413841
storeDirLayout
3842-
(compilerId (pkgConfigCompiler elaboratedShared))
3842+
(pkgConfigCompiler elaboratedShared)
38433843
(elabUnitId elab)
38443844

38453845
-- TODO: [code cleanup] perhaps reorder this code
@@ -4303,6 +4303,7 @@ packageHashConfigInputs
43034303
packageHashConfigInputs shared@ElaboratedSharedConfig{..} pkg =
43044304
PackageHashConfigInputs
43054305
{ pkgHashCompilerId = compilerId pkgConfigCompiler
4306+
, pkgHashCompilerABI = compilerAbiTag pkgConfigCompiler
43064307
, pkgHashPlatform = pkgConfigPlatform
43074308
, pkgHashFlagAssignment = elabFlagAssignment
43084309
, pkgHashConfigureScriptArgs = elabConfigureScriptArgs

0 commit comments

Comments
 (0)