Skip to content

Commit 13e704d

Browse files
authored
Merge pull request #8623 from bairyn/fix-project-local-flags
Fix project-local flags being ignored
2 parents df6c22b + 867cbb9 commit 13e704d

File tree

12 files changed

+216
-8
lines changed

12 files changed

+216
-8
lines changed

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

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -154,6 +154,9 @@ configure verbosity packageDBs repoCtxt comp platform progdb
154154
(fromFlagOrDefault
155155
(useDistPref defaultSetupScriptOptions)
156156
(configDistPref configFlags))
157+
(fromFlagOrDefault
158+
(setupConfigDynamic defaultSetupScriptOptions)
159+
(configDynExe configFlags))
157160
(chooseCabalVersion
158161
configExFlags
159162
(flagToMaybe (configCabalVersion configExFlags)))
@@ -167,6 +170,7 @@ configureSetupScript :: PackageDBStack
167170
-> Platform
168171
-> ProgramDb
169172
-> FilePath
173+
-> Bool
170174
-> VersionRange
171175
-> Maybe Lock
172176
-> Bool
@@ -178,6 +182,7 @@ configureSetupScript packageDBs
178182
platform
179183
progdb
180184
distPref
185+
dynExe
181186
cabalVersion
182187
lock
183188
forceExternal
@@ -209,6 +214,7 @@ configureSetupScript packageDBs
209214
, useDependenciesExclusive = not defaultSetupDeps && isJust explicitSetupDeps
210215
, useVersionMacros = not defaultSetupDeps && isJust explicitSetupDeps
211216
, isInteractive = False
217+
, setupConfigDynamic = dynExe
212218
}
213219
where
214220
-- When we are compiling a legacy setup script without an explicit

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

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1059,6 +1059,7 @@ performInstallations verbosity
10591059
platform
10601060
progdb
10611061
distPref
1062+
(fromFlagOrDefault (setupConfigDynamic defaultSetupScriptOptions) $ configDynExe configFlags)
10621063
(chooseCabalVersion configExFlags (libVersion miscOptions))
10631064
(Just lock)
10641065
parallelInstall

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -272,9 +272,9 @@ encodePlanAsJson distDirLayout elaboratedInstallPlan elaboratedSharedConfig =
272272
comp2str = prettyShow
273273

274274
style2str :: Bool -> BuildStyle -> String
275+
style2str _ BuildAndInstall = "global"
275276
style2str True _ = "local"
276277
style2str False BuildInplaceOnly = "inplace"
277-
style2str False BuildAndInstall = "global"
278278

279279
jdisplay :: Pretty a => a -> J.Value
280280
jdisplay = J.String . prettyShow

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

Lines changed: 36 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -668,6 +668,7 @@ rebuildInstallPlan verbosity
668668
projectConfigAllPackages,
669669
projectConfigLocalPackages,
670670
projectConfigSpecificPackage,
671+
projectPackagesNamed,
671672
projectConfigBuildOnly
672673
}
673674
(compiler, platform, progdb) pkgConfigDB
@@ -692,6 +693,7 @@ rebuildInstallPlan verbosity
692693
localPackages
693694
sourcePackageHashes
694695
defaultInstallDirs
696+
projectPackagesNamed
695697
projectConfigShared
696698
projectConfigAllPackages
697699
projectConfigLocalPackages
@@ -1350,6 +1352,7 @@ elaborateInstallPlan
13501352
-> [PackageSpecifier (SourcePackage (PackageLocation loc))]
13511353
-> Map PackageId PackageSourceHash
13521354
-> InstallDirs.InstallDirTemplates
1355+
-> [PackageVersionConstraint]
13531356
-> ProjectConfigShared
13541357
-> PackageConfig
13551358
-> PackageConfig
@@ -1361,6 +1364,7 @@ elaborateInstallPlan verbosity platform compiler compilerprogdb pkgConfigDB
13611364
solverPlan localPackages
13621365
sourcePackageHashes
13631366
defaultInstallDirs
1367+
extraPackages
13641368
sharedPackageConfig
13651369
allPackagesConfig
13661370
localPackagesConfig
@@ -2031,15 +2035,21 @@ elaborateInstallPlan verbosity platform compiler compilerprogdb pkgConfigDB
20312035
$ map packageId
20322036
$ SolverInstallPlan.reverseDependencyClosure
20332037
solverPlan
2034-
(map PlannedId (Set.toList pkgsLocalToProject))
2038+
(map PlannedId (Set.toList pkgsInplaceToProject))
20352039

20362040
isLocalToProject :: Package pkg => pkg -> Bool
20372041
isLocalToProject pkg = Set.member (packageId pkg)
20382042
pkgsLocalToProject
20392043

2044+
pkgsInplaceToProject :: Set PackageId
2045+
pkgsInplaceToProject =
2046+
Set.fromList (catMaybes (map shouldBeLocal localPackages))
2047+
--TODO: localPackages is a misnomer, it's all project packages
2048+
-- here is where we decide which ones will be local!
2049+
20402050
pkgsLocalToProject :: Set PackageId
20412051
pkgsLocalToProject =
2042-
Set.fromList (catMaybes (map shouldBeLocal localPackages))
2052+
Set.fromList (catMaybes (map (isInLocal extraPackages) localPackages))
20432053
--TODO: localPackages is a misnomer, it's all project packages
20442054
-- here is where we decide which ones will be local!
20452055

@@ -2108,6 +2118,28 @@ shouldBeLocal (SpecificSourcePackage pkg) = case srcpkgSource pkg of
21082118
LocalUnpackedPackage _ -> Just (packageId pkg)
21092119
_ -> Nothing
21102120

2121+
-- Used to determine which packages are affected by local package configuration
2122+
-- flags like ‘--enable-shared --enable-executable-dynamic --disable-library-vanilla’.
2123+
isInLocal :: [PackageVersionConstraint] -> PackageSpecifier (SourcePackage (PackageLocation loc)) -> Maybe PackageId
2124+
isInLocal _ NamedPackage{} = Nothing
2125+
isInLocal _extraPackages (SpecificSourcePackage pkg) = case srcpkgSource pkg of
2126+
LocalUnpackedPackage _ -> Just (packageId pkg)
2127+
-- LocalTarballPackage is matched here too, because otherwise ‘sdistize’
2128+
-- produces for ‘localPackages’ in the ‘ProjectBaseContext’ a
2129+
-- LocalTarballPackage, and ‘shouldBeLocal’ will make flags like
2130+
-- ‘--disable-library-vanilla’ have no effect for a typical
2131+
-- ‘cabal install --lib --enable-shared enable-executable-dynamic --disable-library-vanilla’,
2132+
-- as these flags would apply to local packages, but the sdist would
2133+
-- erroneously not get categorized as a local package, so the flags would be
2134+
-- ignored and produce a package with an unchanged hash.
2135+
LocalTarballPackage _ -> Just (packageId pkg)
2136+
-- TODO: the docs say ‘extra-packages’ is implemented in cabal project
2137+
-- files. We can fix that here by checking that the version range matches.
2138+
--RemoteTarballPackage _ -> _
2139+
--RepoTarballPackage _ -> _
2140+
--RemoteSourceRepoPackage _ -> _
2141+
_ -> Nothing
2142+
21112143
-- | Given a 'ElaboratedPlanPackage', report if it matches a 'ComponentName'.
21122144
matchPlanPkg :: (ComponentName -> Bool) -> ElaboratedPlanPackage -> Bool
21132145
matchPlanPkg p = InstallPlan.foldPlanPackage (p . ipiComponentName) (matchElabPkg p)
@@ -3387,7 +3419,8 @@ setupHsScriptOptions (ReadyPackage elab@ElaboratedConfiguredPackage{..})
33873419
useWin32CleanHack = False, --TODO: [required eventually]
33883420
forceExternalSetupMethod = isParallelBuild,
33893421
setupCacheLock = Just cacheLock,
3390-
isInteractive = False
3422+
isInteractive = False,
3423+
setupConfigDynamic = elabDynExe
33913424
}
33923425

33933426

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

Lines changed: 12 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -71,7 +71,7 @@ import Distribution.Simple.BuildPaths
7171
import Distribution.Simple.Command
7272
( CommandUI(..), commandShowOptions )
7373
import Distribution.Simple.Program.GHC
74-
( GhcMode(..), GhcOptions(..), renderGhcOptions )
74+
( GhcMode(..), GhcDynLinkMode(..), GhcOptions(..), renderGhcOptions )
7575
import qualified Distribution.Simple.PackageIndex as PackageIndex
7676
import Distribution.Simple.PackageIndex (InstalledPackageIndex)
7777
import qualified Distribution.InstalledPackageInfo as IPI
@@ -249,7 +249,12 @@ data SetupScriptOptions = SetupScriptOptions {
249249
-- | Is the task we are going to run an interactive foreground task,
250250
-- or an non-interactive background task? Based on this flag we
251251
-- decide whether or not to delegate ctrl+c to the spawned task
252-
isInteractive :: Bool
252+
isInteractive :: Bool,
253+
254+
-- Also track build output artifact configuration.
255+
256+
-- | Pass `-dynamic` to `ghc` for dynamic rather than static linking.
257+
setupConfigDynamic :: Bool
253258
}
254259

255260
defaultSetupScriptOptions :: SetupScriptOptions
@@ -272,7 +277,8 @@ defaultSetupScriptOptions = SetupScriptOptions {
272277
useWin32CleanHack = False,
273278
forceExternalSetupMethod = False,
274279
setupCacheLock = Nothing,
275-
isInteractive = False
280+
isInteractive = False,
281+
setupConfigDynamic = False
276282
}
277283

278284
workingDir :: SetupScriptOptions -> FilePath
@@ -840,6 +846,9 @@ getExternalSetupMethod verbosity options pkg bt = do
840846
-- --ghc-option=-v instead!
841847
ghcOptVerbosity = Flag (min verbosity normal)
842848
, ghcOptMode = Flag GhcModeMake
849+
, ghcOptDynLinkMode = case setupConfigDynamic options'' of
850+
True -> Flag GhcDynamicOnly
851+
False -> Flag GhcStaticOnly
843852
, ghcOptInputFiles = toNubListR [setupHs]
844853
, ghcOptOutputFile = Flag setupProgFile
845854
, ghcOptObjDir = Flag setupDir

cabal-install/tests/IntegrationTests2.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1591,7 +1591,7 @@ testProgramOptionsLocal config0 = do
15911591
(Just [ghcFlag])
15921592
(getProgArgs localPackages "q")
15931593
assertEqual "p"
1594-
Nothing
1594+
(Just [ghcFlag])
15951595
(getProgArgs localPackages "p")
15961596
where
15971597
testdir = "regression/program-options"
Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
module Basic where
2+
3+
funcs :: (a -> b -> c) -> ((a -> b -> c) -> a -> b -> c) -> b -> a -> c
4+
funcs f g = \a b -> (g f) b a
5+
6+
name :: String
7+
name = "Basic"
8+
9+
number :: Integer
10+
number = 8
Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
cabal-version: >= 1.10
2+
name: basic
3+
version: 0.1
4+
build-type: Simple
5+
6+
library
7+
default-language: Haskell2010
8+
build-depends: base
9+
exposed-modules:
10+
Basic
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
packages: basic
Lines changed: 26 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,26 @@
1+
# cabal v2-install
2+
Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz
3+
Resolving dependencies...
4+
Build profile: -w ghc-<GHCVER> -O1
5+
In order, the following will be built:
6+
- basic-0.1 (lib) (requires build)
7+
Configuring library for basic-0.1..
8+
Preprocessing library for basic-0.1..
9+
Building library for basic-0.1..
10+
Installing library in <PATH>
11+
# cabal v2-install
12+
Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz
13+
Resolving dependencies...
14+
Build profile: -w ghc-<GHCVER> -O1
15+
In order, the following will be built:
16+
- basic-0.1 (lib) (requires build)
17+
Configuring library for basic-0.1..
18+
Preprocessing library for basic-0.1..
19+
Building library for basic-0.1..
20+
Installing library in <PATH>
21+
# cabal v2-install
22+
Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz
23+
Resolving dependencies...
24+
# cabal v2-install
25+
Wrote tarball sdist to <ROOT>/cabal.dist/work/./basic/../dist/sdist/basic-0.1.tar.gz
26+
Resolving dependencies...
Lines changed: 105 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,105 @@
1+
import Test.Cabal.Prelude
2+
3+
-- This test ensures the following fix holds:
4+
-- > Fix project-local build flags being ignored.
5+
-- >
6+
-- > I noticed that running ‘cabal install’ with two separate sets of dynamic /
7+
-- > static build flags (e.g. one with none, and one with ‘--enable-shared
8+
-- > --enable-executable-dynamic --disable-library-vanilla’) produced packages with
9+
-- > the same hash, instead of different hashes.
10+
-- >
11+
-- > After debugging this issue I found that this command (with no explicit cabal
12+
-- > project file) was resulting in these build configuration flags being ignored,
13+
-- > because in ProjectPlanning.hs, the sdist was not considered a local package, so
14+
-- > the (non-shared) local-package-only configuration was being dropped.
15+
-- >
16+
-- > This fix ensures that these command-line arguments properly make it through to
17+
-- > where they belong in cases like this.
18+
--
19+
-- Basically, take a simple package, build it under two sets of build flags:
20+
-- > (nothing)
21+
-- > --enable-shared --enable-executable-dynamic --disable-library-vanilla
22+
--
23+
-- And ensure that whereas before they produced the same hash, now the package
24+
-- hashes produced are different. (And also supplementarily ensure that
25+
-- re-running the same build with the same flags a second time produces a
26+
-- deterministic hash too; the hash should differ only when we change these
27+
-- flags.)
28+
--
29+
-- Based on the UniqueIPID test.
30+
31+
import Control.Monad (forM, foldM_)
32+
import Data.List (isPrefixOf, tails)
33+
34+
data Linking = Static | Dynamic deriving (Eq, Ord, Show)
35+
36+
links :: [Linking]
37+
links = [Static, Dynamic]
38+
39+
linkConfigFlags :: Linking -> [String]
40+
linkConfigFlags Static =
41+
[
42+
]
43+
linkConfigFlags Dynamic =
44+
[
45+
"--enable-shared",
46+
"--enable-executable-dynamic",
47+
"--disable-library-vanilla"
48+
]
49+
50+
lrun :: [Linking]
51+
lrun = [Static, Dynamic, Static, Dynamic]
52+
53+
main = cabalTest $ do
54+
-- Skip if on Windows, since my default Chocolatey Windows setup (and the CI
55+
-- server setup at the time, presumably) lacks support for dynamic builds
56+
-- since the base package appears to be static only, lacking e.g. ‘.dyn_o’
57+
-- files. Normal Windows installations would need suport for dynamic
58+
-- builds, or else this test would fail when it tries to build with the
59+
-- dynamic flags.
60+
skipIfWindows
61+
62+
withPackageDb $ do
63+
-- Phase 1: get 4 hashes according to config flags.
64+
results <- forM (zip [0..] lrun) $ \(idx, linking) -> do
65+
withDirectory "basic" $ do
66+
withSourceCopyDir ("basic" ++ show idx) $ do
67+
cwd <- fmap testSourceCopyDir getTestEnv
68+
-- (Now do ‘cd ..’, since withSourceCopyDir made our previous
69+
-- previous such withDirectories now accumulate to be
70+
-- relative to setup.dist/basic0, not testSourceDir
71+
-- (see 'testCurrentDir').)
72+
withDirectory ".." $ do
73+
packageEnv <- (</> ("basic" ++ show idx ++ ".env")) . testWorkDir <$> getTestEnv
74+
cabal "v2-install" $ ["--disable-deterministic", "--lib", "--package-env=" ++ packageEnv] ++ linkConfigFlags linking ++ ["basic"]
75+
let exIPID s = takeWhile (/= '\n') . head . filter (\t -> any (`isPrefixOf` t) ["basic-0.1-", "bsc-0.1-"]) $ tails s
76+
hashedIpid <- exIPID <$> liftIO (readFile packageEnv)
77+
return $ ((idx, linking), hashedIpid)
78+
-- Phase 2: make sure we have different hashes iff we have different config flags.
79+
-- In particular make sure the dynamic config flags weren't silently
80+
-- dropped and ignored, since this is the bug that prompted this test.
81+
(\step -> foldM_ step (const $ return ()) results) $ \acc x -> do
82+
acc x
83+
return $ \future -> acc future >> do
84+
let
85+
((thisIdx, thisLinking), thisHashedIpid) = x
86+
((futureIdx, futureLinking), futureHashedIpid) = future
87+
when ((thisHashedIpid == futureHashedIpid) /= (thisLinking == futureLinking)) $ do
88+
assertFailure . unlines $
89+
if thisLinking /= futureLinking
90+
then
91+
-- What we are primarily concerned with testing
92+
-- here.
93+
[
94+
"Error: static and dynamic config flags produced an IPID with the same hash; were the dynamic flags silently dropped?",
95+
"\thashed IPID: " ++ thisHashedIpid
96+
]
97+
else
98+
-- Help test our test can also make equal
99+
-- hashes.
100+
[
101+
"Error: config flags were equal, yet a different IPID hash was produced.",
102+
"\thashed IPID 1 : " ++ thisHashedIpid,
103+
"\thashed IPID 2 : " ++ futureHashedIpid,
104+
"\tlinking flags : " ++ show thisLinking
105+
]

changelog.d/pr-8623

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
synopsis: Fix project-local flags being ignored
2+
packages: cabal-install
3+
prs: #8623
4+
description: {
5+
Fix some cases of configuration flags being dropped, e.g. with `v2-install`
6+
and `--enable-shared --enable-executable-dynamic --disable-library-vanilla`.
7+
}

0 commit comments

Comments
 (0)