Skip to content

Commit 1a01c92

Browse files
committed
Merge pull request #3082 from grayjay/setup-configure-backtracking
Improve algorithm for choosing flags with './Setup configure'
2 parents e207ecf + 6d42e6e commit 1a01c92

File tree

3 files changed

+112
-78
lines changed

3 files changed

+112
-78
lines changed

Cabal/src/Distribution/PackageDescription/Configuration.hs

Lines changed: 109 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ module Distribution.PackageDescription.Configuration (
2222
-- Utils
2323
parseCondition,
2424
freeVars,
25+
extractCondition,
2526
mapCondTree,
2627
mapTreeData,
2728
mapTreeConds,
@@ -45,6 +46,7 @@ import Data.Char ( isAlphaNum )
4546
import Data.Maybe ( mapMaybe, maybeToList )
4647
import Data.Map ( Map, fromListWith, toList )
4748
import qualified Data.Map as Map
49+
import Data.Tree ( Tree(Node) )
4850

4951
------------------------------------------------------------------------------
5052

@@ -183,8 +185,9 @@ instance Semigroup d => Semigroup (DepTestRslt d) where
183185
-- resulting data, the associated dependencies, and the chosen flag
184186
-- assignments.
185187
--
186-
-- In case of failure, the _smallest_ number of of missing dependencies is
187-
-- returned. [TODO: Could also be specified with a function argument.]
188+
-- In case of failure, the union of the dependencies that led to backtracking
189+
-- on all branches is returned.
190+
-- [TODO: Could also be specified with a function argument.]
188191
--
189192
-- TODO: The current algorithm is rather naive. A better approach would be to:
190193
--
@@ -209,64 +212,129 @@ resolveWithFlags ::
209212
-> Either [Dependency] (TargetSet PDTagged, FlagAssignment)
210213
-- ^ Either the missing dependencies (error case), or a pair of
211214
-- (set of build targets with dependencies, chosen flag assignments)
212-
resolveWithFlags dom os arch impl constrs trees checkDeps = try dom []
215+
resolveWithFlags dom os arch impl constrs trees checkDeps =
216+
either (Left . fromDepMapUnion) Right $ explore (build [] dom)
213217
where
214218
extraConstrs = toDepMap constrs
215219

216220
-- simplify trees by (partially) evaluating all conditions and converting
217221
-- dependencies to dependency maps.
218222
simplifiedTrees :: [CondTree FlagName DependencyMap PDTagged]
219223
simplifiedTrees = map ( mapTreeConstrs toDepMap -- convert to maps
224+
. addBuildableCondition pdTaggedBuildInfo
220225
. mapTreeConds (fst . simplifyWithSysParams os arch impl))
221226
trees
222227

223-
-- @try@ recursively tries all possible flag assignments in the domain and
224-
-- either succeeds or returns the shortest list of missing dependencies.
225-
try :: [(FlagName, [Bool])]
226-
-> [(FlagName, Bool)]
227-
-> Either [Dependency] (TargetSet PDTagged, FlagAssignment)
228-
try [] flags =
228+
-- @explore@ searches a tree of assignments, backtracking whenever a flag
229+
-- introduces a dependency that cannot be satisfied. If there is no
230+
-- solution, @explore@ returns the union of all dependencies that caused
231+
-- it to backtrack. Since the tree is constructed lazily, we avoid some
232+
-- computation overhead in the successful case.
233+
explore :: Tree FlagAssignment
234+
-> Either DepMapUnion (TargetSet PDTagged, FlagAssignment)
235+
explore (Node flags ts) =
229236
let targetSet = TargetSet $ flip map simplifiedTrees $
230237
-- apply additional constraints to all dependencies
231238
first (`constrainBy` extraConstrs) .
232239
simplifyCondTree (env flags)
233240
deps = overallDependencies targetSet
234241
in case checkDeps (fromDepMap deps) of
235-
DepOk -> Right (targetSet, flags)
236-
MissingDeps mds -> Left mds
237-
238-
try ((n, vals):rest) flags =
239-
tryAll $ map (\v -> try rest ((n, v):flags)) vals
240-
241-
tryAll :: [Either [a] b] -> Either [a] b
242+
DepOk | null ts -> Right (targetSet, flags)
243+
| otherwise -> tryAll $ map explore ts
244+
MissingDeps mds -> Left (toDepMapUnion mds)
245+
246+
-- Builds a tree of all possible flag assignments. Internal nodes
247+
-- have only partial assignments.
248+
build :: FlagAssignment -> [(FlagName, [Bool])] -> Tree FlagAssignment
249+
build assigned [] = Node assigned []
250+
build assigned ((fn, vals) : unassigned) =
251+
Node assigned $ map (\v -> build ((fn, v) : assigned) unassigned) vals
252+
253+
tryAll :: [Either DepMapUnion a] -> Either DepMapUnion a
242254
tryAll = foldr mp mz
243255

244256
-- special version of `mplus' for our local purposes
245-
mp :: Either [a] b -> Either [a] b -> Either [a] b
246-
mp (Left xs) (Left ys) = xs `seq` ys `seq` Left (findShortest xs ys)
247-
mp (Left _) m@(Right _) = m
257+
mp :: Either DepMapUnion a -> Either DepMapUnion a -> Either DepMapUnion a
248258
mp m@(Right _) _ = m
259+
mp _ m@(Right _) = m
260+
mp (Left xs) (Left ys) =
261+
let union = Map.foldrWithKey (Map.insertWith' combine)
262+
(unDepMapUnion xs) (unDepMapUnion ys)
263+
combine x y = simplifyVersionRange $ unionVersionRanges x y
264+
in union `seq` Left (DepMapUnion union)
249265

250266
-- `mzero'
251-
mz :: Either [a] b
252-
mz = Left []
267+
mz :: Either DepMapUnion a
268+
mz = Left (DepMapUnion Map.empty)
253269

254270
env :: FlagAssignment -> FlagName -> Either FlagName Bool
255271
env flags flag = (maybe (Left flag) Right . lookup flag) flags
256272

257-
-- we pick the shortest list of missing dependencies
258-
findShortest :: [a] -> [a] -> [a]
259-
findShortest [] xs = xs -- [] is too short
260-
findShortest xs [] = xs
261-
findShortest [x] _ = [x] -- single elem is optimum
262-
findShortest _ [x] = [x]
263-
findShortest xs ys = if lazyLengthCmp xs ys
264-
then xs else ys
265-
-- lazy variant of @\xs ys -> length xs <= length ys@
266-
lazyLengthCmp :: [a] -> [a] -> Bool
267-
lazyLengthCmp [] _ = True
268-
lazyLengthCmp _ [] = False
269-
lazyLengthCmp (_:xs) (_:ys) = lazyLengthCmp xs ys
273+
pdTaggedBuildInfo :: PDTagged -> BuildInfo
274+
pdTaggedBuildInfo (Lib l) = libBuildInfo l
275+
pdTaggedBuildInfo (Exe _ e) = buildInfo e
276+
pdTaggedBuildInfo (Test _ t) = testBuildInfo t
277+
pdTaggedBuildInfo (Bench _ b) = benchmarkBuildInfo b
278+
pdTaggedBuildInfo PDNull = mempty
279+
280+
-- | Tries to determine under which condition the condition tree
281+
-- is buildable, and will add an additional condition on top accordingly.
282+
addBuildableCondition :: (Eq v, Monoid a, Monoid c) => (a -> BuildInfo)
283+
-> CondTree v c a
284+
-> CondTree v c a
285+
addBuildableCondition getInfo t =
286+
case extractCondition (buildable . getInfo) t of
287+
Lit True -> t
288+
Lit False -> CondNode mempty mempty []
289+
c -> CondNode mempty mempty [(c, t, Nothing)]
290+
291+
-- | Extract buildable condition from a cond tree.
292+
--
293+
-- Background: If the conditions in a cond tree lead to Buildable being set to False,
294+
-- then none of the dependencies for this cond tree should actually be taken into
295+
-- account. On the other hand, some of the flags may only be decided in the solver,
296+
-- so we cannot necessarily make the decision whether a component is Buildable or not
297+
-- prior to solving.
298+
--
299+
-- What we are doing here is to partially evaluate a condition tree in order to extract
300+
-- the condition under which Buildable is True.
301+
extractCondition :: Eq v => (a -> Bool) -> CondTree v c a -> Condition v
302+
extractCondition p = go
303+
where
304+
go (CondNode x _ cs) | not (p x) = Lit False
305+
| otherwise = goList cs
306+
307+
goList [] = Lit True
308+
goList ((c, t, e) : cs) =
309+
let
310+
ct = go t
311+
ce = maybe (Lit True) go e
312+
in
313+
((c `cand` ct) `cor` (CNot c `cand` ce)) `cand` goList cs
314+
315+
cand (Lit False) _ = Lit False
316+
cand _ (Lit False) = Lit False
317+
cand (Lit True) x = x
318+
cand x (Lit True) = x
319+
cand x y = CAnd x y
320+
321+
cor (Lit True) _ = Lit True
322+
cor _ (Lit True) = Lit True
323+
cor (Lit False) x = x
324+
cor x (Lit False) = x
325+
cor c (CNot d)
326+
| c == d = Lit True
327+
cor x y = COr x y
328+
329+
-- | A map of dependencies that combines version ranges using 'unionVersionRanges'.
330+
newtype DepMapUnion = DepMapUnion { unDepMapUnion :: Map PackageName VersionRange }
331+
332+
toDepMapUnion :: [Dependency] -> DepMapUnion
333+
toDepMapUnion ds =
334+
DepMapUnion $ fromListWith unionVersionRanges [ (p,vr) | Dependency p vr <- ds ]
335+
336+
fromDepMapUnion :: DepMapUnion -> [Dependency]
337+
fromDepMapUnion m = [ Dependency p vr | (p,vr) <- toList (unDepMapUnion m) ]
270338

271339
-- | A map of dependencies. Newtyped since the default monoid instance is not
272340
-- appropriate. The monoid instance uses 'intersectVersionRanges'.
@@ -288,6 +356,8 @@ toDepMap ds =
288356
fromDepMap :: DependencyMap -> [Dependency]
289357
fromDepMap m = [ Dependency p vr | (p,vr) <- toList (unDependencyMap m) ]
290358

359+
-- | Flattens a CondTree using a partial flag assignment. When a condition
360+
-- cannot be evaluated, both branches are ignored.
291361
simplifyCondTree :: (Monoid a, Monoid d) =>
292362
(v -> Either v Bool)
293363
-> CondTree v d a
@@ -299,7 +369,7 @@ simplifyCondTree env (CondNode a d ifs) =
299369
case simplifyCondition cnd env of
300370
(Lit True, _) -> Just $ simplifyCondTree env t
301371
(Lit False, _) -> fmap (simplifyCondTree env) me
302-
_ -> error $ "Environment not defined for all free vars"
372+
_ -> Nothing
303373

304374
-- | Flatten a CondTree. This will resolve the CondTree by taking all
305375
-- possible paths into account. Note that since branches represent exclusive
@@ -452,9 +522,10 @@ instance Semigroup PDTagged where
452522
--
453523
-- This function will fail if it cannot find a flag assignment that leads to
454524
-- satisfiable dependencies. (It will not try alternative assignments for
455-
-- explicitly specified flags.) In case of failure it will return a /minimum/
456-
-- number of dependencies that could not be satisfied. On success, it will
457-
-- return the package description and the full flag assignment chosen.
525+
-- explicitly specified flags.) In case of failure it will return the missing
526+
-- dependencies that it encountered when trying different flag assignments.
527+
-- On success, it will return the package description and the full flag
528+
-- assignment chosen.
458529
--
459530
finalizePackageDescription ::
460531
FlagAssignment -- ^ Explicitly specified flag assignments

Cabal/src/Distribution/Simple/Configure.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -819,7 +819,7 @@ configureFinalizedPackage verbosity cfg
819819
pkg_descr0''
820820
of Right r -> return r
821821
Left missing ->
822-
die $ "At least the following dependencies are missing:\n"
822+
die $ "Encountered missing dependencies:\n"
823823
++ (render . nest 4 . sep . punctuate comma
824824
. map (disp . simplifyDependency)
825825
$ missing)

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

Lines changed: 2 additions & 39 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ import Distribution.Compiler
1414
import Distribution.InstalledPackageInfo as IPI
1515
import Distribution.Package -- from Cabal
1616
import Distribution.PackageDescription as PD -- from Cabal
17+
import Distribution.PackageDescription.Configuration as PDC
1718
import qualified Distribution.Simple.PackageIndex as SI
1819
import Distribution.System
1920

@@ -128,44 +129,6 @@ prefix f fds = [f (concat fds)]
128129
flagInfo :: Bool -> [PD.Flag] -> FlagInfo
129130
flagInfo strfl = M.fromList . L.map (\ (MkFlag fn _ b m) -> (fn, FInfo b m (not (strfl || m))))
130131

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-
169132
-- | Convert a condition tree to flagged dependencies.
170133
--
171134
-- In addition, tries to determine under which condition the condition tree
@@ -175,7 +138,7 @@ convBuildableCondTree :: OS -> Arch -> CompilerInfo -> PI PN -> FlagInfo ->
175138
(a -> BuildInfo) ->
176139
CondTree ConfVar [Dependency] a -> FlaggedDeps Component PN
177140
convBuildableCondTree os arch cinfo pi fds comp getInfo t =
178-
case extractCondition (buildable . getInfo) t of
141+
case PDC.extractCondition (buildable . getInfo) t of
179142
Lit True -> convCondTree os arch cinfo pi fds comp getInfo t
180143
Lit False -> []
181144
c -> convBranch os arch cinfo pi fds comp getInfo (c, t, Nothing)

0 commit comments

Comments
 (0)