Skip to content

Commit cce3ae2

Browse files
Merge pull request #3039 from grayjay/buildable-tests
Tests for #2731 (Ignore dependencies that are not Buildable)
2 parents 8fd4071 + 1727f43 commit cce3ae2

File tree

8 files changed

+219
-53
lines changed

8 files changed

+219
-53
lines changed

Cabal/Cabal.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -77,6 +77,8 @@ extra-source-files:
7777
tests/PackageTests/BuildDeps/TargetSpecificDeps3/lemon.hs
7878
tests/PackageTests/BuildDeps/TargetSpecificDeps3/my.cabal
7979
tests/PackageTests/BuildTestSuiteDetailedV09/Dummy2.hs
80+
tests/PackageTests/BuildableField/BuildableField.cabal
81+
tests/PackageTests/BuildableField/Main.hs
8082
tests/PackageTests/CMain/Bar.hs
8183
tests/PackageTests/CMain/foo.c
8284
tests/PackageTests/CMain/my.cabal

Cabal/Distribution/PackageDescription/Configuration.hs

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -220,6 +220,7 @@ resolveWithFlags dom os arch impl constrs trees checkDeps =
220220

221221
-- simplify trees by (partially) evaluating all conditions and converting
222222
-- dependencies to dependency maps.
223+
simplifiedTrees :: [CondTree FlagName DependencyMap PDTagged]
223224
simplifiedTrees = map ( mapTreeConstrs toDepMap -- convert to maps
224225
. mapTreeConds (fst . simplifyWithSysParams os arch impl))
225226
trees
@@ -228,6 +229,9 @@ resolveWithFlags dom os arch impl constrs trees checkDeps =
228229
-- either succeeds or returns a binary tree with the missing dependencies
229230
-- encountered in each run. Since the tree is constructed lazily, we
230231
-- avoid some computation overhead in the successful case.
232+
try :: [(FlagName, [Bool])]
233+
-> [(FlagName, Bool)]
234+
-> Either (BT [Dependency]) (TargetSet PDTagged, FlagAssignment)
231235
try [] flags =
232236
let targetSet = TargetSet $ flip map simplifiedTrees $
233237
-- apply additional constraints to all dependencies
@@ -337,11 +341,11 @@ overallDependencies (TargetSet targets) = mconcat depss
337341
where
338342
(depss, _) = unzip $ filter (removeDisabledSections . snd) targets
339343
removeDisabledSections :: PDTagged -> Bool
340-
removeDisabledSections (Lib _) = True
341-
removeDisabledSections (Exe _ _) = True
342-
removeDisabledSections (Test _ t) = testEnabled t
343-
removeDisabledSections (Bench _ b) = benchmarkEnabled b
344-
removeDisabledSections PDNull = True
344+
removeDisabledSections (Lib l) = buildable (libBuildInfo l)
345+
removeDisabledSections (Exe _ e) = buildable (buildInfo e)
346+
removeDisabledSections (Test _ t) = testEnabled t && buildable (testBuildInfo t)
347+
removeDisabledSections (Bench _ b) = benchmarkEnabled b && buildable (benchmarkBuildInfo b)
348+
removeDisabledSections PDNull = True
345349

346350
-- Apply extra constraints to a dependency map.
347351
-- Combines dependencies where the result will only contain keys from the left
@@ -482,10 +486,6 @@ finalizePackageDescription userflags satisfyDep
482486
, testSuites = tests'
483487
, benchmarks = bms'
484488
, buildDepends = fromDepMap (overallDependencies targetSet)
485-
--TODO: we need to find a way to avoid pulling in deps
486-
-- for non-buildable components. However cannot simply
487-
-- filter at this stage, since if the package were not
488-
-- available we would have failed already.
489489
}
490490
, flagVals )
491491

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
name: BuildableField
2+
version: 0.1.0.0
3+
cabal-version: >=1.2
4+
build-type: Simple
5+
license: BSD3
6+
7+
flag build-exe
8+
default: True
9+
10+
library
11+
12+
executable my-executable
13+
build-depends: base, unavailable-package
14+
main-is: Main.hs
15+
if !flag(build-exe)
16+
buildable: False
Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
import UnavailableModule
2+
3+
main :: IO ()
4+
main = putStrLn "Hello"

Cabal/tests/PackageTests/Tests.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -223,6 +223,14 @@ tests config =
223223
cabal_build ["--enable-tests"]
224224
cabal "test" []
225225

226+
-- Test that Cabal can choose flags to disable building a component when that
227+
-- component's dependencies are unavailable. The build should succeed without
228+
-- requiring the component's dependencies or imports.
229+
, tc "BuildableField" $ do
230+
r <- cabal' "configure" ["-v"]
231+
assertOutputContains "Flags chosen: build-exe=False" r
232+
cabal "build" []
233+
226234
]
227235
where
228236
-- Shared test function for BuildDeps/InternalLibrary* tests.

cabal-install/Distribution/Client/Dependency/Modular/IndexConversion.hs

Lines changed: 59 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -106,7 +106,7 @@ convGPD os arch comp strfl pi
106106
(GenericPackageDescription pkg flags libs exes tests benchs) =
107107
let
108108
fds = flagInfo strfl flags
109-
conv = convCondTree os arch comp pi fds (const True)
109+
conv = convBuildableCondTree os arch comp pi fds
110110
in
111111
PInfo
112112
(maybe [] (conv ComponentLib libBuildInfo ) libs ++
@@ -128,18 +128,68 @@ prefix f fds = [f (concat fds)]
128128
flagInfo :: Bool -> [PD.Flag] -> FlagInfo
129129
flagInfo strfl = M.fromList . L.map (\ (MkFlag fn _ b m) -> (fn, FInfo b m (not (strfl || m))))
130130

131+
-- | Extract buildable condition from a cond tree.
132+
--
133+
-- Background: If the conditions in a cond tree lead to Buildable being set to False,
134+
-- then none of the dependencies for this cond tree should actually be taken into
135+
-- account. On the other hand, some of the flags may only be decided in the solver,
136+
-- so we cannot necessarily make the decision whether a component is Buildable or not
137+
-- prior to solving.
138+
--
139+
-- What we are doing here is to partially evaluate a condition tree in order to extract
140+
-- the condition under which Buildable is True.
141+
extractCondition :: Eq v => (a -> Bool) -> CondTree v [c] a -> Condition v
142+
extractCondition p = go
143+
where
144+
go (CondNode x _ cs) | not (p x) = Lit False
145+
| otherwise = goList cs
146+
147+
goList [] = Lit True
148+
goList ((c, t, e) : cs) =
149+
let
150+
ct = go t
151+
ce = maybe (Lit True) go e
152+
in
153+
((c `cand` ct) `cor` (CNot c `cand` ce)) `cand` goList cs
154+
155+
cand (Lit False) _ = Lit False
156+
cand _ (Lit False) = Lit False
157+
cand (Lit True) x = x
158+
cand x (Lit True) = x
159+
cand x y = CAnd x y
160+
161+
cor (Lit True) _ = Lit True
162+
cor _ (Lit True) = Lit True
163+
cor (Lit False) x = x
164+
cor x (Lit False) = x
165+
cor c (CNot d)
166+
| c == d = Lit True
167+
cor x y = COr x y
168+
169+
-- | Convert a condition tree to flagged dependencies.
170+
--
171+
-- In addition, tries to determine under which condition the condition tree
172+
-- is buildable, and will add an additional condition on top accordingly.
173+
convBuildableCondTree :: OS -> Arch -> CompilerInfo -> PI PN -> FlagInfo ->
174+
Component ->
175+
(a -> BuildInfo) ->
176+
CondTree ConfVar [Dependency] a -> FlaggedDeps Component PN
177+
convBuildableCondTree os arch cinfo pi fds comp getInfo t =
178+
case extractCondition (buildable . getInfo) t of
179+
Lit True -> convCondTree os arch cinfo pi fds comp getInfo t
180+
Lit False -> []
181+
c -> convBranch os arch cinfo pi fds comp getInfo (c, t, Nothing)
182+
131183
-- | Convert condition trees to flagged dependencies.
132184
convCondTree :: OS -> Arch -> CompilerInfo -> PI PN -> FlagInfo ->
133-
(a -> Bool) -> -- how to detect if a branch is active
134185
Component ->
135186
(a -> BuildInfo) ->
136187
CondTree ConfVar [Dependency] a -> FlaggedDeps Component PN
137-
convCondTree os arch cinfo pi@(PI pn _) fds p comp getInfo (CondNode info ds branches)
138-
| p info = L.map (\d -> D.Simple (convDep pn d) comp) ds -- unconditional package dependencies
188+
convCondTree os arch cinfo pi@(PI pn _) fds comp getInfo (CondNode info ds branches) =
189+
L.map (\d -> D.Simple (convDep pn d) comp) ds -- unconditional package dependencies
139190
++ L.map (\e -> D.Simple (Ext e) comp) (PD.allExtensions bi) -- unconditional extension dependencies
140191
++ L.map (\l -> D.Simple (Lang l) comp) (PD.allLanguages bi) -- unconditional language dependencies
141-
++ concatMap (convBranch os arch cinfo pi fds p comp getInfo) branches
142-
| otherwise = []
192+
++ concatMap (convBranch os arch cinfo pi fds comp getInfo) branches
143193
where
144194
bi = getInfo info
145195

@@ -153,15 +203,14 @@ convCondTree os arch cinfo pi@(PI pn _) fds p comp getInfo (CondNode info ds bra
153203
-- simple flag choices.
154204
convBranch :: OS -> Arch -> CompilerInfo ->
155205
PI PN -> FlagInfo ->
156-
(a -> Bool) -> -- how to detect if a branch is active
157206
Component ->
158207
(a -> BuildInfo) ->
159208
(Condition ConfVar,
160209
CondTree ConfVar [Dependency] a,
161210
Maybe (CondTree ConfVar [Dependency] a)) -> FlaggedDeps Component PN
162-
convBranch os arch cinfo pi@(PI pn _) fds p comp getInfo (c', t', mf') =
163-
go c' ( convCondTree os arch cinfo pi fds p comp getInfo t')
164-
(maybe [] (convCondTree os arch cinfo pi fds p comp getInfo) mf')
211+
convBranch os arch cinfo pi@(PI pn _) fds comp getInfo (c', t', mf') =
212+
go c' ( convCondTree os arch cinfo pi fds comp getInfo t')
213+
(maybe [] (convCondTree os arch cinfo pi fds comp getInfo) mf')
165214
where
166215
go :: Condition ConfVar ->
167216
FlaggedDeps Component PN -> FlaggedDeps Component PN -> FlaggedDeps Component PN

cabal-install/tests/UnitTests/Distribution/Client/Dependency/Modular/DSL.hs

Lines changed: 51 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -2,12 +2,14 @@
22
-- | DSL for testing the modular solver
33
module UnitTests.Distribution.Client.Dependency.Modular.DSL (
44
ExampleDependency(..)
5+
, Dependencies(..)
56
, ExPreference(..)
67
, ExampleDb
78
, ExampleVersionRange
89
, ExamplePkgVersion
910
, exAv
1011
, exInst
12+
, exFlag
1113
, exResolve
1214
, extractInstallPlan
1315
, withSetupDeps
@@ -16,6 +18,7 @@ module UnitTests.Distribution.Client.Dependency.Modular.DSL (
1618
-- base
1719
import Data.Either (partitionEithers)
1820
import Data.Maybe (catMaybes)
21+
import Data.List (nub)
1922
import Data.Monoid
2023
import Data.Version
2124
import qualified Data.Map as Map
@@ -88,6 +91,7 @@ type ExamplePkgHash = String -- for example "installed" packages
8891
type ExampleFlagName = String
8992
type ExampleTestName = String
9093
type ExampleVersionRange = C.VersionRange
94+
data Dependencies = NotBuildable | Buildable [ExampleDependency]
9195

9296
data ExampleDependency =
9397
-- | Simple dependency on any version
@@ -97,7 +101,7 @@ data ExampleDependency =
97101
| ExFix ExamplePkgName ExamplePkgVersion
98102

99103
-- | Dependencies indexed by a flag
100-
| ExFlag ExampleFlagName [ExampleDependency] [ExampleDependency]
104+
| ExFlag ExampleFlagName Dependencies Dependencies
101105

102106
-- | Dependency if tests are enabled
103107
| ExTest ExampleTestName [ExampleDependency]
@@ -108,6 +112,10 @@ data ExampleDependency =
108112
-- | Dependency on a language version
109113
| ExLang Language
110114

115+
exFlag :: ExampleFlagName -> [ExampleDependency] -> [ExampleDependency]
116+
-> ExampleDependency
117+
exFlag n t e = ExFlag n (Buildable t) (Buildable e)
118+
111119
data ExPreference = ExPref String ExampleVersionRange
112120

113121
data ExampleAvailable = ExAv {
@@ -163,12 +171,15 @@ exAvSrcPkg ex =
163171
C.setupDepends = mkSetupDeps (CD.setupDeps (exAvDeps ex))
164172
}
165173
}
166-
, C.genPackageFlags = concatMap extractFlags
174+
, C.genPackageFlags = nub $ concatMap extractFlags
167175
(CD.libraryDeps (exAvDeps ex))
168-
, C.condLibrary = Just $ mkCondTree (extsLib exts <> langLib mlang) libraryDeps
176+
, C.condLibrary = Just $ mkCondTree (extsLib exts <> langLib mlang)
177+
disableLib
178+
(Buildable libraryDeps)
169179
, C.condExecutables = []
170-
, C.condTestSuites = map (\(t, deps) -> (t, mkCondTree mempty deps))
171-
testSuites
180+
, C.condTestSuites =
181+
let mkTree = mkCondTree mempty disableTest . Buildable
182+
in map (\(t, deps) -> (t, mkTree deps)) testSuites
172183
, C.condBenchmarks = []
173184
}
174185
}
@@ -207,18 +218,28 @@ exAvSrcPkg ex =
207218
, C.flagDefault = False
208219
, C.flagManual = False
209220
}
210-
: concatMap extractFlags (a ++ b)
221+
: concatMap extractFlags (deps a ++ deps b)
222+
where
223+
deps :: Dependencies -> [ExampleDependency]
224+
deps NotBuildable = []
225+
deps (Buildable ds) = ds
211226
extractFlags (ExTest _ a) = concatMap extractFlags a
212227
extractFlags (ExExt _) = []
213228
extractFlags (ExLang _) = []
214229

215-
mkCondTree :: Monoid a => a -> [ExampleDependency] -> DependencyTree a
216-
mkCondTree x deps =
230+
mkCondTree :: Monoid a => a -> (a -> a) -> Dependencies -> DependencyTree a
231+
mkCondTree x dontBuild NotBuildable =
232+
C.CondNode {
233+
C.condTreeData = dontBuild x
234+
, C.condTreeConstraints = []
235+
, C.condTreeComponents = []
236+
}
237+
mkCondTree x dontBuild (Buildable deps) =
217238
let (directDeps, flaggedDeps) = splitDeps deps
218239
in C.CondNode {
219240
C.condTreeData = x -- Necessary for language extensions
220241
, C.condTreeConstraints = map mkDirect directDeps
221-
, C.condTreeComponents = map mkFlagged flaggedDeps
242+
, C.condTreeComponents = map (mkFlagged dontBuild) flaggedDeps
222243
}
223244

224245
mkDirect :: (ExamplePkgName, Maybe ExamplePkgVersion) -> C.Dependency
@@ -228,13 +249,14 @@ exAvSrcPkg ex =
228249
v = Version [n, 0, 0] []
229250

230251
mkFlagged :: Monoid a
231-
=> (ExampleFlagName, [ExampleDependency], [ExampleDependency])
252+
=> (a -> a)
253+
-> (ExampleFlagName, Dependencies, Dependencies)
232254
-> (C.Condition C.ConfVar
233255
, DependencyTree a, Maybe (DependencyTree a))
234-
mkFlagged (f, a, b) = ( C.Var (C.Flag (C.FlagName f))
235-
, mkCondTree mempty a
236-
, Just (mkCondTree mempty b)
237-
)
256+
mkFlagged dontBuild (f, a, b) = ( C.Var (C.Flag (C.FlagName f))
257+
, mkCondTree mempty dontBuild a
258+
, Just (mkCondTree mempty dontBuild b)
259+
)
238260

239261
-- Split a set of dependencies into direct dependencies and flagged
240262
-- dependencies. A direct dependency is a tuple of the name of package and
@@ -245,7 +267,7 @@ exAvSrcPkg ex =
245267
-- TODO: Take care of flagged language extensions and language flavours.
246268
splitDeps :: [ExampleDependency]
247269
-> ( [(ExamplePkgName, Maybe Int)]
248-
, [(ExampleFlagName, [ExampleDependency], [ExampleDependency])]
270+
, [(ExampleFlagName, Dependencies, Dependencies)]
249271
)
250272
splitDeps [] =
251273
([], [])
@@ -276,6 +298,14 @@ exAvSrcPkg ex =
276298
langLib (Just lang) = mempty { C.libBuildInfo = mempty { C.defaultLanguage = Just lang } }
277299
langLib _ = mempty
278300

301+
disableLib :: C.Library -> C.Library
302+
disableLib lib =
303+
lib { C.libBuildInfo = (C.libBuildInfo lib) { C.buildable = False }}
304+
305+
disableTest :: C.TestSuite -> C.TestSuite
306+
disableTest test =
307+
test { C.testBuildInfo = (C.testBuildInfo test) { C.buildable = False }}
308+
279309
exAvPkgId :: ExampleAvailable -> C.PackageIdentifier
280310
exAvPkgId ex = C.PackageIdentifier {
281311
pkgName = C.PackageName (exAvName ex)
@@ -303,10 +333,10 @@ exInstIdx :: [ExampleInstalled] -> C.PackageIndex.InstalledPackageIndex
303333
exInstIdx = C.PackageIndex.fromList . map exInstInfo
304334

305335
exResolve :: ExampleDb
306-
-- List of extensions supported by the compiler.
307-
-> [Extension]
308-
-- A compiler can support multiple languages.
309-
-> [Language]
336+
-- List of extensions supported by the compiler, or Nothing if unknown.
337+
-> Maybe [Extension]
338+
-- List of languages supported by the compiler, or Nothing if unknown.
339+
-> Maybe [Language]
310340
-> [ExamplePkgName]
311341
-> Bool
312342
-> [ExPreference]
@@ -318,12 +348,8 @@ exResolve db exts langs targets indepGoals prefs = runProgress $
318348
params
319349
where
320350
defaultCompiler = C.unknownCompilerInfo C.buildCompilerId C.NoAbiTag
321-
compiler = defaultCompiler { C.compilerInfoExtensions = if null exts
322-
then Nothing
323-
else Just exts
324-
, C.compilerInfoLanguages = if null langs
325-
then Nothing
326-
else Just langs
351+
compiler = defaultCompiler { C.compilerInfoExtensions = exts
352+
, C.compilerInfoLanguages = langs
327353
}
328354
(inst, avai) = partitionEithers db
329355
instIdx = exInstIdx inst

0 commit comments

Comments
 (0)