Add skipping installed tests
[cabal.git] / cabal-install / tests / UnitTests / Distribution / Solver / Modular / Solver.hs
bloba77c25b8ff58e0d9fa3613db2265259e30f2bb27
1 {-# LANGUAGE OverloadedStrings #-}
3 -- | This is a set of unit tests for the dependency solver,
4 -- which uses the solver DSL ("UnitTests.Distribution.Solver.Modular.DSL")
5 -- to more conveniently create package databases to run the solver tests on.
6 module UnitTests.Distribution.Solver.Modular.Solver (tests)
7 where
9 -- base
10 import Data.List (isInfixOf)
12 import qualified Distribution.Version as V
14 -- test-framework
15 import Test.Tasty as TF
17 -- Cabal
18 import Language.Haskell.Extension
19 ( Extension (..)
20 , KnownExtension (..)
21 , Language (..)
24 -- cabal-install
25 import Distribution.Solver.Types.Flag
26 import Distribution.Solver.Types.OptionalStanza
27 import Distribution.Solver.Types.PackageConstraint
28 import qualified Distribution.Solver.Types.PackagePath as P
29 import UnitTests.Distribution.Solver.Modular.DSL
30 import UnitTests.Distribution.Solver.Modular.DSL.TestCaseUtils
32 tests :: [TF.TestTree]
33 tests =
34 [ testGroup
35 "Simple dependencies"
36 [ runTest $ mkTest db1 "alreadyInstalled" ["A"] (solverSuccess [])
37 , runTest $ mkTest db1 "installLatest" ["B"] (solverSuccess [("B", 2)])
38 , runTest $
39 preferOldest $
40 mkTest db1 "installOldest" ["B"] (solverSuccess [("B", 1)])
41 , runTest $ mkTest db1 "simpleDep1" ["C"] (solverSuccess [("B", 1), ("C", 1)])
42 , runTest $ mkTest db1 "simpleDep2" ["D"] (solverSuccess [("B", 2), ("D", 1)])
43 , runTest $ mkTest db1 "failTwoVersions" ["C", "D"] anySolverFailure
44 , runTest $ indep $ mkTest db1 "indepTwoVersions" ["C", "D"] (solverSuccess [("B", 1), ("B", 2), ("C", 1), ("D", 1)])
45 , runTest $ indep $ mkTest db1 "aliasWhenPossible1" ["C", "E"] (solverSuccess [("B", 1), ("C", 1), ("E", 1)])
46 , runTest $ indep $ mkTest db1 "aliasWhenPossible2" ["D", "E"] (solverSuccess [("B", 2), ("D", 1), ("E", 1)])
47 , runTest $ indep $ mkTest db2 "aliasWhenPossible3" ["C", "D"] (solverSuccess [("A", 1), ("A", 2), ("B", 1), ("B", 2), ("C", 1), ("D", 1)])
48 , runTest $ mkTest db1 "buildDepAgainstOld" ["F"] (solverSuccess [("B", 1), ("E", 1), ("F", 1)])
49 , runTest $ mkTest db1 "buildDepAgainstNew" ["G"] (solverSuccess [("B", 2), ("E", 1), ("G", 1)])
50 , runTest $ indep $ mkTest db1 "multipleInstances" ["F", "G"] anySolverFailure
51 , runTest $ mkTest db21 "unknownPackage1" ["A"] (solverSuccess [("A", 1), ("B", 1)])
52 , runTest $ mkTest db22 "unknownPackage2" ["A"] (solverFailure (isInfixOf "unknown package: C"))
53 , runTest $ mkTest db23 "unknownPackage3" ["A"] (solverFailure (isInfixOf "unknown package: B"))
54 , runTest $ mkTest [] "unknown target" ["A"] (solverFailure (isInfixOf "unknown package: A"))
56 , testGroup
57 "Flagged dependencies"
58 [ runTest $ mkTest db3 "forceFlagOn" ["C"] (solverSuccess [("A", 1), ("B", 1), ("C", 1)])
59 , runTest $ mkTest db3 "forceFlagOff" ["D"] (solverSuccess [("A", 2), ("B", 1), ("D", 1)])
60 , runTest $ indep $ mkTest db3 "linkFlags1" ["C", "D"] anySolverFailure
61 , runTest $ indep $ mkTest db4 "linkFlags2" ["C", "D"] anySolverFailure
62 , runTest $ indep $ mkTest db18 "linkFlags3" ["A", "B"] (solverSuccess [("A", 1), ("B", 1), ("C", 1), ("D", 1), ("D", 2), ("F", 1)])
64 , testGroup
65 "Lifting dependencies out of conditionals"
66 [ runTest $ commonDependencyLogMessage "common dependency log message"
67 , runTest $ twoLevelDeepCommonDependencyLogMessage "two level deep common dependency log message"
68 , runTest $ testBackjumpingWithCommonDependency "backjumping with common dependency"
70 , testGroup
71 "Manual flags"
72 [ runTest $
73 mkTest dbManualFlags "Use default value for manual flag" ["pkg"] $
74 solverSuccess [("pkg", 1), ("true-dep", 1)]
75 , let checkFullLog =
76 any $ isInfixOf "rejecting: pkg:-flag (manual flag can only be changed explicitly)"
77 in runTest $
78 setVerbose $
79 constraints [ExVersionConstraint (ScopeAnyQualifier "true-dep") V.noVersion] $
80 mkTest dbManualFlags "Don't toggle manual flag to avoid conflict" ["pkg"] $
81 -- TODO: We should check the summarized log instead of the full log
82 -- for the manual flags error message, but it currently only
83 -- appears in the full log.
84 SolverResult checkFullLog (Left $ const True)
85 , let cs = [ExFlagConstraint (ScopeAnyQualifier "pkg") "flag" False]
86 in runTest $
87 constraints cs $
88 mkTest dbManualFlags "Toggle manual flag with flag constraint" ["pkg"] $
89 solverSuccess [("false-dep", 1), ("pkg", 1)]
91 , testGroup
92 "Qualified manual flag constraints"
93 [ let name = "Top-level flag constraint does not constrain setup dep's flag"
94 cs = [ExFlagConstraint (ScopeQualified P.QualToplevel "B") "flag" False]
95 in runTest $
96 constraints cs $
97 mkTest dbSetupDepWithManualFlag name ["A"] $
98 solverSuccess
99 [ ("A", 1)
100 , ("B", 1)
101 , ("B", 2)
102 , ("b-1-false-dep", 1)
103 , ("b-2-true-dep", 1)
105 , let name = "Solver can toggle setup dep's flag to match top-level constraint"
106 cs =
107 [ ExFlagConstraint (ScopeQualified P.QualToplevel "B") "flag" False
108 , ExVersionConstraint (ScopeAnyQualifier "b-2-true-dep") V.noVersion
110 in runTest $
111 constraints cs $
112 mkTest dbSetupDepWithManualFlag name ["A"] $
113 solverSuccess
114 [ ("A", 1)
115 , ("B", 1)
116 , ("B", 2)
117 , ("b-1-false-dep", 1)
118 , ("b-2-false-dep", 1)
120 , let name = "User can constrain flags separately with qualified constraints"
121 cs =
122 [ ExFlagConstraint (ScopeQualified P.QualToplevel "B") "flag" True
123 , ExFlagConstraint (ScopeQualified (P.QualSetup "A") "B") "flag" False
125 in runTest $
126 constraints cs $
127 mkTest dbSetupDepWithManualFlag name ["A"] $
128 solverSuccess
129 [ ("A", 1)
130 , ("B", 1)
131 , ("B", 2)
132 , ("b-1-true-dep", 1)
133 , ("b-2-false-dep", 1)
135 , -- Regression test for #4299
136 let name = "Solver can link deps when only one has constrained manual flag"
137 cs = [ExFlagConstraint (ScopeQualified P.QualToplevel "B") "flag" False]
138 in runTest $
139 constraints cs $
140 mkTest dbLinkedSetupDepWithManualFlag name ["A"] $
141 solverSuccess [("A", 1), ("B", 1), ("b-1-false-dep", 1)]
142 , let name = "Solver cannot link deps that have conflicting manual flag constraints"
143 cs =
144 [ ExFlagConstraint (ScopeQualified P.QualToplevel "B") "flag" True
145 , ExFlagConstraint (ScopeQualified (P.QualSetup "A") "B") "flag" False
147 failureReason = "(constraint from unknown source requires opposite flag selection)"
148 checkFullLog lns =
150 (\msg -> any (msg `isInfixOf`) lns)
151 [ "rejecting: B:-flag " ++ failureReason
152 , "rejecting: A:setup.B:+flag " ++ failureReason
154 in runTest $
155 constraints cs $
156 setVerbose $
157 mkTest dbLinkedSetupDepWithManualFlag name ["A"] $
158 SolverResult checkFullLog (Left $ const True)
160 , testGroup
161 "Stanzas"
162 [ runTest $ enableAllTests $ mkTest db5 "simpleTest1" ["C"] (solverSuccess [("A", 2), ("C", 1)])
163 , runTest $ enableAllTests $ mkTest db5 "simpleTest2" ["D"] anySolverFailure
164 , runTest $ enableAllTests $ mkTest db5 "simpleTest3" ["E"] (solverSuccess [("A", 1), ("E", 1)])
165 , runTest $ enableAllTests $ mkTest db5 "simpleTest4" ["F"] anySolverFailure -- TODO
166 , runTest $ enableAllTests $ mkTest db5 "simpleTest5" ["G"] (solverSuccess [("A", 2), ("G", 1)])
167 , runTest $ enableAllTests $ mkTest db5 "simpleTest6" ["E", "G"] anySolverFailure
168 , runTest $ indep $ enableAllTests $ mkTest db5 "simpleTest7" ["E", "G"] (solverSuccess [("A", 1), ("A", 2), ("E", 1), ("G", 1)])
169 , runTest $ enableAllTests $ mkTest db6 "depsWithTests1" ["C"] (solverSuccess [("A", 1), ("B", 1), ("C", 1)])
170 , runTest $ indep $ enableAllTests $ mkTest db6 "depsWithTests2" ["C", "D"] (solverSuccess [("A", 1), ("B", 1), ("C", 1), ("D", 1)])
171 , runTest $ testTestSuiteWithFlag "test suite with flag"
173 , testGroup
174 "Setup dependencies"
175 [ runTest $ mkTest db7 "setupDeps1" ["B"] (solverSuccess [("A", 2), ("B", 1)])
176 , runTest $ mkTest db7 "setupDeps2" ["C"] (solverSuccess [("A", 2), ("C", 1)])
177 , runTest $ mkTest db7 "setupDeps3" ["D"] (solverSuccess [("A", 1), ("D", 1)])
178 , runTest $ mkTest db7 "setupDeps4" ["E"] (solverSuccess [("A", 1), ("A", 2), ("E", 1)])
179 , runTest $ mkTest db7 "setupDeps5" ["F"] (solverSuccess [("A", 1), ("A", 2), ("F", 1)])
180 , runTest $ mkTest db8 "setupDeps6" ["C", "D"] (solverSuccess [("A", 1), ("B", 1), ("B", 2), ("C", 1), ("D", 1)])
181 , runTest $ mkTest db9 "setupDeps7" ["F", "G"] (solverSuccess [("A", 1), ("B", 1), ("B", 2), ("C", 1), ("D", 1), ("E", 1), ("E", 2), ("F", 1), ("G", 1)])
182 , runTest $ mkTest db10 "setupDeps8" ["C"] (solverSuccess [("C", 1)])
183 , runTest $ indep $ mkTest dbSetupDeps "setupDeps9" ["A", "B"] (solverSuccess [("A", 1), ("B", 1), ("C", 1), ("D", 1), ("D", 2)])
185 , testGroup
186 "Base shim"
187 [ runTest $ mkTest db11 "baseShim1" ["A"] (solverSuccess [("A", 1)])
188 , runTest $ mkTest db12 "baseShim2" ["A"] (solverSuccess [("A", 1)])
189 , runTest $ mkTest db12 "baseShim3" ["B"] (solverSuccess [("B", 1)])
190 , runTest $ mkTest db12 "baseShim4" ["C"] (solverSuccess [("A", 1), ("B", 1), ("C", 1)])
191 , runTest $ mkTest db12 "baseShim5" ["D"] anySolverFailure
192 , runTest $ mkTest db12 "baseShim6" ["E"] (solverSuccess [("E", 1), ("syb", 2)])
194 , testGroup
195 "Base and non-reinstallable"
196 [ runTest $
197 mkTest dbBase "Refuse to install base without --allow-boot-library-installs" ["base"] $
198 solverFailure (isInfixOf "rejecting: base-1.0.0 (constraint from non-reinstallable package requires installed instance)")
199 , runTest $
200 allowBootLibInstalls $
201 mkTest dbBase "Install base with --allow-boot-library-installs" ["base"] $
202 solverSuccess [("base", 1), ("ghc-prim", 1), ("integer-gmp", 1), ("integer-simple", 1)]
203 , runTest $
204 mkTest dbNonupgrade "Refuse to install newer ghc requested by another library" ["A"] $
205 solverFailure (isInfixOf "rejecting: ghc-2.0.0 (constraint from non-reinstallable package requires installed instance)")
207 , testGroup
208 "reject-unconstrained"
209 [ runTest $
210 onlyConstrained $
211 mkTest db12 "missing syb" ["E"] $
212 solverFailure (isInfixOf "not a user-provided goal")
213 , runTest $
214 onlyConstrained $
215 mkTest db12 "all goals" ["E", "syb"] $
216 solverSuccess [("E", 1), ("syb", 2)]
217 , runTest $
218 onlyConstrained $
219 mkTest db17 "backtracking" ["A", "B"] $
220 solverSuccess [("A", 2), ("B", 1)]
221 , runTest $
222 onlyConstrained $
223 mkTest db17 "failure message" ["A"] $
224 solverFailure $
225 isInfixOf $
226 "Could not resolve dependencies:\n"
227 ++ "[__0] trying: A-3.0.0 (user goal)\n"
228 ++ "[__1] next goal: C (dependency of A)\n"
229 ++ "[__1] fail (not a user-provided goal nor mentioned as a constraint, "
230 ++ "but reject-unconstrained-dependencies was set)\n"
231 ++ "[__1] fail (backjumping, conflict set: A, C)\n"
232 ++ "After searching the rest of the dependency tree exhaustively, "
233 ++ "these were the goals I've had most trouble fulfilling: A, C, B"
235 , testGroup
236 "Cycles"
237 [ runTest $ mkTest db14 "simpleCycle1" ["A"] anySolverFailure
238 , runTest $ mkTest db14 "simpleCycle2" ["A", "B"] anySolverFailure
239 , runTest $ mkTest db14 "cycleWithFlagChoice1" ["C"] (solverSuccess [("C", 1), ("E", 1)])
240 , runTest $ mkTest db15 "cycleThroughSetupDep1" ["A"] anySolverFailure
241 , runTest $ mkTest db15 "cycleThroughSetupDep2" ["B"] anySolverFailure
242 , runTest $ mkTest db15 "cycleThroughSetupDep3" ["C"] (solverSuccess [("C", 2), ("D", 1)])
243 , runTest $ mkTest db15 "cycleThroughSetupDep4" ["D"] (solverSuccess [("D", 1)])
244 , runTest $ mkTest db15 "cycleThroughSetupDep5" ["E"] (solverSuccess [("C", 2), ("D", 1), ("E", 1)])
245 , runTest $ issue4161 "detect cycle between package and its setup script"
246 , runTest $ testCyclicDependencyErrorMessages "cyclic dependency error messages"
248 , testGroup
249 "Extensions"
250 [ runTest $ mkTestExts [EnableExtension CPP] dbExts1 "unsupported" ["A"] anySolverFailure
251 , runTest $ mkTestExts [EnableExtension CPP] dbExts1 "unsupportedIndirect" ["B"] anySolverFailure
252 , runTest $ mkTestExts [EnableExtension RankNTypes] dbExts1 "supported" ["A"] (solverSuccess [("A", 1)])
253 , runTest $ mkTestExts (map EnableExtension [CPP, RankNTypes]) dbExts1 "supportedIndirect" ["C"] (solverSuccess [("A", 1), ("B", 1), ("C", 1)])
254 , runTest $ mkTestExts [EnableExtension CPP] dbExts1 "disabledExtension" ["D"] anySolverFailure
255 , runTest $ mkTestExts (map EnableExtension [CPP, RankNTypes]) dbExts1 "disabledExtension" ["D"] anySolverFailure
256 , runTest $ mkTestExts (UnknownExtension "custom" : map EnableExtension [CPP, RankNTypes]) dbExts1 "supportedUnknown" ["E"] (solverSuccess [("A", 1), ("B", 1), ("C", 1), ("E", 1)])
258 , testGroup
259 "Languages"
260 [ runTest $ mkTestLangs [Haskell98] dbLangs1 "unsupported" ["A"] anySolverFailure
261 , runTest $ mkTestLangs [Haskell98, Haskell2010] dbLangs1 "supported" ["A"] (solverSuccess [("A", 1)])
262 , runTest $ mkTestLangs [Haskell98] dbLangs1 "unsupportedIndirect" ["B"] anySolverFailure
263 , runTest $ mkTestLangs [Haskell98, Haskell2010, UnknownLanguage "Haskell3000"] dbLangs1 "supportedUnknown" ["C"] (solverSuccess [("A", 1), ("B", 1), ("C", 1)])
265 , testGroup
266 "Qualified Package Constraints"
267 [ runTest $
268 mkTest dbConstraints "install latest versions without constraints" ["A", "B", "C"] $
269 solverSuccess [("A", 7), ("B", 8), ("C", 9), ("D", 7), ("D", 8), ("D", 9)]
270 , let cs = [ExVersionConstraint (ScopeAnyQualifier "D") $ mkVersionRange 1 4]
271 in runTest $
272 constraints cs $
273 mkTest dbConstraints "force older versions with unqualified constraint" ["A", "B", "C"] $
274 solverSuccess [("A", 1), ("B", 2), ("C", 3), ("D", 1), ("D", 2), ("D", 3)]
275 , let cs =
276 [ ExVersionConstraint (ScopeQualified P.QualToplevel "D") $ mkVersionRange 1 4
277 , ExVersionConstraint (ScopeQualified (P.QualSetup "B") "D") $ mkVersionRange 4 7
279 in runTest $
280 constraints cs $
281 mkTest dbConstraints "force multiple versions with qualified constraints" ["A", "B", "C"] $
282 solverSuccess [("A", 1), ("B", 5), ("C", 9), ("D", 1), ("D", 5), ("D", 9)]
283 , let cs = [ExVersionConstraint (ScopeAnySetupQualifier "D") $ mkVersionRange 1 4]
284 in runTest $
285 constraints cs $
286 mkTest dbConstraints "constrain package across setup scripts" ["A", "B", "C"] $
287 solverSuccess [("A", 7), ("B", 2), ("C", 3), ("D", 2), ("D", 3), ("D", 7)]
289 , testGroup
290 "Package Preferences"
291 [ runTest $ preferences [ExPkgPref "A" $ mkvrThis 1] $ mkTest db13 "selectPreferredVersionSimple" ["A"] (solverSuccess [("A", 1)])
292 , runTest $ preferences [ExPkgPref "A" $ mkvrOrEarlier 2] $ mkTest db13 "selectPreferredVersionSimple2" ["A"] (solverSuccess [("A", 2)])
293 , runTest
294 $ preferences
295 [ ExPkgPref "A" $ mkvrOrEarlier 2
296 , ExPkgPref "A" $ mkvrOrEarlier 1
298 $ mkTest db13 "selectPreferredVersionMultiple" ["A"] (solverSuccess [("A", 1)])
299 , runTest
300 $ preferences
301 [ ExPkgPref "A" $ mkvrOrEarlier 1
302 , ExPkgPref "A" $ mkvrOrEarlier 2
304 $ mkTest db13 "selectPreferredVersionMultiple2" ["A"] (solverSuccess [("A", 1)])
305 , runTest
306 $ preferences
307 [ ExPkgPref "A" $ mkvrThis 1
308 , ExPkgPref "A" $ mkvrThis 2
310 $ mkTest db13 "selectPreferredVersionMultiple3" ["A"] (solverSuccess [("A", 2)])
311 , runTest
312 $ preferences
313 [ ExPkgPref "A" $ mkvrThis 1
314 , ExPkgPref "A" $ mkvrOrEarlier 2
316 $ mkTest db13 "selectPreferredVersionMultiple4" ["A"] (solverSuccess [("A", 1)])
318 , testGroup
319 "Stanza Preferences"
320 [ runTest $
321 mkTest dbStanzaPreferences1 "disable tests by default" ["pkg"] $
322 solverSuccess [("pkg", 1)]
323 , runTest $
324 preferences [ExStanzaPref "pkg" [TestStanzas]] $
325 mkTest dbStanzaPreferences1 "enable tests with testing preference" ["pkg"] $
326 solverSuccess [("pkg", 1), ("test-dep", 1)]
327 , runTest $
328 preferences [ExStanzaPref "pkg" [TestStanzas]] $
329 mkTest dbStanzaPreferences2 "disable testing when it's not possible" ["pkg"] $
330 solverSuccess [("pkg", 1)]
331 , testStanzaPreference "test stanza preference"
333 , testGroup
334 "Buildable Field"
335 [ testBuildable "avoid building component with unknown dependency" (ExAny "unknown")
336 , testBuildable "avoid building component with unknown extension" (ExExt (UnknownExtension "unknown"))
337 , testBuildable "avoid building component with unknown language" (ExLang (UnknownLanguage "unknown"))
338 , runTest $ mkTest dbBuildable1 "choose flags that set buildable to false" ["pkg"] (solverSuccess [("flag1-false", 1), ("flag2-true", 1), ("pkg", 1)])
339 , runTest $ mkTest dbBuildable2 "choose version that sets buildable to false" ["A"] (solverSuccess [("A", 1), ("B", 2)])
341 , testGroup
342 "Pkg-config dependencies"
343 [ runTest $ mkTestPCDepends (Just []) dbPC1 "noPkgs" ["A"] anySolverFailure
344 , runTest $ mkTestPCDepends (Just [("pkgA", "0")]) dbPC1 "tooOld" ["A"] anySolverFailure
345 , runTest $ mkTestPCDepends (Just [("pkgA", "1.0.0"), ("pkgB", "1.0.0")]) dbPC1 "pruneNotFound" ["C"] (solverSuccess [("A", 1), ("B", 1), ("C", 1)])
346 , runTest $ mkTestPCDepends (Just [("pkgA", "1.0.0"), ("pkgB", "2.0.0")]) dbPC1 "chooseNewest" ["C"] (solverSuccess [("A", 1), ("B", 2), ("C", 1)])
347 , runTest $ mkTestPCDepends Nothing dbPC1 "noPkgConfigFailure" ["A"] anySolverFailure
348 , runTest $ mkTestPCDepends Nothing dbPC1 "noPkgConfigSuccess" ["D"] (solverSuccess [("D", 1)])
350 , testGroup
351 "Independent goals"
352 [ runTest $ indep $ mkTest db16 "indepGoals1" ["A", "B"] (solverSuccess [("A", 1), ("B", 1), ("C", 1), ("D", 1), ("D", 2), ("E", 1)])
353 , runTest $ testIndepGoals2 "indepGoals2"
354 , runTest $ testIndepGoals3 "indepGoals3"
355 , runTest $ testIndepGoals4 "indepGoals4"
356 , runTest $ testIndepGoals5 "indepGoals5 - fixed goal order" FixedGoalOrder
357 , runTest $ testIndepGoals5 "indepGoals5 - default goal order" DefaultGoalOrder
358 , runTest $ testIndepGoals6 "indepGoals6 - fixed goal order" FixedGoalOrder
359 , runTest $ testIndepGoals6 "indepGoals6 - default goal order" DefaultGoalOrder
361 , -- Tests designed for the backjumping blog post
362 testGroup
363 "Backjumping"
364 [ runTest $ mkTest dbBJ1a "bj1a" ["A"] (solverSuccess [("A", 1), ("B", 1)])
365 , runTest $ mkTest dbBJ1b "bj1b" ["A"] (solverSuccess [("A", 1), ("B", 1)])
366 , runTest $ mkTest dbBJ1c "bj1c" ["A"] (solverSuccess [("A", 1), ("B", 1)])
367 , runTest $ mkTest dbBJ2 "bj2" ["A"] (solverSuccess [("A", 1), ("B", 1), ("C", 1)])
368 , runTest $ mkTest dbBJ3 "bj3" ["A"] (solverSuccess [("A", 1), ("Ba", 1), ("C", 1)])
369 , runTest $ mkTest dbBJ4 "bj4" ["A"] (solverSuccess [("A", 1), ("B", 1), ("C", 1)])
370 , runTest $ mkTest dbBJ5 "bj5" ["A"] (solverSuccess [("A", 1), ("B", 1), ("D", 1)])
371 , runTest $ mkTest dbBJ6 "bj6" ["A"] (solverSuccess [("A", 1), ("B", 1)])
372 , runTest $ mkTest dbBJ7 "bj7" ["A"] (solverSuccess [("A", 1), ("B", 1), ("C", 1)])
373 , runTest $ indep $ mkTest dbBJ8 "bj8" ["A", "B"] (solverSuccess [("A", 1), ("B", 1), ("C", 1)])
375 , testGroup
376 "main library dependencies"
377 [ let db = [Right $ exAvNoLibrary "A" 1 `withExe` exExe "exe" []]
378 in runTest $
379 mkTest db "install build target without a library" ["A"] $
380 solverSuccess [("A", 1)]
381 , let db =
382 [ Right $ exAv "A" 1 [ExAny "B"]
383 , Right $ exAvNoLibrary "B" 1 `withExe` exExe "exe" []
385 in runTest $
386 mkTest db "reject build-depends dependency with no library" ["A"] $
387 solverFailure (isInfixOf "rejecting: B-1.0.0 (does not contain library, which is required by A)")
388 , let exe = exExe "exe" []
389 db =
390 [ Right $ exAv "A" 1 [ExAny "B"]
391 , Right $ exAvNoLibrary "B" 2 `withExe` exe
392 , Right $ exAv "B" 1 [] `withExe` exe
394 in runTest $
395 mkTest db "choose version of build-depends dependency that has a library" ["A"] $
396 solverSuccess [("A", 1), ("B", 1)]
398 , testGroup
399 "sub-library dependencies"
400 [ let db =
401 [ Right $ exAv "A" 1 [ExSubLibAny "B" "sub-lib"]
402 , Right $ exAv "B" 1 []
404 in runTest $
405 mkTest db "reject package that is missing required sub-library" ["A"] $
406 solverFailure $
407 isInfixOf $
408 "rejecting: B-1.0.0 (does not contain library 'sub-lib', which is required by A)"
409 , let db =
410 [ Right $ exAv "A" 1 [ExSubLibAny "B" "sub-lib"]
411 , Right $ exAvNoLibrary "B" 1 `withSubLibrary` exSubLib "sub-lib" []
413 in runTest $
414 mkTest db "reject package with private but required sub-library" ["A"] $
415 solverFailure $
416 isInfixOf $
417 "rejecting: B-1.0.0 (library 'sub-lib' is private, but it is required by A)"
418 , let db =
419 [ Right $ exAv "A" 1 [ExSubLibAny "B" "sub-lib"]
420 , Right $
421 exAvNoLibrary "B" 1
422 `withSubLibrary` exSubLib "sub-lib" [ExFlagged "make-lib-private" (dependencies []) publicDependencies]
424 in runTest $
425 constraints [ExFlagConstraint (ScopeAnyQualifier "B") "make-lib-private" True] $
426 mkTest db "reject package with sub-library made private by flag constraint" ["A"] $
427 solverFailure $
428 isInfixOf $
429 "rejecting: B-1.0.0 (library 'sub-lib' is private, but it is required by A)"
430 , let db =
431 [ Right $ exAv "A" 1 [ExSubLibAny "B" "sub-lib"]
432 , Right $
433 exAvNoLibrary "B" 1
434 `withSubLibrary` exSubLib "sub-lib" [ExFlagged "make-lib-private" (dependencies []) publicDependencies]
436 in runTest $
437 mkTest db "treat sub-library as visible even though flag choice could make it private" ["A"] $
438 solverSuccess [("A", 1), ("B", 1)]
439 , let db =
440 [ Right $ exAv "A" 1 [ExAny "B"]
441 , Right $ exAv "B" 1 [] `withSubLibrary` exSubLib "sub-lib" []
442 , Right $ exAv "C" 1 [ExSubLibAny "B" "sub-lib"]
444 goals :: [ExampleVar]
445 goals =
446 [ P QualNone "A"
447 , P QualNone "B"
448 , P QualNone "C"
450 in runTest $
451 goalOrder goals $
452 mkTest db "reject package that requires a private sub-library" ["A", "C"] $
453 solverFailure $
454 isInfixOf $
455 "rejecting: C-1.0.0 (requires library 'sub-lib' from B, but the component is private)"
456 , let db =
457 [ Right $ exAv "A" 1 [ExSubLibAny "B" "sub-lib-v1"]
458 , Right $ exAv "B" 2 [] `withSubLibrary` ExSubLib "sub-lib-v2" publicDependencies
459 , Right $ exAv "B" 1 [] `withSubLibrary` ExSubLib "sub-lib-v1" publicDependencies
461 in runTest $
462 mkTest db "choose version of package containing correct sub-library" ["A"] $
463 solverSuccess [("A", 1), ("B", 1)]
464 , let db =
465 [ Right $ exAv "A" 1 [ExSubLibAny "B" "sub-lib"]
466 , Right $ exAv "B" 2 [] `withSubLibrary` ExSubLib "sub-lib" (dependencies [])
467 , Right $ exAv "B" 1 [] `withSubLibrary` ExSubLib "sub-lib" publicDependencies
469 in runTest $
470 mkTest db "choose version of package with public sub-library" ["A"] $
471 solverSuccess [("A", 1), ("B", 1)]
473 , -- build-tool-depends dependencies
474 testGroup
475 "build-tool-depends"
476 [ runTest $ mkTest dbBuildTools "simple exe dependency" ["A"] (solverSuccess [("A", 1), ("bt-pkg", 2)])
477 , runTest $
478 disableSolveExecutables $
479 mkTest dbBuildTools "don't install build tool packages in legacy mode" ["A"] (solverSuccess [("A", 1)])
480 , runTest $ mkTest dbBuildTools "flagged exe dependency" ["B"] (solverSuccess [("B", 1), ("bt-pkg", 2)])
481 , runTest $
482 enableAllTests $
483 mkTest dbBuildTools "test suite exe dependency" ["C"] (solverSuccess [("C", 1), ("bt-pkg", 2)])
484 , runTest $
485 mkTest dbBuildTools "unknown exe" ["D"] $
486 solverFailure (isInfixOf "does not contain executable 'unknown-exe', which is required by D")
487 , runTest $
488 disableSolveExecutables $
489 mkTest dbBuildTools "don't check for build tool executables in legacy mode" ["D"] $
490 solverSuccess [("D", 1)]
491 , runTest $
492 mkTest dbBuildTools "unknown build tools package error mentions package, not exe" ["E"] $
493 solverFailure (isInfixOf "unknown package: E:unknown-pkg:exe.unknown-pkg (dependency of E)")
494 , runTest $
495 mkTest dbBuildTools "unknown flagged exe" ["F"] $
496 solverFailure (isInfixOf "does not contain executable 'unknown-exe', which is required by F +flagF")
497 , runTest $
498 enableAllTests $
499 mkTest dbBuildTools "unknown test suite exe" ["G"] $
500 solverFailure (isInfixOf "does not contain executable 'unknown-exe', which is required by G *test")
501 , runTest $
502 mkTest dbBuildTools "wrong exe for build tool package version" ["H"] $
503 solverFailure $
504 isInfixOf $
505 -- The solver reports the version conflict when a version conflict
506 -- and an executable conflict apply to the same package version.
507 "[__1] rejecting: H:bt-pkg:exe.bt-pkg-4.0.0 (conflict: H => H:bt-pkg:exe.bt-pkg (exe exe1)==3.0.0)\n"
508 ++ "[__1] rejecting: H:bt-pkg:exe.bt-pkg-3.0.0 (does not contain executable 'exe1', which is required by H)\n"
509 ++ "[__1] rejecting: H:bt-pkg:exe.bt-pkg-2.0.0 (conflict: H => H:bt-pkg:exe.bt-pkg (exe exe1)==3.0.0)"
510 , runTest $ chooseExeAfterBuildToolsPackage True "choose exe after choosing its package - success"
511 , runTest $ chooseExeAfterBuildToolsPackage False "choose exe after choosing its package - failure"
512 , runTest $ rejectInstalledBuildToolPackage "reject installed package for build-tool dependency"
513 , runTest $ requireConsistentBuildToolVersions "build tool versions must be consistent within one package"
515 , -- build-tools dependencies
516 testGroup
517 "legacy build-tools"
518 [ runTest $ mkTest dbLegacyBuildTools1 "bt1" ["A"] (solverSuccess [("A", 1), ("alex", 1)])
519 , runTest $
520 disableSolveExecutables $
521 mkTest dbLegacyBuildTools1 "bt1 - don't install build tool packages in legacy mode" ["A"] (solverSuccess [("A", 1)])
522 , runTest $
523 mkTest dbLegacyBuildTools2 "bt2" ["A"] $
524 solverFailure (isInfixOf "does not contain executable 'alex', which is required by A")
525 , runTest $
526 disableSolveExecutables $
527 mkTest dbLegacyBuildTools2 "bt2 - don't check for build tool executables in legacy mode" ["A"] (solverSuccess [("A", 1)])
528 , runTest $ mkTest dbLegacyBuildTools3 "bt3" ["A"] (solverSuccess [("A", 1)])
529 , runTest $ mkTest dbLegacyBuildTools4 "bt4" ["C"] (solverSuccess [("A", 1), ("B", 1), ("C", 1), ("alex", 1), ("alex", 2)])
530 , runTest $ mkTest dbLegacyBuildTools5 "bt5" ["B"] (solverSuccess [("A", 1), ("A", 2), ("B", 1), ("alex", 1)])
531 , runTest $ mkTest dbLegacyBuildTools6 "bt6" ["A"] (solverSuccess [("A", 1), ("alex", 1), ("happy", 1)])
533 , -- internal dependencies
534 testGroup
535 "internal dependencies"
536 [ runTest $ mkTest dbIssue3775 "issue #3775" ["B"] (solverSuccess [("A", 2), ("B", 2), ("warp", 1)])
538 , -- tests for partial fix for issue #5325
539 testGroup "Components that are unbuildable in the current environment" $
540 let flagConstraint = ExFlagConstraint . ScopeAnyQualifier
541 in [ let db = [Right $ exAv "A" 1 [ExFlagged "build-lib" (dependencies []) unbuildableDependencies]]
542 in runTest $
543 constraints [flagConstraint "A" "build-lib" False] $
544 mkTest db "install unbuildable library" ["A"] $
545 solverSuccess [("A", 1)]
546 , let db =
547 [ Right $
548 exAvNoLibrary "A" 1
549 `withExe` exExe "exe" [ExFlagged "build-exe" (dependencies []) unbuildableDependencies]
551 in runTest $
552 constraints [flagConstraint "A" "build-exe" False] $
553 mkTest db "install unbuildable exe" ["A"] $
554 solverSuccess [("A", 1)]
555 , let db =
556 [ Right $ exAv "A" 1 [ExAny "B"]
557 , Right $ exAv "B" 1 [ExFlagged "build-lib" (dependencies []) unbuildableDependencies]
559 in runTest $
560 constraints [flagConstraint "B" "build-lib" False] $
561 mkTest db "reject library dependency with unbuildable library" ["A"] $
562 solverFailure $
563 isInfixOf $
564 "rejecting: B-1.0.0 (library is not buildable in the "
565 ++ "current environment, but it is required by A)"
566 , let db =
567 [ Right $ exAv "A" 1 [ExBuildToolAny "B" "bt"]
568 , Right $
569 exAv "B" 1 [ExFlagged "build-lib" (dependencies []) unbuildableDependencies]
570 `withExe` exExe "bt" []
572 in runTest $
573 constraints [flagConstraint "B" "build-lib" False] $
574 mkTest db "allow build-tool dependency with unbuildable library" ["A"] $
575 solverSuccess [("A", 1), ("B", 1)]
576 , let db =
577 [ Right $ exAv "A" 1 [ExBuildToolAny "B" "bt"]
578 , Right $
579 exAv "B" 1 []
580 `withExe` exExe "bt" [ExFlagged "build-exe" (dependencies []) unbuildableDependencies]
582 in runTest $
583 constraints [flagConstraint "B" "build-exe" False] $
584 mkTest db "reject build-tool dependency with unbuildable exe" ["A"] $
585 solverFailure $
586 isInfixOf $
587 "rejecting: A:B:exe.B-1.0.0 (executable 'bt' is not "
588 ++ "buildable in the current environment, but it is required by A)"
589 , runTest $
590 chooseUnbuildableExeAfterBuildToolsPackage
591 "choose unbuildable exe after choosing its package"
593 , testGroup
594 "--fine-grained-conflicts"
595 [ -- Skipping a version because of a problematic dependency:
597 -- When the solver explores A-4, it finds that it cannot satisfy B's
598 -- dependencies. This allows the solver to skip the subsequent
599 -- versions of A that also depend on B.
600 runTest $
601 let db =
602 [ Right $ exAv "A" 4 [ExAny "B"]
603 , Right $ exAv "A" 3 [ExAny "B"]
604 , Right $ exAv "A" 2 [ExAny "B"]
605 , Right $ exAv "A" 1 []
606 , Right $ exAv "B" 2 [ExAny "unknown1"]
607 , Right $ exAv "B" 1 [ExAny "unknown2"]
609 msg =
610 [ "[__0] trying: A-4.0.0 (user goal)"
611 , "[__1] trying: B-2.0.0 (dependency of A)"
612 , "[__2] unknown package: unknown1 (dependency of B)"
613 , "[__2] fail (backjumping, conflict set: B, unknown1)"
614 , "[__1] trying: B-1.0.0"
615 , "[__2] unknown package: unknown2 (dependency of B)"
616 , "[__2] fail (backjumping, conflict set: B, unknown2)"
617 , "[__1] fail (backjumping, conflict set: A, B, unknown1, unknown2)"
618 , "[__0] skipping: A; 3.0.0, 2.0.0 (has the same characteristics that "
619 ++ "caused the previous version to fail: depends on 'B')"
620 , "[__0] trying: A-1.0.0"
621 , "[__1] done"
623 in setVerbose $
624 mkTest db "skip version due to problematic dependency" ["A"] $
625 SolverResult (isInfixOf msg) $
626 Right [("A", 1)]
627 , -- Skipping a version because of a restrictive constraint on a
628 -- dependency:
630 -- The solver rejects A-4 because its constraint on B excludes B-1.
631 -- Then the solver is able to skip A-3 and A-2 because they also
632 -- exclude B-1, even though they don't have the exact same constraints
633 -- on B.
634 runTest $
635 let db =
636 [ Right $ exAv "A" 4 [ExFix "B" 14]
637 , Right $ exAv "A" 3 [ExFix "B" 13]
638 , Right $ exAv "A" 2 [ExFix "B" 12]
639 , Right $ exAv "A" 1 [ExFix "B" 11]
640 , Right $ exAv "B" 11 []
642 msg =
643 [ "[__0] trying: A-4.0.0 (user goal)"
644 , "[__1] next goal: B (dependency of A)"
645 , "[__1] rejecting: B-11.0.0 (conflict: A => B==14.0.0)"
646 , "[__1] fail (backjumping, conflict set: A, B)"
647 , "[__0] skipping: A; 3.0.0, 2.0.0 (has the same characteristics that "
648 ++ "caused the previous version to fail: depends on 'B' but excludes "
649 ++ "version 11.0.0)"
650 , "[__0] trying: A-1.0.0"
651 , "[__1] next goal: B (dependency of A)"
652 , "[__1] trying: B-11.0.0"
653 , "[__2] done"
655 in setVerbose $
656 mkTest db "skip version due to restrictive constraint on its dependency" ["A"] $
657 SolverResult (isInfixOf msg) $
658 Right [("A", 1), ("B", 11)]
659 , -- This test tests the case where the solver chooses a version for one
660 -- package, B, before choosing a version for one of its reverse
661 -- dependencies, C. While the solver is exploring the subtree rooted
662 -- at B-3, it finds that C-2's dependency on B conflicts with B-3.
663 -- Then the solver is able to skip C-1, because it also excludes B-3.
665 -- --fine-grained-conflicts could have a benefit in this case even
666 -- though the solver would have found the conflict between B-3 and C-1
667 -- immediately after trying C-1 anyway. It prevents C-1 from
668 -- introducing any other conflicts which could increase the size of
669 -- the conflict set.
670 runTest $
671 let db =
672 [ Right $ exAv "A" 1 [ExAny "B", ExAny "C"]
673 , Right $ exAv "B" 3 []
674 , Right $ exAv "B" 2 []
675 , Right $ exAv "B" 1 []
676 , Right $ exAv "C" 2 [ExFix "B" 2]
677 , Right $ exAv "C" 1 [ExFix "B" 1]
679 goals = [P QualNone pkg | pkg <- ["A", "B", "C"]]
680 expectedMsg =
681 [ "[__0] trying: A-1.0.0 (user goal)"
682 , "[__1] trying: B-3.0.0 (dependency of A)"
683 , "[__2] next goal: C (dependency of A)"
684 , "[__2] rejecting: C-2.0.0 (conflict: B==3.0.0, C => B==2.0.0)"
685 , "[__2] skipping: C-1.0.0 (has the same characteristics that caused the "
686 ++ "previous version to fail: excludes 'B' version 3.0.0)"
687 , "[__2] fail (backjumping, conflict set: A, B, C)"
688 , "[__1] trying: B-2.0.0"
689 , "[__2] next goal: C (dependency of A)"
690 , "[__2] trying: C-2.0.0"
691 , "[__3] done"
693 in setVerbose $
694 goalOrder goals $
695 mkTest db "skip version that excludes dependency that was already chosen" ["A"] $
696 SolverResult (isInfixOf expectedMsg) $
697 Right [("A", 1), ("B", 2), ("C", 2)]
698 , -- This test tests how the solver merges conflicts when it has
699 -- multiple reasons to add a variable to the conflict set. In this
700 -- case, package A conflicts with B and C. The solver should take the
701 -- union of the conflicts and then only skip a version if it does not
702 -- resolve any of the conflicts.
704 -- The solver rejects A-3 because it can't find consistent versions for
705 -- its two dependencies, B and C. Then it skips A-2 because A-2 also
706 -- depends on B and C. This test ensures that the solver considers
707 -- A-1 even though A-1 only resolves one of the conflicts (A-1 removes
708 -- the dependency on C).
709 runTest $
710 let db =
711 [ Right $ exAv "A" 3 [ExAny "B", ExAny "C"]
712 , Right $ exAv "A" 2 [ExAny "B", ExAny "C"]
713 , Right $ exAv "A" 1 [ExAny "B"]
714 , Right $ exAv "B" 1 [ExFix "D" 1]
715 , Right $ exAv "C" 1 [ExFix "D" 2]
716 , Right $ exAv "D" 1 []
717 , Right $ exAv "D" 2 []
719 goals = [P QualNone pkg | pkg <- ["A", "B", "C", "D"]]
720 msg =
721 [ "[__0] trying: A-3.0.0 (user goal)"
722 , "[__1] trying: B-1.0.0 (dependency of A)"
723 , "[__2] trying: C-1.0.0 (dependency of A)"
724 , "[__3] next goal: D (dependency of B)"
725 , "[__3] rejecting: D-2.0.0 (conflict: B => D==1.0.0)"
726 , "[__3] rejecting: D-1.0.0 (conflict: C => D==2.0.0)"
727 , "[__3] fail (backjumping, conflict set: B, C, D)"
728 , "[__2] fail (backjumping, conflict set: A, B, C, D)"
729 , "[__1] fail (backjumping, conflict set: A, B, C, D)"
730 , "[__0] skipping: A-2.0.0 (has the same characteristics that caused the "
731 ++ "previous version to fail: depends on 'B'; depends on 'C')"
732 , "[__0] trying: A-1.0.0"
733 , "[__1] trying: B-1.0.0 (dependency of A)"
734 , "[__2] next goal: D (dependency of B)"
735 , "[__2] rejecting: D-2.0.0 (conflict: B => D==1.0.0)"
736 , "[__2] trying: D-1.0.0"
737 , "[__3] done"
739 in setVerbose $
740 goalOrder goals $
741 mkTest db "only skip a version if it resolves none of the previous conflicts" ["A"] $
742 SolverResult (isInfixOf msg) $
743 Right [("A", 1), ("B", 1), ("D", 1)]
744 , -- This test ensures that the solver log doesn't show all conflicts
745 -- that the solver encountered in a subtree. The solver should only
746 -- show the conflicts that are contained in the current conflict set.
748 -- The goal order forces the solver to try A-4, encounter a conflict
749 -- with B-2, try B-1, and then try C. A-4 conflicts with the only
750 -- version of C, so the solver backjumps with a conflict set of
751 -- {A, C}. When the solver skips the next version of A, the log should
752 -- mention the conflict with C but not B.
753 runTest $
754 let db =
755 [ Right $ exAv "A" 4 [ExFix "B" 1, ExFix "C" 1]
756 , Right $ exAv "A" 3 [ExFix "B" 1, ExFix "C" 1]
757 , Right $ exAv "A" 2 [ExFix "C" 1]
758 , Right $ exAv "A" 1 [ExFix "C" 2]
759 , Right $ exAv "B" 2 []
760 , Right $ exAv "B" 1 []
761 , Right $ exAv "C" 2 []
763 goals = [P QualNone pkg | pkg <- ["A", "B", "C"]]
764 msg =
765 [ "[__0] trying: A-4.0.0 (user goal)"
766 , "[__1] next goal: B (dependency of A)"
767 , "[__1] rejecting: B-2.0.0 (conflict: A => B==1.0.0)"
768 , "[__1] trying: B-1.0.0"
769 , "[__2] next goal: C (dependency of A)"
770 , "[__2] rejecting: C-2.0.0 (conflict: A => C==1.0.0)"
771 , "[__2] fail (backjumping, conflict set: A, C)"
772 , "[__0] skipping: A; 3.0.0, 2.0.0 (has the same characteristics that caused the "
773 ++ "previous version to fail: depends on 'C' but excludes version 2.0.0)"
774 , "[__0] trying: A-1.0.0"
775 , "[__1] next goal: C (dependency of A)"
776 , "[__1] trying: C-2.0.0"
777 , "[__2] done"
779 in setVerbose $
780 goalOrder goals $
781 mkTest db "don't show conflicts that aren't part of the conflict set" ["A"] $
782 SolverResult (isInfixOf msg) $
783 Right [("A", 1), ("C", 2)]
784 , -- Tests that the conflict set is properly updated when a version is
785 -- skipped due to being excluded by one of its reverse dependencies'
786 -- constraints.
787 runTest $
788 let db =
789 [ Right $ exAv "A" 2 [ExFix "B" 3]
790 , Right $ exAv "A" 1 [ExFix "B" 1]
791 , Right $ exAv "B" 2 []
792 , Right $ exAv "B" 1 []
794 msg =
795 [ "[__0] trying: A-2.0.0 (user goal)"
796 , "[__1] next goal: B (dependency of A)"
797 , -- During this step, the solver adds A and B to the
798 -- conflict set, with the details of each package's
799 -- conflict:
801 -- A: A's constraint rejected B-2.
802 -- B: B was rejected by A's B==3 constraint
803 "[__1] rejecting: B-2.0.0 (conflict: A => B==3.0.0)"
804 , -- When the solver skips B-1, it cannot simply reuse the
805 -- previous conflict set. It also needs to update A's
806 -- entry to say that A also rejected B-1. Otherwise, the
807 -- solver wouldn't know that A-1 could resolve one of
808 -- the conflicts encountered while exploring A-2. The
809 -- solver would skip A-1, even though it leads to the
810 -- solution.
811 "[__1] skipping: B-1.0.0 (has the same characteristics that caused "
812 ++ "the previous version to fail: excluded by constraint '==3.0.0' from 'A')"
813 , "[__1] fail (backjumping, conflict set: A, B)"
814 , "[__0] trying: A-1.0.0"
815 , "[__1] next goal: B (dependency of A)"
816 , "[__1] rejecting: B-2.0.0 (conflict: A => B==1.0.0)"
817 , "[__1] trying: B-1.0.0"
818 , "[__2] done"
820 in setVerbose $
821 mkTest db "update conflict set after skipping version - 1" ["A"] $
822 SolverResult (isInfixOf msg) $
823 Right [("A", 1), ("B", 1)]
824 , -- Tests that the conflict set is properly updated when a version is
825 -- skipped due to excluding a version of one of its dependencies.
826 -- This test is similar the previous one, with the goal order reversed.
827 runTest $
828 let db =
829 [ Right $ exAv "A" 2 []
830 , Right $ exAv "A" 1 []
831 , Right $ exAv "B" 2 [ExFix "A" 3]
832 , Right $ exAv "B" 1 [ExFix "A" 1]
834 goals = [P QualNone pkg | pkg <- ["A", "B"]]
835 msg =
836 [ "[__0] trying: A-2.0.0 (user goal)"
837 , "[__1] next goal: B (user goal)"
838 , "[__1] rejecting: B-2.0.0 (conflict: A==2.0.0, B => A==3.0.0)"
839 , "[__1] skipping: B-1.0.0 (has the same characteristics that caused "
840 ++ "the previous version to fail: excludes 'A' version 2.0.0)"
841 , "[__1] fail (backjumping, conflict set: A, B)"
842 , "[__0] trying: A-1.0.0"
843 , "[__1] next goal: B (user goal)"
844 , "[__1] rejecting: B-2.0.0 (conflict: A==1.0.0, B => A==3.0.0)"
845 , "[__1] trying: B-1.0.0"
846 , "[__2] done"
848 in setVerbose $
849 goalOrder goals $
850 mkTest db "update conflict set after skipping version - 2" ["A", "B"] $
851 SolverResult (isInfixOf msg) $
852 Right [("A", 1), ("B", 1)]
854 , -- Tests for the contents of the solver's log
855 testGroup
856 "Solver log"
857 [ -- See issue #3203. The solver should only choose a version for A once.
858 runTest $
859 let db = [Right $ exAv "A" 1 []]
861 p :: [String] -> Bool
862 p lg =
863 elem "targets: A" lg
864 && length (filter ("trying: A" `isInfixOf`) lg) == 1
865 in setVerbose $
866 mkTest db "deduplicate targets" ["A", "A"] $
867 SolverResult p $
868 Right [("A", 1)]
869 , runTest $
870 let db = [Right $ exAv "A" 1 [ExAny "B"]]
871 msg =
872 "After searching the rest of the dependency tree exhaustively, "
873 ++ "these were the goals I've had most trouble fulfilling: A, B"
874 in mkTest db "exhaustive search failure message" ["A"] $
875 solverFailure (isInfixOf msg)
876 , testSummarizedLog "show conflicts from final conflict set after exhaustive search" Nothing $
877 "Could not resolve dependencies:\n"
878 ++ "[__0] trying: A-1.0.0 (user goal)\n"
879 ++ "[__1] unknown package: F (dependency of A)\n"
880 ++ "[__1] fail (backjumping, conflict set: A, F)\n"
881 ++ "After searching the rest of the dependency tree exhaustively, "
882 ++ "these were the goals I've had most trouble fulfilling: A, F"
883 , testSummarizedLog "show first conflicts after inexhaustive search" (Just 3) $
884 "Could not resolve dependencies:\n"
885 ++ "[__0] trying: A-1.0.0 (user goal)\n"
886 ++ "[__1] trying: B-3.0.0 (dependency of A)\n"
887 ++ "[__2] unknown package: C (dependency of B)\n"
888 ++ "[__2] fail (backjumping, conflict set: B, C)\n"
889 ++ "Backjump limit reached (currently 3, change with --max-backjumps "
890 ++ "or try to run with --reorder-goals).\n"
891 , testSummarizedLog "don't show summarized log when backjump limit is too low" (Just 1) $
892 "Backjump limit reached (currently 1, change with --max-backjumps "
893 ++ "or try to run with --reorder-goals).\n"
894 ++ "Failed to generate a summarized dependency solver log due to low backjump limit."
895 , testMinimizeConflictSet
896 "minimize conflict set with --minimize-conflict-set"
897 , testNoMinimizeConflictSet
898 "show original conflict set with --no-minimize-conflict-set"
899 , runTest $
900 let db =
901 [ Right $ exAv "my-package" 1 [ExFix "other-package" 3]
902 , Left $ exInst "other-package" 2 "other-package-2.0.0" []
904 msg = "rejecting: other-package-2.0.0/installed-2.0.0"
905 in mkTest db "show full installed package version (issue #5892)" ["my-package"] $
906 solverFailure (isInfixOf msg)
907 , runTest $
908 let db =
909 [ Right $ exAv "my-package" 1 [ExFix "other-package" 3]
910 , Left $ exInst "other-package" 2 "other-package-AbCdEfGhIj0123456789" []
912 msg = "rejecting: other-package-2.0.0/installed-AbCdEfGhIj0123456789"
913 in mkTest db "show full installed package ABI hash (issue #5892)" ["my-package"] $
914 solverFailure (isInfixOf msg)
915 , testGroup
916 "package versions abbreviation (issue #9559.)"
917 [ runTest $
918 let db =
919 [ Right $ exAv "A" 1 []
920 , Right $ exAv "A" 2 []
921 , Right $ exAv "B" 1 [ExFix "A" 3]
923 rejecting = "rejecting: A-2.0.0"
924 skipping = "skipping: A-1.0.0"
925 in mkTest db "show skipping singleton" ["B"] $
926 solverFailure (\msg -> rejecting `isInfixOf` msg && skipping `isInfixOf` msg)
927 , runTest $
928 let db =
929 [ Left $ exInst "A" 1 "A-1.0.0" []
930 , Left $ exInst "A" 2 "A-2.0.0" []
931 , Right $ exAv "B" 1 [ExFix "A" 3]
933 rejecting = "rejecting: A-2.0.0"
934 skipping = "skipping: A-1.0.0"
935 in mkTest db "show skipping singleton, installed" ["B"] $
936 solverFailure (\msg -> rejecting `isInfixOf` msg && skipping `isInfixOf` msg)
937 , runTest $
938 let db =
939 [ Right $ exAv "A" 1 []
940 , Right $ exAv "A" 2 []
941 , Right $ exAv "A" 3 []
942 , Right $ exAv "B" 1 [ExFix "A" 4]
944 rejecting = "rejecting: A-3.0.0"
945 skipping = "skipping: A; 2.0.0, 1.0.0"
946 in mkTest db "show skipping versions list" ["B"] $
947 solverFailure (\msg -> rejecting `isInfixOf` msg && skipping `isInfixOf` msg)
948 , runTest $
949 let db =
950 [ Left $ exInst "A" 1 "A-1.0.0" []
951 , Left $ exInst "A" 2 "A-2.0.0" []
952 , Left $ exInst "A" 3 "A-3.0.0" []
953 , Right $ exAv "B" 1 [ExFix "A" 4]
955 rejecting = "rejecting: A-3.0.0"
956 skipping = "skipping: A-2.0.0/installed-2.0.0, A-1.0.0/installed-1.0.0"
957 in mkTest db "show skipping versions list, installed" ["B"] $
958 solverFailure (\msg -> rejecting `isInfixOf` msg && skipping `isInfixOf` msg)
962 where
963 indep = independentGoals
964 mkvrThis = V.thisVersion . makeV
965 mkvrOrEarlier = V.orEarlierVersion . makeV
966 makeV v = V.mkVersion [v, 0, 0]
968 data GoalOrder = FixedGoalOrder | DefaultGoalOrder
970 {-------------------------------------------------------------------------------
971 Specific example database for the tests
972 -------------------------------------------------------------------------------}
974 db1 :: ExampleDb
975 db1 =
976 let a = exInst "A" 1 "A-1" []
977 in [ Left a
978 , Right $ exAv "B" 1 [ExAny "A"]
979 , Right $ exAv "B" 2 [ExAny "A"]
980 , Right $ exAv "C" 1 [ExFix "B" 1]
981 , Right $ exAv "D" 1 [ExFix "B" 2]
982 , Right $ exAv "E" 1 [ExAny "B"]
983 , Right $ exAv "F" 1 [ExFix "B" 1, ExAny "E"]
984 , Right $ exAv "G" 1 [ExFix "B" 2, ExAny "E"]
985 , Right $ exAv "Z" 1 []
988 -- In this example, we _can_ install C and D as independent goals, but we have
989 -- to pick two different versions for B (arbitrarily)
990 db2 :: ExampleDb
991 db2 =
992 [ Right $ exAv "A" 1 []
993 , Right $ exAv "A" 2 []
994 , Right $ exAv "B" 1 [ExAny "A"]
995 , Right $ exAv "B" 2 [ExAny "A"]
996 , Right $ exAv "C" 1 [ExAny "B", ExFix "A" 1]
997 , Right $ exAv "D" 1 [ExAny "B", ExFix "A" 2]
1000 db3 :: ExampleDb
1001 db3 =
1002 [ Right $ exAv "A" 1 []
1003 , Right $ exAv "A" 2 []
1004 , Right $ exAv "B" 1 [exFlagged "flagB" [ExFix "A" 1] [ExFix "A" 2]]
1005 , Right $ exAv "C" 1 [ExFix "A" 1, ExAny "B"]
1006 , Right $ exAv "D" 1 [ExFix "A" 2, ExAny "B"]
1009 -- | Like db3, but the flag picks a different package rather than a
1010 -- different package version
1012 -- In db3 we cannot install C and D as independent goals because:
1014 -- * The multiple instance restriction says C and D _must_ share B
1015 -- * Since C relies on A-1, C needs B to be compiled with flagB on
1016 -- * Since D relies on A-2, D needs B to be compiled with flagB off
1017 -- * Hence C and D have incompatible requirements on B's flags.
1019 -- However, _even_ if we don't check explicitly that we pick the same flag
1020 -- assignment for 0.B and 1.B, we will still detect the problem because
1021 -- 0.B depends on 0.A-1, 1.B depends on 1.A-2, hence we cannot link 0.A to
1022 -- 1.A and therefore we cannot link 0.B to 1.B.
1024 -- In db4 the situation however is trickier. We again cannot install
1025 -- packages C and D as independent goals because:
1027 -- * As above, the multiple instance restriction says that C and D _must_ share B
1028 -- * Since C relies on Ax-2, it requires B to be compiled with flagB off
1029 -- * Since D relies on Ay-2, it requires B to be compiled with flagB on
1030 -- * Hence C and D have incompatible requirements on B's flags.
1032 -- But now this requirement is more indirect. If we only check dependencies
1033 -- we don't see the problem:
1035 -- * We link 0.B to 1.B
1036 -- * 0.B relies on Ay-1
1037 -- * 1.B relies on Ax-1
1039 -- We will insist that 0.Ay will be linked to 1.Ay, and 0.Ax to 1.Ax, but since
1040 -- we only ever assign to one of these, these constraints are never broken.
1041 db4 :: ExampleDb
1042 db4 =
1043 [ Right $ exAv "Ax" 1 []
1044 , Right $ exAv "Ax" 2 []
1045 , Right $ exAv "Ay" 1 []
1046 , Right $ exAv "Ay" 2 []
1047 , Right $ exAv "B" 1 [exFlagged "flagB" [ExFix "Ax" 1] [ExFix "Ay" 1]]
1048 , Right $ exAv "C" 1 [ExFix "Ax" 2, ExAny "B"]
1049 , Right $ exAv "D" 1 [ExFix "Ay" 2, ExAny "B"]
1052 -- | Simple database containing one package with a manual flag.
1053 dbManualFlags :: ExampleDb
1054 dbManualFlags =
1055 [ Right $
1056 declareFlags [ExFlag "flag" True Manual] $
1057 exAv "pkg" 1 [exFlagged "flag" [ExAny "true-dep"] [ExAny "false-dep"]]
1058 , Right $ exAv "true-dep" 1 []
1059 , Right $ exAv "false-dep" 1 []
1062 -- | Database containing a setup dependency with a manual flag. A's library and
1063 -- setup script depend on two different versions of B. B's manual flag can be
1064 -- set to different values in the two places where it is used.
1065 dbSetupDepWithManualFlag :: ExampleDb
1066 dbSetupDepWithManualFlag =
1067 let bFlags = [ExFlag "flag" True Manual]
1068 in [ Right $ exAv "A" 1 [ExFix "B" 1] `withSetupDeps` [ExFix "B" 2]
1069 , Right $
1070 declareFlags bFlags $
1071 exAv
1074 [ exFlagged
1075 "flag"
1076 [ExAny "b-1-true-dep"]
1077 [ExAny "b-1-false-dep"]
1079 , Right $
1080 declareFlags bFlags $
1081 exAv
1084 [ exFlagged
1085 "flag"
1086 [ExAny "b-2-true-dep"]
1087 [ExAny "b-2-false-dep"]
1089 , Right $ exAv "b-1-true-dep" 1 []
1090 , Right $ exAv "b-1-false-dep" 1 []
1091 , Right $ exAv "b-2-true-dep" 1 []
1092 , Right $ exAv "b-2-false-dep" 1 []
1095 -- | A database similar to 'dbSetupDepWithManualFlag', except that the library
1096 -- and setup script both depend on B-1. B must be linked because of the Single
1097 -- Instance Restriction, and its flag can only have one value.
1098 dbLinkedSetupDepWithManualFlag :: ExampleDb
1099 dbLinkedSetupDepWithManualFlag =
1100 [ Right $ exAv "A" 1 [ExFix "B" 1] `withSetupDeps` [ExFix "B" 1]
1101 , Right $
1102 declareFlags [ExFlag "flag" True Manual] $
1103 exAv
1106 [ exFlagged
1107 "flag"
1108 [ExAny "b-1-true-dep"]
1109 [ExAny "b-1-false-dep"]
1111 , Right $ exAv "b-1-true-dep" 1 []
1112 , Right $ exAv "b-1-false-dep" 1 []
1115 -- | Some tests involving testsuites
1117 -- Note that in this test framework test suites are always enabled; if you
1118 -- want to test without test suites just set up a test database without
1119 -- test suites.
1121 -- * C depends on A (through its test suite)
1122 -- * D depends on B-2 (through its test suite), but B-2 is unavailable
1123 -- * E depends on A-1 directly and on A through its test suite. We prefer
1124 -- to use A-1 for the test suite in this case.
1125 -- * F depends on A-1 directly and on A-2 through its test suite. In this
1126 -- case we currently fail to install F, although strictly speaking
1127 -- test suites should be considered independent goals.
1128 -- * G is like E, but for version A-2. This means that if we cannot install
1129 -- E and G together, unless we regard them as independent goals.
1130 db5 :: ExampleDb
1131 db5 =
1132 [ Right $ exAv "A" 1 []
1133 , Right $ exAv "A" 2 []
1134 , Right $ exAv "B" 1 []
1135 , Right $ exAv "C" 1 [] `withTest` exTest "testC" [ExAny "A"]
1136 , Right $ exAv "D" 1 [] `withTest` exTest "testD" [ExFix "B" 2]
1137 , Right $ exAv "E" 1 [ExFix "A" 1] `withTest` exTest "testE" [ExAny "A"]
1138 , Right $ exAv "F" 1 [ExFix "A" 1] `withTest` exTest "testF" [ExFix "A" 2]
1139 , Right $ exAv "G" 1 [ExFix "A" 2] `withTest` exTest "testG" [ExAny "A"]
1142 -- Now the _dependencies_ have test suites
1145 -- * Installing C is a simple example. C wants version 1 of A, but depends on
1147 -- B, and B's testsuite depends on an any version of A. In this case we prefer
1148 -- to link (if we don't regard test suites as independent goals then of course
1149 -- linking here doesn't even come into it).
1151 -- * Installing [C, D] means that we prefer to link B -- depending on how we
1153 -- set things up, this means that we should also link their test suites.
1154 db6 :: ExampleDb
1155 db6 =
1156 [ Right $ exAv "A" 1 []
1157 , Right $ exAv "A" 2 []
1158 , Right $ exAv "B" 1 [] `withTest` exTest "testA" [ExAny "A"]
1159 , Right $ exAv "C" 1 [ExFix "A" 1, ExAny "B"]
1160 , Right $ exAv "D" 1 [ExAny "B"]
1163 -- | This test checks that the solver can backjump to disable a flag, even if
1164 -- the problematic dependency is also under a test suite. (issue #4390)
1166 -- The goal order forces the solver to choose the flag before enabling testing.
1167 -- Previously, the solver couldn't handle this case, because it only tried to
1168 -- disable testing, and when that failed, it backjumped past the flag choice.
1169 -- The solver should also try to set the flag to false, because that avoids the
1170 -- dependency on B.
1171 testTestSuiteWithFlag :: String -> SolverTest
1172 testTestSuiteWithFlag name =
1173 goalOrder goals $
1174 enableAllTests $
1175 mkTest db name ["A", "B"] $
1176 solverSuccess [("A", 1), ("B", 1)]
1177 where
1178 db :: ExampleDb
1179 db =
1180 [ Right $
1181 exAv "A" 1 []
1182 `withTest` exTest "test" [exFlagged "flag" [ExFix "B" 2] []]
1183 , Right $ exAv "B" 1 []
1186 goals :: [ExampleVar]
1187 goals =
1188 [ P QualNone "B"
1189 , P QualNone "A"
1190 , F QualNone "A" "flag"
1191 , S QualNone "A" TestStanzas
1194 -- Packages with setup dependencies
1196 -- Install..
1198 -- * B: Simple example, just make sure setup deps are taken into account at all
1200 -- * C: Both the package and the setup script depend on any version of A.
1202 -- In this case we prefer to link
1204 -- * D: Variation on C.1 where the package requires a specific (not latest)
1206 -- version but the setup dependency is not fixed. Again, we prefer to
1207 -- link (picking the older version)
1209 -- * E: Variation on C.2 with the setup dependency the more inflexible.
1211 -- Currently, in this case we do not see the opportunity to link because
1212 -- we consider setup dependencies after normal dependencies; we will
1213 -- pick A.2 for E, then realize we cannot link E.setup.A to A.2, and pick
1214 -- A.1 instead. This isn't so easy to fix (if we want to fix it at all);
1215 -- in particular, considering setup dependencies _before_ other deps is
1216 -- not an improvement, because in general we would prefer to link setup
1217 -- setups to package deps, rather than the other way around. (For example,
1218 -- if we change this ordering then the test for D would start to install
1219 -- two versions of A).
1221 -- * F: The package and the setup script depend on different versions of A.
1223 -- This will only work if setup dependencies are considered independent.
1224 db7 :: ExampleDb
1225 db7 =
1226 [ Right $ exAv "A" 1 []
1227 , Right $ exAv "A" 2 []
1228 , Right $ exAv "B" 1 [] `withSetupDeps` [ExAny "A"]
1229 , Right $ exAv "C" 1 [ExAny "A"] `withSetupDeps` [ExAny "A"]
1230 , Right $ exAv "D" 1 [ExFix "A" 1] `withSetupDeps` [ExAny "A"]
1231 , Right $ exAv "E" 1 [ExAny "A"] `withSetupDeps` [ExFix "A" 1]
1232 , Right $ exAv "F" 1 [ExFix "A" 2] `withSetupDeps` [ExFix "A" 1]
1235 -- If we install C and D together (not as independent goals), we need to build
1236 -- both B.1 and B.2, both of which depend on A.
1237 db8 :: ExampleDb
1238 db8 =
1239 [ Right $ exAv "A" 1 []
1240 , Right $ exAv "B" 1 [ExAny "A"]
1241 , Right $ exAv "B" 2 [ExAny "A"]
1242 , Right $ exAv "C" 1 [] `withSetupDeps` [ExFix "B" 1]
1243 , Right $ exAv "D" 1 [] `withSetupDeps` [ExFix "B" 2]
1246 -- Extended version of `db8` so that we have nested setup dependencies
1247 db9 :: ExampleDb
1248 db9 =
1250 ++ [ Right $ exAv "E" 1 [ExAny "C"]
1251 , Right $ exAv "E" 2 [ExAny "D"]
1252 , Right $ exAv "F" 1 [] `withSetupDeps` [ExFix "E" 1]
1253 , Right $ exAv "G" 1 [] `withSetupDeps` [ExFix "E" 2]
1256 -- Multiple already-installed packages with inter-dependencies, and one package
1257 -- (C) that depends on package A-1 for its setup script and package A-2 as a
1258 -- library dependency.
1259 db10 :: ExampleDb
1260 db10 =
1261 let rts = exInst "rts" 1 "rts-inst" []
1262 ghc_prim = exInst "ghc-prim" 1 "ghc-prim-inst" [rts]
1263 base = exInst "base" 1 "base-inst" [rts, ghc_prim]
1264 a1 = exInst "A" 1 "A1-inst" [base]
1265 a2 = exInst "A" 2 "A2-inst" [base]
1266 in [ Left rts
1267 , Left ghc_prim
1268 , Left base
1269 , Left a1
1270 , Left a2
1271 , Right $ exAv "C" 1 [ExFix "A" 2] `withSetupDeps` [ExFix "A" 1]
1274 -- | This database tests that a package's setup dependencies are correctly
1275 -- linked when the package is linked. See pull request #3268.
1277 -- When A and B are installed as independent goals, their dependencies on C must
1278 -- be linked, due to the single instance restriction. Since C depends on D, 0.D
1279 -- and 1.D must be linked. C also has a setup dependency on D, so 0.C-setup.D
1280 -- and 1.C-setup.D must be linked. However, D's two link groups must remain
1281 -- independent. The solver should be able to choose D-1 for C's library and D-2
1282 -- for C's setup script.
1283 dbSetupDeps :: ExampleDb
1284 dbSetupDeps =
1285 [ Right $ exAv "A" 1 [ExAny "C"]
1286 , Right $ exAv "B" 1 [ExAny "C"]
1287 , Right $ exAv "C" 1 [ExFix "D" 1] `withSetupDeps` [ExFix "D" 2]
1288 , Right $ exAv "D" 1 []
1289 , Right $ exAv "D" 2 []
1292 -- | Tests for dealing with base shims
1293 db11 :: ExampleDb
1294 db11 =
1295 let base3 = exInst "base" 3 "base-3-inst" [base4]
1296 base4 = exInst "base" 4 "base-4-inst" []
1297 in [ Left base3
1298 , Left base4
1299 , Right $ exAv "A" 1 [ExFix "base" 3]
1302 -- | Slightly more realistic version of db11 where base-3 depends on syb
1303 -- This means that if a package depends on base-3 and on syb, then they MUST
1304 -- share the version of syb
1306 -- * Package A relies on base-3 (which relies on base-4)
1307 -- * Package B relies on base-4
1308 -- * Package C relies on both A and B
1309 -- * Package D relies on base-3 and on syb-2, which is not possible because
1310 -- base-3 has a dependency on syb-1 (non-inheritance of the Base qualifier)
1311 -- * Package E relies on base-4 and on syb-2, which is fine.
1312 db12 :: ExampleDb
1313 db12 =
1314 let base3 = exInst "base" 3 "base-3-inst" [base4, syb1]
1315 base4 = exInst "base" 4 "base-4-inst" []
1316 syb1 = exInst "syb" 1 "syb-1-inst" [base4]
1317 in [ Left base3
1318 , Left base4
1319 , Left syb1
1320 , Right $ exAv "syb" 2 [ExFix "base" 4]
1321 , Right $ exAv "A" 1 [ExFix "base" 3, ExAny "syb"]
1322 , Right $ exAv "B" 1 [ExFix "base" 4, ExAny "syb"]
1323 , Right $ exAv "C" 1 [ExAny "A", ExAny "B"]
1324 , Right $ exAv "D" 1 [ExFix "base" 3, ExFix "syb" 2]
1325 , Right $ exAv "E" 1 [ExFix "base" 4, ExFix "syb" 2]
1328 dbBase :: ExampleDb
1329 dbBase =
1330 [ Right $
1331 exAv
1332 "base"
1334 [ExAny "ghc-prim", ExAny "integer-simple", ExAny "integer-gmp"]
1335 , Right $ exAv "ghc-prim" 1 []
1336 , Right $ exAv "integer-simple" 1 []
1337 , Right $ exAv "integer-gmp" 1 []
1340 dbNonupgrade :: ExampleDb
1341 dbNonupgrade =
1342 [ Left $ exInst "ghc" 1 "ghc-1" []
1343 , Right $ exAv "ghc" 2 []
1344 , Right $ exAv "ghci" 2 []
1345 , Right $ exAv "ghc-boot" 2 []
1346 , Right $ exAv "A" 1 [ExFix "ghc" 2]
1347 , Right $ exAv "B" 1 [ExFix "ghci" 2]
1348 , Right $ exAv "C" 1 [ExFix "ghc-boot" 2]
1351 db13 :: ExampleDb
1352 db13 =
1353 [ Right $ exAv "A" 1 []
1354 , Right $ exAv "A" 2 []
1355 , Right $ exAv "A" 3 []
1358 -- | A, B, and C have three different dependencies on D that can be set to
1359 -- different versions with qualified constraints. Each version of D can only
1360 -- be depended upon by one version of A, B, or C, so that the versions of A, B,
1361 -- and C in the install plan indicate which version of D was chosen for each
1362 -- dependency. The one-to-one correspondence between versions of A, B, and C and
1363 -- versions of D also prevents linking, which would complicate the solver's
1364 -- behavior.
1365 dbConstraints :: ExampleDb
1366 dbConstraints =
1367 [Right $ exAv "A" v [ExFix "D" v] | v <- [1, 4, 7]]
1368 ++ [Right $ exAv "B" v [] `withSetupDeps` [ExFix "D" v] | v <- [2, 5, 8]]
1369 ++ [Right $ exAv "C" v [] `withSetupDeps` [ExFix "D" v] | v <- [3, 6, 9]]
1370 ++ [Right $ exAv "D" v [] | v <- [1 .. 9]]
1372 dbStanzaPreferences1 :: ExampleDb
1373 dbStanzaPreferences1 =
1374 [ Right $ exAv "pkg" 1 [] `withTest` exTest "test" [ExAny "test-dep"]
1375 , Right $ exAv "test-dep" 1 []
1378 dbStanzaPreferences2 :: ExampleDb
1379 dbStanzaPreferences2 =
1380 [ Right $ exAv "pkg" 1 [] `withTest` exTest "test" [ExAny "unknown"]
1383 -- | This is a test case for a bug in stanza preferences (#3930). The solver
1384 -- should be able to install 'A' by enabling 'flag' and disabling testing. When
1385 -- it tries goals in the specified order and prefers testing, it encounters
1386 -- 'unknown-pkg2'. 'unknown-pkg2' is only introduced by testing and 'flag', so
1387 -- the conflict set should contain both of those variables. Before the fix, it
1388 -- only contained 'flag'. The solver backjumped past the choice to disable
1389 -- testing and failed to find the solution.
1390 testStanzaPreference :: String -> TestTree
1391 testStanzaPreference name =
1392 let pkg =
1393 exAv
1396 [ exFlagged
1397 "flag"
1399 [ExAny "unknown-pkg1"]
1401 `withTest` exTest
1402 "test"
1403 [ exFlagged
1404 "flag"
1405 [ExAny "unknown-pkg2"]
1408 goals =
1409 [ P QualNone "A"
1410 , F QualNone "A" "flag"
1411 , S QualNone "A" TestStanzas
1413 in runTest $
1414 goalOrder goals $
1415 preferences [ExStanzaPref "A" [TestStanzas]] $
1416 mkTest [Right pkg] name ["A"] $
1417 solverSuccess [("A", 1)]
1419 -- | Database with some cycles
1421 -- * Simplest non-trivial cycle: A -> B and B -> A
1422 -- * There is a cycle C -> D -> C, but it can be broken by picking the
1423 -- right flag assignment.
1424 db14 :: ExampleDb
1425 db14 =
1426 [ Right $ exAv "A" 1 [ExAny "B"]
1427 , Right $ exAv "B" 1 [ExAny "A"]
1428 , Right $ exAv "C" 1 [exFlagged "flagC" [ExAny "D"] [ExAny "E"]]
1429 , Right $ exAv "D" 1 [ExAny "C"]
1430 , Right $ exAv "E" 1 []
1433 -- | Cycles through setup dependencies
1435 -- The first cycle is unsolvable: package A has a setup dependency on B,
1436 -- B has a regular dependency on A, and we only have a single version available
1437 -- for both.
1439 -- The second cycle can be broken by picking different versions: package C-2.0
1440 -- has a setup dependency on D, and D has a regular dependency on C-*. However,
1441 -- version C-1.0 is already available (perhaps it didn't have this setup dep).
1442 -- Thus, we should be able to break this cycle even if we are installing package
1443 -- E, which explicitly depends on C-2.0.
1444 db15 :: ExampleDb
1445 db15 =
1446 [ -- First example (real cycle, no solution)
1447 Right $ exAv "A" 1 [] `withSetupDeps` [ExAny "B"]
1448 , Right $ exAv "B" 1 [ExAny "A"]
1449 , -- Second example (cycle can be broken by picking versions carefully)
1450 Left $ exInst "C" 1 "C-1-inst" []
1451 , Right $ exAv "C" 2 [] `withSetupDeps` [ExAny "D"]
1452 , Right $ exAv "D" 1 [ExAny "C"]
1453 , Right $ exAv "E" 1 [ExFix "C" 2]
1456 -- | Detect a cycle between a package and its setup script.
1458 -- This type of cycle can easily occur when v2-build adds default setup
1459 -- dependencies to packages without custom-setup stanzas. For example, cabal
1460 -- adds 'time' as a setup dependency for 'time'. The solver should detect the
1461 -- cycle when it attempts to link the setup and non-setup instances of the
1462 -- package and then choose a different version for the setup dependency.
1463 issue4161 :: String -> SolverTest
1464 issue4161 name =
1465 setVerbose $
1466 mkTest db name ["target"] $
1467 SolverResult checkFullLog $
1468 Right [("target", 1), ("time", 1), ("time", 2)]
1469 where
1470 db :: ExampleDb
1471 db =
1472 [ Right $ exAv "target" 1 [ExFix "time" 2]
1473 , Right $ exAv "time" 2 [] `withSetupDeps` [ExAny "time"]
1474 , Right $ exAv "time" 1 []
1477 checkFullLog :: [String] -> Bool
1478 checkFullLog =
1479 any $
1480 isInfixOf $
1481 "rejecting: time:setup.time~>time-2.0.0 (cyclic dependencies; "
1482 ++ "conflict set: time:setup.time)"
1484 -- | Packages pkg-A, pkg-B, and pkg-C form a cycle. The solver should backtrack
1485 -- as soon as it chooses the last package in the cycle, to avoid searching parts
1486 -- of the tree that have no solution. Since there is no way to break the cycle,
1487 -- it should fail with an error message describing the cycle.
1488 testCyclicDependencyErrorMessages :: String -> SolverTest
1489 testCyclicDependencyErrorMessages name =
1490 goalOrder goals $
1491 mkTest db name ["pkg-A"] $
1492 SolverResult checkFullLog $
1493 Left checkSummarizedLog
1494 where
1495 db :: ExampleDb
1496 db =
1497 [ Right $ exAv "pkg-A" 1 [ExAny "pkg-B"]
1498 , Right $ exAv "pkg-B" 1 [ExAny "pkg-C"]
1499 , Right $ exAv "pkg-C" 1 [ExAny "pkg-A", ExAny "pkg-D"]
1500 , Right $ exAv "pkg-D" 1 [ExAny "pkg-E"]
1501 , Right $ exAv "pkg-E" 1 []
1504 -- The solver should backtrack as soon as pkg-A, pkg-B, and pkg-C form a
1505 -- cycle. It shouldn't try pkg-D or pkg-E.
1506 checkFullLog :: [String] -> Bool
1507 checkFullLog =
1508 not . any (\l -> "pkg-D" `isInfixOf` l || "pkg-E" `isInfixOf` l)
1510 checkSummarizedLog :: String -> Bool
1511 checkSummarizedLog =
1512 isInfixOf "rejecting: pkg-C-1.0.0 (cyclic dependencies; conflict set: pkg-A, pkg-B, pkg-C)"
1514 -- Solve for pkg-D and pkg-E last.
1515 goals :: [ExampleVar]
1516 goals = [P QualNone ("pkg-" ++ [c]) | c <- ['A' .. 'E']]
1518 -- | Check that the solver can backtrack after encountering the SIR (issue #2843)
1520 -- When A and B are installed as independent goals, the single instance
1521 -- restriction prevents B from depending on C. This database tests that the
1522 -- solver can backtrack after encountering the single instance restriction and
1523 -- choose the only valid flag assignment (-flagA +flagB):
1525 -- > flagA flagB B depends on
1526 -- > On _ C-*
1527 -- > Off On E-* <-- only valid flag assignment
1528 -- > Off Off D-2.0, C-*
1530 -- Since A depends on C-* and D-1.0, and C-1.0 depends on any version of D,
1531 -- we must build C-1.0 against D-1.0. Since B depends on D-2.0, we cannot have
1532 -- C in the transitive closure of B's dependencies, because that would mean we
1533 -- would need two instances of C: one built against D-1.0 and one built against
1534 -- D-2.0.
1535 db16 :: ExampleDb
1536 db16 =
1537 [ Right $ exAv "A" 1 [ExAny "C", ExFix "D" 1]
1538 , Right $
1539 exAv
1542 [ ExFix "D" 2
1543 , exFlagged
1544 "flagA"
1545 [ExAny "C"]
1546 [ exFlagged
1547 "flagB"
1548 [ExAny "E"]
1549 [ExAny "C"]
1552 , Right $ exAv "C" 1 [ExAny "D"]
1553 , Right $ exAv "D" 1 []
1554 , Right $ exAv "D" 2 []
1555 , Right $ exAv "E" 1 []
1558 -- Try to get the solver to backtrack while satisfying
1559 -- reject-unconstrained-dependencies: both the first and last versions of A
1560 -- require packages outside the closed set, so it will have to try the
1561 -- middle one.
1562 db17 :: ExampleDb
1563 db17 =
1564 [ Right $ exAv "A" 1 [ExAny "C"]
1565 , Right $ exAv "A" 2 [ExAny "B"]
1566 , Right $ exAv "A" 3 [ExAny "C"]
1567 , Right $ exAv "B" 1 []
1568 , Right $ exAv "C" 1 [ExAny "B"]
1571 -- | This test checks that when the solver discovers a constraint on a
1572 -- package's version after choosing to link that package, it can backtrack to
1573 -- try alternative versions for the linked-to package. See pull request #3327.
1575 -- When A and B are installed as independent goals, their dependencies on C
1576 -- must be linked. Since C depends on D, A and B's dependencies on D must also
1577 -- be linked. This test fixes the goal order so that the solver chooses D-2 for
1578 -- both 0.D and 1.D before it encounters the test suites' constraints. The
1579 -- solver must backtrack to try D-1 for both 0.D and 1.D.
1580 testIndepGoals2 :: String -> SolverTest
1581 testIndepGoals2 name =
1582 goalOrder goals $
1583 independentGoals $
1584 enableAllTests $
1585 mkTest db name ["A", "B"] $
1586 solverSuccess [("A", 1), ("B", 1), ("C", 1), ("D", 1)]
1587 where
1588 db :: ExampleDb
1589 db =
1590 [ Right $ exAv "A" 1 [ExAny "C"] `withTest` exTest "test" [ExFix "D" 1]
1591 , Right $ exAv "B" 1 [ExAny "C"] `withTest` exTest "test" [ExFix "D" 1]
1592 , Right $ exAv "C" 1 [ExAny "D"]
1593 , Right $ exAv "D" 1 []
1594 , Right $ exAv "D" 2 []
1597 goals :: [ExampleVar]
1598 goals =
1599 [ P (QualIndep "A") "A"
1600 , P (QualIndep "A") "C"
1601 , P (QualIndep "A") "D"
1602 , P (QualIndep "B") "B"
1603 , P (QualIndep "B") "C"
1604 , P (QualIndep "B") "D"
1605 , S (QualIndep "B") "B" TestStanzas
1606 , S (QualIndep "A") "A" TestStanzas
1609 -- | Issue #2834
1610 -- When both A and B are installed as independent goals, their dependencies on
1611 -- C must be linked. The only combination of C's flags that is consistent with
1612 -- A and B's dependencies on D is -flagA +flagB. This database tests that the
1613 -- solver can backtrack to find the right combination of flags (requiring F, but
1614 -- not E or G) and apply it to both 0.C and 1.C.
1616 -- > flagA flagB C depends on
1617 -- > On _ D-1, E-*
1618 -- > Off On F-* <-- Only valid choice
1619 -- > Off Off D-2, G-*
1621 -- The single instance restriction means we cannot have one instance of C
1622 -- built against D-1 and one instance built against D-2; since A depends on
1623 -- D-1, and B depends on C-2, it is therefore important that C cannot depend
1624 -- on any version of D.
1625 db18 :: ExampleDb
1626 db18 =
1627 [ Right $ exAv "A" 1 [ExAny "C", ExFix "D" 1]
1628 , Right $ exAv "B" 1 [ExAny "C", ExFix "D" 2]
1629 , Right $
1630 exAv
1633 [ exFlagged
1634 "flagA"
1635 [ExFix "D" 1, ExAny "E"]
1636 [ exFlagged
1637 "flagB"
1638 [ExAny "F"]
1639 [ExFix "D" 2, ExAny "G"]
1642 , Right $ exAv "D" 1 []
1643 , Right $ exAv "D" 2 []
1644 , Right $ exAv "E" 1 []
1645 , Right $ exAv "F" 1 []
1646 , Right $ exAv "G" 1 []
1649 -- | When both values for flagA introduce package B, the solver should be able
1650 -- to choose B before choosing a value for flagA. It should try to choose a
1651 -- version for B that is in the union of the version ranges required by +flagA
1652 -- and -flagA.
1653 commonDependencyLogMessage :: String -> SolverTest
1654 commonDependencyLogMessage name =
1655 mkTest db name ["A"] $
1656 solverFailure $
1657 isInfixOf $
1658 "[__0] trying: A-1.0.0 (user goal)\n"
1659 ++ "[__1] next goal: B (dependency of A +/-flagA)\n"
1660 ++ "[__1] rejecting: B-2.0.0 (conflict: A +/-flagA => B==1.0.0 || ==3.0.0)"
1661 where
1662 db :: ExampleDb
1663 db =
1664 [ Right $
1665 exAv
1668 [ exFlagged
1669 "flagA"
1670 [ExFix "B" 1]
1671 [ExFix "B" 3]
1673 , Right $ exAv "B" 2 []
1676 -- | Test lifting dependencies out of multiple levels of conditionals.
1677 twoLevelDeepCommonDependencyLogMessage :: String -> SolverTest
1678 twoLevelDeepCommonDependencyLogMessage name =
1679 mkTest db name ["A"] $
1680 solverFailure $
1681 isInfixOf $
1682 "unknown package: B (dependency of A +/-flagA +/-flagB)"
1683 where
1684 db :: ExampleDb
1685 db =
1686 [ Right $
1687 exAv
1690 [ exFlagged
1691 "flagA"
1692 [ exFlagged
1693 "flagB"
1694 [ExAny "B"]
1695 [ExAny "B"]
1697 [ exFlagged
1698 "flagB"
1699 [ExAny "B"]
1700 [ExAny "B"]
1705 -- | Test handling nested conditionals that are controlled by the same flag.
1706 -- The solver should treat flagA as introducing 'unknown' with value true, not
1707 -- both true and false. That means that when +flagA causes a conflict, the
1708 -- solver should try flipping flagA to false to resolve the conflict, rather
1709 -- than backjumping past flagA.
1710 testBackjumpingWithCommonDependency :: String -> SolverTest
1711 testBackjumpingWithCommonDependency name =
1712 mkTest db name ["A"] $ solverSuccess [("A", 1), ("B", 1)]
1713 where
1714 db :: ExampleDb
1715 db =
1716 [ Right $
1717 exAv
1720 [ exFlagged
1721 "flagA"
1722 [ exFlagged
1723 "flagA"
1724 [ExAny "unknown"]
1725 [ExAny "unknown"]
1727 [ExAny "B"]
1729 , Right $ exAv "B" 1 []
1732 -- | Tricky test case with independent goals (issue #2842)
1734 -- Suppose we are installing D, E, and F as independent goals:
1736 -- * D depends on A-* and C-1, requiring A-1 to be built against C-1
1737 -- * E depends on B-* and C-2, requiring B-1 to be built against C-2
1738 -- * F depends on A-* and B-*; this means we need A-1 and B-1 both to be built
1739 -- against the same version of C, violating the single instance restriction.
1741 -- We can visualize this DB as:
1743 -- > C-1 C-2
1744 -- > /|\ /|\
1745 -- > / | \ / | \
1746 -- > / | X | \
1747 -- > | | / \ | |
1748 -- > | |/ \| |
1749 -- > | + + |
1750 -- > | | | |
1751 -- > | A B |
1752 -- > \ |\ /| /
1753 -- > \ | \ / | /
1754 -- > \| V |/
1755 -- > D F E
1756 testIndepGoals3 :: String -> SolverTest
1757 testIndepGoals3 name =
1758 goalOrder goals $
1759 independentGoals $
1760 mkTest db name ["D", "E", "F"] anySolverFailure
1761 where
1762 db :: ExampleDb
1763 db =
1764 [ Right $ exAv "A" 1 [ExAny "C"]
1765 , Right $ exAv "B" 1 [ExAny "C"]
1766 , Right $ exAv "C" 1 []
1767 , Right $ exAv "C" 2 []
1768 , Right $ exAv "D" 1 [ExAny "A", ExFix "C" 1]
1769 , Right $ exAv "E" 1 [ExAny "B", ExFix "C" 2]
1770 , Right $ exAv "F" 1 [ExAny "A", ExAny "B"]
1773 goals :: [ExampleVar]
1774 goals =
1775 [ P (QualIndep "D") "D"
1776 , P (QualIndep "D") "C"
1777 , P (QualIndep "D") "A"
1778 , P (QualIndep "E") "E"
1779 , P (QualIndep "E") "C"
1780 , P (QualIndep "E") "B"
1781 , P (QualIndep "F") "F"
1782 , P (QualIndep "F") "B"
1783 , P (QualIndep "F") "C"
1784 , P (QualIndep "F") "A"
1787 -- | This test checks that the solver correctly backjumps when dependencies
1788 -- of linked packages are not linked. It is an example where the conflict set
1789 -- from enforcing the single instance restriction is not sufficient. See pull
1790 -- request #3327.
1792 -- When A, B, and C are installed as independent goals with the specified goal
1793 -- order, the first choice that the solver makes for E is 0.E-2. Then, when it
1794 -- chooses dependencies for B and C, it links both 1.E and 2.E to 0.E. Finally,
1795 -- the solver discovers C's test's constraint on E. It must backtrack to try
1796 -- 1.E-1 and then link 2.E to 1.E. Backjumping all the way to 0.E does not lead
1797 -- to a solution, because 0.E's version is constrained by A and cannot be
1798 -- changed.
1799 testIndepGoals4 :: String -> SolverTest
1800 testIndepGoals4 name =
1801 goalOrder goals $
1802 independentGoals $
1803 enableAllTests $
1804 mkTest db name ["A", "B", "C"] $
1805 solverSuccess [("A", 1), ("B", 1), ("C", 1), ("D", 1), ("E", 1), ("E", 2)]
1806 where
1807 db :: ExampleDb
1808 db =
1809 [ Right $ exAv "A" 1 [ExFix "E" 2]
1810 , Right $ exAv "B" 1 [ExAny "D"]
1811 , Right $ exAv "C" 1 [ExAny "D"] `withTest` exTest "test" [ExFix "E" 1]
1812 , Right $ exAv "D" 1 [ExAny "E"]
1813 , Right $ exAv "E" 1 []
1814 , Right $ exAv "E" 2 []
1817 goals :: [ExampleVar]
1818 goals =
1819 [ P (QualIndep "A") "A"
1820 , P (QualIndep "A") "E"
1821 , P (QualIndep "B") "B"
1822 , P (QualIndep "B") "D"
1823 , P (QualIndep "B") "E"
1824 , P (QualIndep "C") "C"
1825 , P (QualIndep "C") "D"
1826 , P (QualIndep "C") "E"
1827 , S (QualIndep "C") "C" TestStanzas
1830 -- | Test the trace messages that we get when a package refers to an unknown pkg
1832 -- TODO: Currently we don't actually test the trace messages, and this particular
1833 -- test still succeeds. The trace can only be verified by hand.
1834 db21 :: ExampleDb
1835 db21 =
1836 [ Right $ exAv "A" 1 [ExAny "B"]
1837 , Right $ exAv "A" 2 [ExAny "C"] -- A-2.0 will be tried first, but C unknown
1838 , Right $ exAv "B" 1 []
1841 -- | A variant of 'db21', which actually fails.
1842 db22 :: ExampleDb
1843 db22 =
1844 [ Right $ exAv "A" 1 [ExAny "B"]
1845 , Right $ exAv "A" 2 [ExAny "C"]
1848 -- | Another test for the unknown package message. This database tests that
1849 -- filtering out redundant conflict set messages in the solver log doesn't
1850 -- interfere with generating a message about a missing package (part of issue
1851 -- #3617). The conflict set for the missing package is {A, B}. That conflict set
1852 -- is propagated up the tree to the level of A. Since the conflict set is the
1853 -- same at both levels, the solver only keeps one of the backjumping messages.
1854 db23 :: ExampleDb
1855 db23 =
1856 [ Right $ exAv "A" 1 [ExAny "B"]
1859 -- | Database for (unsuccessfully) trying to expose a bug in the handling
1860 -- of implied linking constraints. The question is whether an implied linking
1861 -- constraint should only have the introducing package in its conflict set,
1862 -- or also its link target.
1864 -- It turns out that as long as the Single Instance Restriction is in place,
1865 -- it does not matter, because there will always be an option that is failing
1866 -- due to the SIR, which contains the link target in its conflict set.
1868 -- Even if the SIR is not in place, if there is a solution, one will always
1869 -- be found, because without the SIR, linking is always optional, but never
1870 -- necessary.
1871 testIndepGoals5 :: String -> GoalOrder -> SolverTest
1872 testIndepGoals5 name fixGoalOrder =
1873 case fixGoalOrder of
1874 FixedGoalOrder -> goalOrder goals test
1875 DefaultGoalOrder -> test
1876 where
1877 test :: SolverTest
1878 test =
1879 independentGoals $
1880 mkTest db name ["X", "Y"] $
1881 solverSuccess
1882 [("A", 1), ("A", 2), ("B", 1), ("C", 1), ("C", 2), ("X", 1), ("Y", 1)]
1884 db :: ExampleDb
1885 db =
1886 [ Right $ exAv "X" 1 [ExFix "C" 2, ExAny "A"]
1887 , Right $ exAv "Y" 1 [ExFix "C" 1, ExFix "A" 2]
1888 , Right $ exAv "A" 1 []
1889 , Right $ exAv "A" 2 [ExAny "B"]
1890 , Right $ exAv "B" 1 [ExAny "C"]
1891 , Right $ exAv "C" 1 []
1892 , Right $ exAv "C" 2 []
1895 goals :: [ExampleVar]
1896 goals =
1897 [ P (QualIndep "X") "X"
1898 , P (QualIndep "X") "A"
1899 , P (QualIndep "X") "B"
1900 , P (QualIndep "X") "C"
1901 , P (QualIndep "Y") "Y"
1902 , P (QualIndep "Y") "A"
1903 , P (QualIndep "Y") "B"
1904 , P (QualIndep "Y") "C"
1907 -- | A simplified version of 'testIndepGoals5'.
1908 testIndepGoals6 :: String -> GoalOrder -> SolverTest
1909 testIndepGoals6 name fixGoalOrder =
1910 case fixGoalOrder of
1911 FixedGoalOrder -> goalOrder goals test
1912 DefaultGoalOrder -> test
1913 where
1914 test :: SolverTest
1915 test =
1916 independentGoals $
1917 mkTest db name ["X", "Y"] $
1918 solverSuccess
1919 [("A", 1), ("A", 2), ("B", 1), ("B", 2), ("X", 1), ("Y", 1)]
1921 db :: ExampleDb
1922 db =
1923 [ Right $ exAv "X" 1 [ExFix "B" 2, ExAny "A"]
1924 , Right $ exAv "Y" 1 [ExFix "B" 1, ExFix "A" 2]
1925 , Right $ exAv "A" 1 []
1926 , Right $ exAv "A" 2 [ExAny "B"]
1927 , Right $ exAv "B" 1 []
1928 , Right $ exAv "B" 2 []
1931 goals :: [ExampleVar]
1932 goals =
1933 [ P (QualIndep "X") "X"
1934 , P (QualIndep "X") "A"
1935 , P (QualIndep "X") "B"
1936 , P (QualIndep "Y") "Y"
1937 , P (QualIndep "Y") "A"
1938 , P (QualIndep "Y") "B"
1941 dbExts1 :: ExampleDb
1942 dbExts1 =
1943 [ Right $ exAv "A" 1 [ExExt (EnableExtension RankNTypes)]
1944 , Right $ exAv "B" 1 [ExExt (EnableExtension CPP), ExAny "A"]
1945 , Right $ exAv "C" 1 [ExAny "B"]
1946 , Right $ exAv "D" 1 [ExExt (DisableExtension CPP), ExAny "B"]
1947 , Right $ exAv "E" 1 [ExExt (UnknownExtension "custom"), ExAny "C"]
1950 dbLangs1 :: ExampleDb
1951 dbLangs1 =
1952 [ Right $ exAv "A" 1 [ExLang Haskell2010]
1953 , Right $ exAv "B" 1 [ExLang Haskell98, ExAny "A"]
1954 , Right $ exAv "C" 1 [ExLang (UnknownLanguage "Haskell3000"), ExAny "B"]
1957 -- | cabal must set enable-exe to false in order to avoid the unavailable
1958 -- dependency. Flags are true by default. The flag choice causes "pkg" to
1959 -- depend on "false-dep".
1960 testBuildable :: String -> ExampleDependency -> TestTree
1961 testBuildable testName unavailableDep =
1962 runTest $
1963 mkTestExtLangPC (Just []) (Just [Haskell98]) (Just []) db testName ["pkg"] expected
1964 where
1965 expected = solverSuccess [("false-dep", 1), ("pkg", 1)]
1966 db =
1967 [ Right $
1968 exAv
1969 "pkg"
1971 [ exFlagged
1972 "enable-exe"
1973 [ExAny "true-dep"]
1974 [ExAny "false-dep"]
1976 `withExe` exExe
1977 "exe"
1978 [ unavailableDep
1979 , ExFlagged "enable-exe" (dependencies []) unbuildableDependencies
1981 , Right $ exAv "true-dep" 1 []
1982 , Right $ exAv "false-dep" 1 []
1985 -- | cabal must choose -flag1 +flag2 for "pkg", which requires packages
1986 -- "flag1-false" and "flag2-true".
1987 dbBuildable1 :: ExampleDb
1988 dbBuildable1 =
1989 [ Right $
1990 exAv
1991 "pkg"
1993 [ exFlagged "flag1" [ExAny "flag1-true"] [ExAny "flag1-false"]
1994 , exFlagged "flag2" [ExAny "flag2-true"] [ExAny "flag2-false"]
1996 `withExes` [ exExe
1997 "exe1"
1998 [ ExAny "unknown"
1999 , ExFlagged "flag1" (dependencies []) unbuildableDependencies
2000 , ExFlagged "flag2" (dependencies []) unbuildableDependencies
2002 , exExe
2003 "exe2"
2004 [ ExAny "unknown"
2005 , ExFlagged
2006 "flag1"
2007 (dependencies [])
2008 (dependencies [ExFlagged "flag2" unbuildableDependencies (dependencies [])])
2011 , Right $ exAv "flag1-true" 1 []
2012 , Right $ exAv "flag1-false" 1 []
2013 , Right $ exAv "flag2-true" 1 []
2014 , Right $ exAv "flag2-false" 1 []
2017 -- | cabal must pick B-2 to avoid the unknown dependency.
2018 dbBuildable2 :: ExampleDb
2019 dbBuildable2 =
2020 [ Right $ exAv "A" 1 [ExAny "B"]
2021 , Right $ exAv "B" 1 [ExAny "unknown"]
2022 , Right $
2023 exAv "B" 2 []
2024 `withExe` exExe
2025 "exe"
2026 [ ExAny "unknown"
2027 , ExFlagged "disable-exe" unbuildableDependencies (dependencies [])
2029 , Right $ exAv "B" 3 [ExAny "unknown"]
2032 -- | Package databases for testing @pkg-config@ dependencies.
2033 -- when no pkgconfig db is present, cabal must pick flag1 false and flag2 true to avoid the pkg dependency.
2034 dbPC1 :: ExampleDb
2035 dbPC1 =
2036 [ Right $ exAv "A" 1 [ExPkg ("pkgA", 1)]
2037 , Right $ exAv "B" 1 [ExPkg ("pkgB", 1), ExAny "A"]
2038 , Right $ exAv "B" 2 [ExPkg ("pkgB", 2), ExAny "A"]
2039 , Right $ exAv "C" 1 [ExAny "B"]
2040 , Right $ exAv "D" 1 [exFlagged "flag1" [ExAny "A"] [], exFlagged "flag2" [] [ExAny "A"]]
2043 -- | Test for the solver's summarized log. The final conflict set is {A, F},
2044 -- though the goal order forces the solver to find the (avoidable) conflict
2045 -- between B and C first. When the solver reaches the backjump limit, it should
2046 -- only show the log to the first conflict. When the backjump limit is high
2047 -- enough to allow an exhaustive search, the solver should make use of the final
2048 -- conflict set to only show the conflict between A and F in the summarized log.
2049 testSummarizedLog :: String -> Maybe Int -> String -> TestTree
2050 testSummarizedLog testName mbj expectedMsg =
2051 runTest $
2052 maxBackjumps mbj $
2053 goalOrder goals $
2054 mkTest db testName ["A"] $
2055 solverFailure (== expectedMsg)
2056 where
2057 db =
2058 [ Right $ exAv "A" 1 [ExAny "B", ExAny "F"]
2059 , Right $ exAv "B" 3 [ExAny "C"]
2060 , Right $ exAv "B" 2 [ExAny "D"]
2061 , Right $ exAv "B" 1 [ExAny "E"]
2062 , Right $ exAv "E" 1 []
2065 goals :: [ExampleVar]
2066 goals = [P QualNone pkg | pkg <- ["A", "B", "C", "D", "E", "F"]]
2068 dbMinimizeConflictSet :: ExampleDb
2069 dbMinimizeConflictSet =
2070 [ Right $ exAv "A" 3 [ExFix "B" 2, ExFix "C" 1, ExFix "D" 2]
2071 , Right $ exAv "A" 2 [ExFix "B" 1, ExFix "C" 2, ExFix "D" 2]
2072 , Right $ exAv "A" 1 [ExFix "B" 1, ExFix "C" 1, ExFix "D" 2]
2073 , Right $ exAv "B" 1 []
2074 , Right $ exAv "C" 1 []
2075 , Right $ exAv "D" 1 []
2078 -- | Test that the solver can find a minimal conflict set with
2079 -- --minimize-conflict-set. In the first run, the goal order causes the solver
2080 -- to find that A-3 conflicts with B, A-2 conflicts with C, and A-1 conflicts
2081 -- with D. The full log should show that the original final conflict set is
2082 -- {A, B, C, D}. Then the solver should be able to reduce the conflict set to
2083 -- {A, D}, since all versions of A conflict with D. The summarized log should
2084 -- only mention A and D.
2085 testMinimizeConflictSet :: String -> TestTree
2086 testMinimizeConflictSet testName =
2087 runTest $
2088 minimizeConflictSet $
2089 goalOrder goals $
2090 setVerbose $
2091 mkTest dbMinimizeConflictSet testName ["A"] $
2092 SolverResult checkFullLog (Left (== expectedMsg))
2093 where
2094 checkFullLog :: [String] -> Bool
2095 checkFullLog =
2096 containsInOrder
2097 [ "[__0] fail (backjumping, conflict set: A, B, C, D)"
2098 , "Found no solution after exhaustively searching the dependency tree. "
2099 ++ "Rerunning the dependency solver to minimize the conflict set ({A, B, C, D})."
2100 , "Trying to remove variable \"A\" from the conflict set."
2101 , "Failed to remove \"A\" from the conflict set. Continuing with {A, B, C, D}."
2102 , "Trying to remove variable \"B\" from the conflict set."
2103 , "Successfully removed \"B\" from the conflict set. Continuing with {A, D}."
2104 , "Trying to remove variable \"D\" from the conflict set."
2105 , "Failed to remove \"D\" from the conflict set. Continuing with {A, D}."
2108 expectedMsg =
2109 "Could not resolve dependencies:\n"
2110 ++ "[__0] trying: A-3.0.0 (user goal)\n"
2111 ++ "[__1] next goal: D (dependency of A)\n"
2112 ++ "[__1] rejecting: D-1.0.0 (conflict: A => D==2.0.0)\n"
2113 ++ "[__1] fail (backjumping, conflict set: A, D)\n"
2114 ++ "After searching the rest of the dependency tree exhaustively, these "
2115 ++ "were the goals I've had most trouble fulfilling: A (5), D (4)"
2117 goals :: [ExampleVar]
2118 goals = [P QualNone pkg | pkg <- ["A", "B", "C", "D"]]
2120 -- | This test uses the same packages and goal order as testMinimizeConflictSet,
2121 -- but it doesn't set --minimize-conflict-set. The solver should print the
2122 -- original final conflict set and the conflict between A and B. It should also
2123 -- suggest rerunning with --minimize-conflict-set.
2124 testNoMinimizeConflictSet :: String -> TestTree
2125 testNoMinimizeConflictSet testName =
2126 runTest $
2127 goalOrder goals $
2128 setVerbose $
2129 mkTest dbMinimizeConflictSet testName ["A"] $
2130 solverFailure (== expectedMsg)
2131 where
2132 expectedMsg =
2133 "Could not resolve dependencies:\n"
2134 ++ "[__0] trying: A-3.0.0 (user goal)\n"
2135 ++ "[__1] next goal: B (dependency of A)\n"
2136 ++ "[__1] rejecting: B-1.0.0 (conflict: A => B==2.0.0)\n"
2137 ++ "[__1] fail (backjumping, conflict set: A, B)\n"
2138 ++ "After searching the rest of the dependency tree exhaustively, "
2139 ++ "these were the goals I've had most trouble fulfilling: "
2140 ++ "A (7), B (2), C (2), D (2)\n"
2141 ++ "Try running with --minimize-conflict-set to improve the error message."
2143 goals :: [ExampleVar]
2144 goals = [P QualNone pkg | pkg <- ["A", "B", "C", "D"]]
2146 {-------------------------------------------------------------------------------
2147 Simple databases for the illustrations for the backjumping blog post
2148 -------------------------------------------------------------------------------}
2150 -- | Motivate conflict sets
2151 dbBJ1a :: ExampleDb
2152 dbBJ1a =
2153 [ Right $ exAv "A" 1 [ExFix "B" 1]
2154 , Right $ exAv "A" 2 [ExFix "B" 2]
2155 , Right $ exAv "B" 1 []
2158 -- | Show that we can skip some decisions
2159 dbBJ1b :: ExampleDb
2160 dbBJ1b =
2161 [ Right $ exAv "A" 1 [ExFix "B" 1]
2162 , Right $ exAv "A" 2 [ExFix "B" 2, ExAny "C"]
2163 , Right $ exAv "B" 1 []
2164 , Right $ exAv "C" 1 []
2165 , Right $ exAv "C" 2 []
2168 -- | Motivate why both A and B need to be in the conflict set
2169 dbBJ1c :: ExampleDb
2170 dbBJ1c =
2171 [ Right $ exAv "A" 1 [ExFix "B" 1]
2172 , Right $ exAv "B" 1 []
2173 , Right $ exAv "B" 2 []
2176 -- | Motivate the need for accumulating conflict sets while we walk the tree
2177 dbBJ2 :: ExampleDb
2178 dbBJ2 =
2179 [ Right $ exAv "A" 1 [ExFix "B" 1]
2180 , Right $ exAv "A" 2 [ExFix "B" 2]
2181 , Right $ exAv "B" 1 [ExFix "C" 1]
2182 , Right $ exAv "B" 2 [ExFix "C" 2]
2183 , Right $ exAv "C" 1 []
2186 -- | Motivate the need for `QGoalReason`
2187 dbBJ3 :: ExampleDb
2188 dbBJ3 =
2189 [ Right $ exAv "A" 1 [ExAny "Ba"]
2190 , Right $ exAv "A" 2 [ExAny "Bb"]
2191 , Right $ exAv "Ba" 1 [ExFix "C" 1]
2192 , Right $ exAv "Bb" 1 [ExFix "C" 2]
2193 , Right $ exAv "C" 1 []
2196 -- | `QGOalReason` not unique
2197 dbBJ4 :: ExampleDb
2198 dbBJ4 =
2199 [ Right $ exAv "A" 1 [ExAny "B", ExAny "C"]
2200 , Right $ exAv "B" 1 [ExAny "C"]
2201 , Right $ exAv "C" 1 []
2204 -- | Flags are represented somewhat strangely in the tree
2206 -- This example probably won't be in the blog post itself but as a separate
2207 -- bug report (#3409)
2208 dbBJ5 :: ExampleDb
2209 dbBJ5 =
2210 [ Right $ exAv "A" 1 [exFlagged "flagA" [ExFix "B" 1] [ExFix "C" 1]]
2211 , Right $ exAv "B" 1 [ExFix "D" 1]
2212 , Right $ exAv "C" 1 [ExFix "D" 2]
2213 , Right $ exAv "D" 1 []
2216 -- | Conflict sets for cycles
2217 dbBJ6 :: ExampleDb
2218 dbBJ6 =
2219 [ Right $ exAv "A" 1 [ExAny "B"]
2220 , Right $ exAv "B" 1 []
2221 , Right $ exAv "B" 2 [ExAny "C"]
2222 , Right $ exAv "C" 1 [ExAny "A"]
2225 -- | Conflicts not unique
2226 dbBJ7 :: ExampleDb
2227 dbBJ7 =
2228 [ Right $ exAv "A" 1 [ExAny "B", ExFix "C" 1]
2229 , Right $ exAv "B" 1 [ExFix "C" 1]
2230 , Right $ exAv "C" 1 []
2231 , Right $ exAv "C" 2 []
2234 -- | Conflict sets for SIR (C shared subgoal of independent goals A, B)
2235 dbBJ8 :: ExampleDb
2236 dbBJ8 =
2237 [ Right $ exAv "A" 1 [ExAny "C"]
2238 , Right $ exAv "B" 1 [ExAny "C"]
2239 , Right $ exAv "C" 1 []
2242 {-------------------------------------------------------------------------------
2243 Databases for build-tool-depends
2244 -------------------------------------------------------------------------------}
2246 -- | Multiple packages depending on exes from 'bt-pkg'.
2247 dbBuildTools :: ExampleDb
2248 dbBuildTools =
2249 [ Right $ exAv "A" 1 [ExBuildToolAny "bt-pkg" "exe1"]
2250 , Right $
2251 exAv
2254 [ exFlagged
2255 "flagB"
2256 [ExAny "unknown"]
2257 [ExBuildToolAny "bt-pkg" "exe1"]
2259 , Right $ exAv "C" 1 [] `withTest` exTest "testC" [ExBuildToolAny "bt-pkg" "exe1"]
2260 , Right $ exAv "D" 1 [ExBuildToolAny "bt-pkg" "unknown-exe"]
2261 , Right $ exAv "E" 1 [ExBuildToolAny "unknown-pkg" "exe1"]
2262 , Right $
2263 exAv
2266 [ exFlagged
2267 "flagF"
2268 [ExBuildToolAny "bt-pkg" "unknown-exe"]
2269 [ExAny "unknown"]
2271 , Right $ exAv "G" 1 [] `withTest` exTest "testG" [ExBuildToolAny "bt-pkg" "unknown-exe"]
2272 , Right $ exAv "H" 1 [ExBuildToolFix "bt-pkg" "exe1" 3]
2273 , Right $ exAv "bt-pkg" 4 []
2274 , Right $ exAv "bt-pkg" 3 [] `withExe` exExe "exe2" []
2275 , Right $ exAv "bt-pkg" 2 [] `withExe` exExe "exe1" []
2276 , Right $ exAv "bt-pkg" 1 []
2279 -- The solver should never choose an installed package for a build tool
2280 -- dependency.
2281 rejectInstalledBuildToolPackage :: String -> SolverTest
2282 rejectInstalledBuildToolPackage name =
2283 mkTest db name ["A"] $
2284 solverFailure $
2285 isInfixOf $
2286 "rejecting: A:B:exe.B-1.0.0/installed-1 "
2287 ++ "(does not contain executable 'exe', which is required by A)"
2288 where
2289 db :: ExampleDb
2290 db =
2291 [ Right $ exAv "A" 1 [ExBuildToolAny "B" "exe"]
2292 , Left $ exInst "B" 1 "B-1" []
2295 -- | This test forces the solver to choose B as a build-tool dependency before
2296 -- it sees the dependency on executable exe2 from B. The solver needs to check
2297 -- that the version that it already chose for B contains the necessary
2298 -- executable. This order causes a different "missing executable" error message
2299 -- than when the solver checks for the executable in the same step that it
2300 -- chooses the build-tool package.
2302 -- This case may become impossible if we ever add the executable name to the
2303 -- build-tool goal qualifier. Then this test would involve two qualified goals
2304 -- for B, one for exe1 and another for exe2.
2305 chooseExeAfterBuildToolsPackage :: Bool -> String -> SolverTest
2306 chooseExeAfterBuildToolsPackage shouldSucceed name =
2307 goalOrder goals $
2308 mkTest db name ["A"] $
2309 if shouldSucceed
2310 then solverSuccess [("A", 1), ("B", 1)]
2311 else
2312 solverFailure $
2313 isInfixOf $
2314 "rejecting: A:+flagA (requires executable 'exe2' from A:B:exe.B, "
2315 ++ "but the component does not exist)"
2316 where
2317 db :: ExampleDb
2318 db =
2319 [ Right $
2320 exAv
2323 [ ExBuildToolAny "B" "exe1"
2324 , exFlagged
2325 "flagA"
2326 [ExBuildToolAny "B" "exe2"]
2327 [ExAny "unknown"]
2329 , Right $
2330 exAv "B" 1 []
2331 `withExes` [exExe exe [] | exe <- if shouldSucceed then ["exe1", "exe2"] else ["exe1"]]
2334 goals :: [ExampleVar]
2335 goals =
2336 [ P QualNone "A"
2337 , P (QualExe "A" "B") "B"
2338 , F QualNone "A" "flagA"
2341 -- | Test that when one package depends on two executables from another package,
2342 -- both executables must come from the same instance of that package. We could
2343 -- lift this restriction in the future by adding the executable name to the goal
2344 -- qualifier.
2345 requireConsistentBuildToolVersions :: String -> SolverTest
2346 requireConsistentBuildToolVersions name =
2347 mkTest db name ["A"] $
2348 solverFailure $
2349 isInfixOf $
2350 "[__1] rejecting: A:B:exe.B-2.0.0 (conflict: A => A:B:exe.B (exe exe1)==1.0.0)\n"
2351 ++ "[__1] rejecting: A:B:exe.B-1.0.0 (conflict: A => A:B:exe.B (exe exe2)==2.0.0)"
2352 where
2353 db :: ExampleDb
2354 db =
2355 [ Right $
2356 exAv
2359 [ ExBuildToolFix "B" "exe1" 1
2360 , ExBuildToolFix "B" "exe2" 2
2362 , Right $ exAv "B" 2 [] `withExes` exes
2363 , Right $ exAv "B" 1 [] `withExes` exes
2366 exes = [exExe "exe1" [], exExe "exe2" []]
2368 -- | This test is similar to the failure case for
2369 -- chooseExeAfterBuildToolsPackage, except that the build tool is unbuildable
2370 -- instead of missing.
2371 chooseUnbuildableExeAfterBuildToolsPackage :: String -> SolverTest
2372 chooseUnbuildableExeAfterBuildToolsPackage name =
2373 constraints [ExFlagConstraint (ScopeAnyQualifier "B") "build-bt2" False] $
2374 goalOrder goals $
2375 mkTest db name ["A"] $
2376 solverFailure $
2377 isInfixOf $
2378 "rejecting: A:+use-bt2 (requires executable 'bt2' from A:B:exe.B, but "
2379 ++ "the component is not buildable in the current environment)"
2380 where
2381 db :: ExampleDb
2382 db =
2383 [ Right $
2384 exAv
2387 [ ExBuildToolAny "B" "bt1"
2388 , exFlagged
2389 "use-bt2"
2390 [ExBuildToolAny "B" "bt2"]
2391 [ExAny "unknown"]
2393 , Right $
2394 exAvNoLibrary "B" 1
2395 `withExes` [ exExe "bt1" []
2396 , exExe "bt2" [ExFlagged "build-bt2" (dependencies []) unbuildableDependencies]
2400 goals :: [ExampleVar]
2401 goals =
2402 [ P QualNone "A"
2403 , P (QualExe "A" "B") "B"
2404 , F QualNone "A" "use-bt2"
2407 {-------------------------------------------------------------------------------
2408 Databases for legacy build-tools
2409 -------------------------------------------------------------------------------}
2410 dbLegacyBuildTools1 :: ExampleDb
2411 dbLegacyBuildTools1 =
2412 [ Right $ exAv "alex" 1 [] `withExe` exExe "alex" []
2413 , Right $ exAv "A" 1 [ExLegacyBuildToolAny "alex"]
2416 -- Test that a recognized build tool dependency specifies the name of both the
2417 -- package and the executable. This db has no solution.
2418 dbLegacyBuildTools2 :: ExampleDb
2419 dbLegacyBuildTools2 =
2420 [ Right $ exAv "alex" 1 [] `withExe` exExe "other-exe" []
2421 , Right $ exAv "other-package" 1 [] `withExe` exExe "alex" []
2422 , Right $ exAv "A" 1 [ExLegacyBuildToolAny "alex"]
2425 -- Test that build-tools on a random thing doesn't matter (only
2426 -- the ones we recognize need to be in db)
2427 dbLegacyBuildTools3 :: ExampleDb
2428 dbLegacyBuildTools3 =
2429 [ Right $ exAv "A" 1 [ExLegacyBuildToolAny "otherdude"]
2432 -- Test that we can solve for different versions of executables
2433 dbLegacyBuildTools4 :: ExampleDb
2434 dbLegacyBuildTools4 =
2435 [ Right $ exAv "alex" 1 [] `withExe` exExe "alex" []
2436 , Right $ exAv "alex" 2 [] `withExe` exExe "alex" []
2437 , Right $ exAv "A" 1 [ExLegacyBuildToolFix "alex" 1]
2438 , Right $ exAv "B" 1 [ExLegacyBuildToolFix "alex" 2]
2439 , Right $ exAv "C" 1 [ExAny "A", ExAny "B"]
2442 -- Test that exe is not related to library choices
2443 dbLegacyBuildTools5 :: ExampleDb
2444 dbLegacyBuildTools5 =
2445 [ Right $ exAv "alex" 1 [ExFix "A" 1] `withExe` exExe "alex" []
2446 , Right $ exAv "A" 1 []
2447 , Right $ exAv "A" 2 []
2448 , Right $ exAv "B" 1 [ExLegacyBuildToolFix "alex" 1, ExFix "A" 2]
2451 -- Test that build-tools on build-tools works
2452 dbLegacyBuildTools6 :: ExampleDb
2453 dbLegacyBuildTools6 =
2454 [ Right $ exAv "alex" 1 [] `withExe` exExe "alex" []
2455 , Right $ exAv "happy" 1 [ExLegacyBuildToolAny "alex"] `withExe` exExe "happy" []
2456 , Right $ exAv "A" 1 [ExLegacyBuildToolAny "happy"]
2459 -- Test that build-depends on library/executable package works.
2460 -- Extracted from https://github.com/haskell/cabal/issues/3775
2461 dbIssue3775 :: ExampleDb
2462 dbIssue3775 =
2463 [ Right $ exAv "warp" 1 []
2464 , -- NB: the warp build-depends refers to the package, not the internal
2465 -- executable!
2466 Right $ exAv "A" 2 [ExFix "warp" 1] `withExe` exExe "warp" [ExAny "A"]
2467 , Right $ exAv "B" 2 [ExAny "A", ExAny "warp"]
2470 -- | Returns true if the second list contains all elements of the first list, in
2471 -- order.
2472 containsInOrder :: Eq a => [a] -> [a] -> Bool
2473 containsInOrder [] _ = True
2474 containsInOrder _ [] = False
2475 containsInOrder (x : xs) (y : ys)
2476 | x == y = containsInOrder xs ys
2477 | otherwise = containsInOrder (x : xs) ys