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
)
10 import Data
.List
(isInfixOf
)
12 import qualified Distribution
.Version
as V
15 import Test
.Tasty
as TF
18 import Language
.Haskell
.Extension
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
]
36 [ runTest
$ mkTest db1
"alreadyInstalled" ["A"] (solverSuccess
[])
37 , runTest
$ mkTest db1
"installLatest" ["B"] (solverSuccess
[("B", 2)])
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"))
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)])
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"
73 mkTest dbManualFlags
"Use default value for manual flag" ["pkg"] $
74 solverSuccess
[("pkg", 1), ("true-dep", 1)]
76 any $ isInfixOf
"rejecting: pkg:-flag (manual flag can only be changed explicitly)"
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]
88 mkTest dbManualFlags
"Toggle manual flag with flag constraint" ["pkg"] $
89 solverSuccess
[("false-dep", 1), ("pkg", 1)]
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]
97 mkTest dbSetupDepWithManualFlag name
["A"] $
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"
107 [ ExFlagConstraint
(ScopeQualified P
.QualToplevel
"B") "flag" False
108 , ExVersionConstraint
(ScopeAnyQualifier
"b-2-true-dep") V
.noVersion
112 mkTest dbSetupDepWithManualFlag name
["A"] $
117 , ("b-1-false-dep", 1)
118 , ("b-2-false-dep", 1)
120 , let name
= "User can constrain flags separately with qualified constraints"
122 [ ExFlagConstraint
(ScopeQualified P
.QualToplevel
"B") "flag" True
123 , ExFlagConstraint
(ScopeQualified
(P
.QualSetup
"A") "B") "flag" False
127 mkTest dbSetupDepWithManualFlag name
["A"] $
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]
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"
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)"
150 (\msg
-> any (msg `isInfixOf`
) lns
)
151 [ "rejecting: B:-flag " ++ failureReason
152 , "rejecting: A:setup.B:+flag " ++ failureReason
157 mkTest dbLinkedSetupDepWithManualFlag name
["A"] $
158 SolverResult checkFullLog
(Left
$ const True)
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"
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)])
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)])
195 "Base and non-reinstallable"
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)")
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)]
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)")
208 "reject-unconstrained"
211 mkTest db12
"missing syb" ["E"] $
212 solverFailure
(isInfixOf
"not a user-provided goal")
215 mkTest db12
"all goals" ["E", "syb"] $
216 solverSuccess
[("E", 1), ("syb", 2)]
219 mkTest db17
"backtracking" ["A", "B"] $
220 solverSuccess
[("A", 2), ("B", 1)]
223 mkTest db17
"failure message" ["A"] $
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"
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"
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)])
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)])
266 "Qualified Package Constraints"
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]
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)]
276 [ ExVersionConstraint
(ScopeQualified P
.QualToplevel
"D") $ mkVersionRange
1 4
277 , ExVersionConstraint
(ScopeQualified
(P
.QualSetup
"B") "D") $ mkVersionRange
4 7
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]
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)]
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)])
295 [ ExPkgPref
"A" $ mkvrOrEarlier
2
296 , ExPkgPref
"A" $ mkvrOrEarlier
1
298 $ mkTest db13
"selectPreferredVersionMultiple" ["A"] (solverSuccess
[("A", 1)])
301 [ ExPkgPref
"A" $ mkvrOrEarlier
1
302 , ExPkgPref
"A" $ mkvrOrEarlier
2
304 $ mkTest db13
"selectPreferredVersionMultiple2" ["A"] (solverSuccess
[("A", 1)])
307 [ ExPkgPref
"A" $ mkvrThis
1
308 , ExPkgPref
"A" $ mkvrThis
2
310 $ mkTest db13
"selectPreferredVersionMultiple3" ["A"] (solverSuccess
[("A", 2)])
313 [ ExPkgPref
"A" $ mkvrThis
1
314 , ExPkgPref
"A" $ mkvrOrEarlier
2
316 $ mkTest db13
"selectPreferredVersionMultiple4" ["A"] (solverSuccess
[("A", 1)])
321 mkTest dbStanzaPreferences1
"disable tests by default" ["pkg"] $
322 solverSuccess
[("pkg", 1)]
324 preferences
[ExStanzaPref
"pkg" [TestStanzas
]] $
325 mkTest dbStanzaPreferences1
"enable tests with testing preference" ["pkg"] $
326 solverSuccess
[("pkg", 1), ("test-dep", 1)]
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"
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)])
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)])
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
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)])
376 "main library dependencies"
377 [ let db
= [Right
$ exAvNoLibrary
"A" 1 `withExe` exExe
"exe" []]
379 mkTest db
"install build target without a library" ["A"] $
380 solverSuccess
[("A", 1)]
382 [ Right
$ exAv
"A" 1 [ExAny
"B"]
383 , Right
$ exAvNoLibrary
"B" 1 `withExe` exExe
"exe" []
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" []
390 [ Right
$ exAv
"A" 1 [ExAny
"B"]
391 , Right
$ exAvNoLibrary
"B" 2 `withExe` exe
392 , Right
$ exAv
"B" 1 [] `withExe` exe
395 mkTest db
"choose version of build-depends dependency that has a library" ["A"] $
396 solverSuccess
[("A", 1), ("B", 1)]
399 "sub-library dependencies"
401 [ Right
$ exAv
"A" 1 [ExSubLibAny
"B" "sub-lib"]
402 , Right
$ exAv
"B" 1 []
405 mkTest db
"reject package that is missing required sub-library" ["A"] $
408 "rejecting: B-1.0.0 (does not contain library 'sub-lib', which is required by A)"
410 [ Right
$ exAv
"A" 1 [ExSubLibAny
"B" "sub-lib"]
411 , Right
$ exAvNoLibrary
"B" 1 `withSubLibrary` exSubLib
"sub-lib" []
414 mkTest db
"reject package with private but required sub-library" ["A"] $
417 "rejecting: B-1.0.0 (library 'sub-lib' is private, but it is required by A)"
419 [ Right
$ exAv
"A" 1 [ExSubLibAny
"B" "sub-lib"]
422 `withSubLibrary` exSubLib
"sub-lib" [ExFlagged
"make-lib-private" (dependencies
[]) publicDependencies
]
425 constraints
[ExFlagConstraint
(ScopeAnyQualifier
"B") "make-lib-private" True] $
426 mkTest db
"reject package with sub-library made private by flag constraint" ["A"] $
429 "rejecting: B-1.0.0 (library 'sub-lib' is private, but it is required by A)"
431 [ Right
$ exAv
"A" 1 [ExSubLibAny
"B" "sub-lib"]
434 `withSubLibrary` exSubLib
"sub-lib" [ExFlagged
"make-lib-private" (dependencies
[]) publicDependencies
]
437 mkTest db
"treat sub-library as visible even though flag choice could make it private" ["A"] $
438 solverSuccess
[("A", 1), ("B", 1)]
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
]
452 mkTest db
"reject package that requires a private sub-library" ["A", "C"] $
455 "rejecting: C-1.0.0 (requires library 'sub-lib' from B, but the component is private)"
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
462 mkTest db
"choose version of package containing correct sub-library" ["A"] $
463 solverSuccess
[("A", 1), ("B", 1)]
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
470 mkTest db
"choose version of package with public sub-library" ["A"] $
471 solverSuccess
[("A", 1), ("B", 1)]
473 , -- build-tool-depends dependencies
476 [ runTest
$ mkTest dbBuildTools
"simple exe dependency" ["A"] (solverSuccess
[("A", 1), ("bt-pkg", 2)])
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)])
483 mkTest dbBuildTools
"test suite exe dependency" ["C"] (solverSuccess
[("C", 1), ("bt-pkg", 2)])
485 mkTest dbBuildTools
"unknown exe" ["D"] $
486 solverFailure
(isInfixOf
"does not contain executable 'unknown-exe', which is required by D")
488 disableSolveExecutables
$
489 mkTest dbBuildTools
"don't check for build tool executables in legacy mode" ["D"] $
490 solverSuccess
[("D", 1)]
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)")
495 mkTest dbBuildTools
"unknown flagged exe" ["F"] $
496 solverFailure
(isInfixOf
"does not contain executable 'unknown-exe', which is required by F +flagF")
499 mkTest dbBuildTools
"unknown test suite exe" ["G"] $
500 solverFailure
(isInfixOf
"does not contain executable 'unknown-exe', which is required by G *test")
502 mkTest dbBuildTools
"wrong exe for build tool package version" ["H"] $
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
518 [ runTest
$ mkTest dbLegacyBuildTools1
"bt1" ["A"] (solverSuccess
[("A", 1), ("alex", 1)])
520 disableSolveExecutables
$
521 mkTest dbLegacyBuildTools1
"bt1 - don't install build tool packages in legacy mode" ["A"] (solverSuccess
[("A", 1)])
523 mkTest dbLegacyBuildTools2
"bt2" ["A"] $
524 solverFailure
(isInfixOf
"does not contain executable 'alex', which is required by A")
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
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
]]
543 constraints
[flagConstraint
"A" "build-lib" False] $
544 mkTest db
"install unbuildable library" ["A"] $
545 solverSuccess
[("A", 1)]
549 `withExe` exExe
"exe" [ExFlagged
"build-exe" (dependencies
[]) unbuildableDependencies
]
552 constraints
[flagConstraint
"A" "build-exe" False] $
553 mkTest db
"install unbuildable exe" ["A"] $
554 solverSuccess
[("A", 1)]
556 [ Right
$ exAv
"A" 1 [ExAny
"B"]
557 , Right
$ exAv
"B" 1 [ExFlagged
"build-lib" (dependencies
[]) unbuildableDependencies
]
560 constraints
[flagConstraint
"B" "build-lib" False] $
561 mkTest db
"reject library dependency with unbuildable library" ["A"] $
564 "rejecting: B-1.0.0 (library is not buildable in the "
565 ++ "current environment, but it is required by A)"
567 [ Right
$ exAv
"A" 1 [ExBuildToolAny
"B" "bt"]
569 exAv
"B" 1 [ExFlagged
"build-lib" (dependencies
[]) unbuildableDependencies
]
570 `withExe` exExe
"bt" []
573 constraints
[flagConstraint
"B" "build-lib" False] $
574 mkTest db
"allow build-tool dependency with unbuildable library" ["A"] $
575 solverSuccess
[("A", 1), ("B", 1)]
577 [ Right
$ exAv
"A" 1 [ExBuildToolAny
"B" "bt"]
580 `withExe` exExe
"bt" [ExFlagged
"build-exe" (dependencies
[]) unbuildableDependencies
]
583 constraints
[flagConstraint
"B" "build-exe" False] $
584 mkTest db
"reject build-tool dependency with unbuildable exe" ["A"] $
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)"
590 chooseUnbuildableExeAfterBuildToolsPackage
591 "choose unbuildable exe after choosing its package"
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.
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"]
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"
624 mkTest db
"skip version due to problematic dependency" ["A"] $
625 SolverResult
(isInfixOf msg
) $
627 , -- Skipping a version because of a restrictive constraint on a
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
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 []
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 "
650 , "[__0] trying: A-1.0.0"
651 , "[__1] next goal: B (dependency of A)"
652 , "[__1] trying: B-11.0.0"
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
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"]]
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"
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).
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"]]
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"
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.
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"]]
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"
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'
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 []
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
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
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"
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.
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"]]
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"
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
857 [ -- See issue #3203. The solver should only choose a version for A once.
859 let db
= [Right
$ exAv
"A" 1 []]
861 p
:: [String] -> Bool
864 && length (filter ("trying: A" `isInfixOf`
) lg
) == 1
866 mkTest db
"deduplicate targets" ["A", "A"] $
870 let db
= [Right
$ exAv
"A" 1 [ExAny
"B"]]
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"
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
)
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
)
916 "package versions abbreviation (issue #9559.)"
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
)
929 [ Right
$ exAv
"A" 1 []
930 , Right
$ exAv
"A" 2 []
931 , Right
$ exAv
"A" 3 []
932 , Right
$ exAv
"B" 1 [ExFix
"A" 4]
934 rejecting
= "rejecting: A-3.0.0"
935 skipping
= "skipping: A; 2.0.0, 1.0.0"
936 in mkTest db
"show skipping versions list" ["B"] $
937 solverFailure
(\msg
-> rejecting `isInfixOf` msg
&& skipping `isInfixOf` msg
)
942 indep
= independentGoals
943 mkvrThis
= V
.thisVersion
. makeV
944 mkvrOrEarlier
= V
.orEarlierVersion
. makeV
945 makeV v
= V
.mkVersion
[v
, 0, 0]
947 data GoalOrder
= FixedGoalOrder | DefaultGoalOrder
949 {-------------------------------------------------------------------------------
950 Specific example database for the tests
951 -------------------------------------------------------------------------------}
955 let a
= exInst
"A" 1 "A-1" []
957 , Right
$ exAv
"B" 1 [ExAny
"A"]
958 , Right
$ exAv
"B" 2 [ExAny
"A"]
959 , Right
$ exAv
"C" 1 [ExFix
"B" 1]
960 , Right
$ exAv
"D" 1 [ExFix
"B" 2]
961 , Right
$ exAv
"E" 1 [ExAny
"B"]
962 , Right
$ exAv
"F" 1 [ExFix
"B" 1, ExAny
"E"]
963 , Right
$ exAv
"G" 1 [ExFix
"B" 2, ExAny
"E"]
964 , Right
$ exAv
"Z" 1 []
967 -- In this example, we _can_ install C and D as independent goals, but we have
968 -- to pick two different versions for B (arbitrarily)
971 [ Right
$ exAv
"A" 1 []
972 , Right
$ exAv
"A" 2 []
973 , Right
$ exAv
"B" 1 [ExAny
"A"]
974 , Right
$ exAv
"B" 2 [ExAny
"A"]
975 , Right
$ exAv
"C" 1 [ExAny
"B", ExFix
"A" 1]
976 , Right
$ exAv
"D" 1 [ExAny
"B", ExFix
"A" 2]
981 [ Right
$ exAv
"A" 1 []
982 , Right
$ exAv
"A" 2 []
983 , Right
$ exAv
"B" 1 [exFlagged
"flagB" [ExFix
"A" 1] [ExFix
"A" 2]]
984 , Right
$ exAv
"C" 1 [ExFix
"A" 1, ExAny
"B"]
985 , Right
$ exAv
"D" 1 [ExFix
"A" 2, ExAny
"B"]
988 -- | Like db3, but the flag picks a different package rather than a
989 -- different package version
991 -- In db3 we cannot install C and D as independent goals because:
993 -- * The multiple instance restriction says C and D _must_ share B
994 -- * Since C relies on A-1, C needs B to be compiled with flagB on
995 -- * Since D relies on A-2, D needs B to be compiled with flagB off
996 -- * Hence C and D have incompatible requirements on B's flags.
998 -- However, _even_ if we don't check explicitly that we pick the same flag
999 -- assignment for 0.B and 1.B, we will still detect the problem because
1000 -- 0.B depends on 0.A-1, 1.B depends on 1.A-2, hence we cannot link 0.A to
1001 -- 1.A and therefore we cannot link 0.B to 1.B.
1003 -- In db4 the situation however is trickier. We again cannot install
1004 -- packages C and D as independent goals because:
1006 -- * As above, the multiple instance restriction says that C and D _must_ share B
1007 -- * Since C relies on Ax-2, it requires B to be compiled with flagB off
1008 -- * Since D relies on Ay-2, it requires B to be compiled with flagB on
1009 -- * Hence C and D have incompatible requirements on B's flags.
1011 -- But now this requirement is more indirect. If we only check dependencies
1012 -- we don't see the problem:
1014 -- * We link 0.B to 1.B
1015 -- * 0.B relies on Ay-1
1016 -- * 1.B relies on Ax-1
1018 -- We will insist that 0.Ay will be linked to 1.Ay, and 0.Ax to 1.Ax, but since
1019 -- we only ever assign to one of these, these constraints are never broken.
1022 [ Right
$ exAv
"Ax" 1 []
1023 , Right
$ exAv
"Ax" 2 []
1024 , Right
$ exAv
"Ay" 1 []
1025 , Right
$ exAv
"Ay" 2 []
1026 , Right
$ exAv
"B" 1 [exFlagged
"flagB" [ExFix
"Ax" 1] [ExFix
"Ay" 1]]
1027 , Right
$ exAv
"C" 1 [ExFix
"Ax" 2, ExAny
"B"]
1028 , Right
$ exAv
"D" 1 [ExFix
"Ay" 2, ExAny
"B"]
1031 -- | Simple database containing one package with a manual flag.
1032 dbManualFlags
:: ExampleDb
1035 declareFlags
[ExFlag
"flag" True Manual
] $
1036 exAv
"pkg" 1 [exFlagged
"flag" [ExAny
"true-dep"] [ExAny
"false-dep"]]
1037 , Right
$ exAv
"true-dep" 1 []
1038 , Right
$ exAv
"false-dep" 1 []
1041 -- | Database containing a setup dependency with a manual flag. A's library and
1042 -- setup script depend on two different versions of B. B's manual flag can be
1043 -- set to different values in the two places where it is used.
1044 dbSetupDepWithManualFlag
:: ExampleDb
1045 dbSetupDepWithManualFlag
=
1046 let bFlags
= [ExFlag
"flag" True Manual
]
1047 in [ Right
$ exAv
"A" 1 [ExFix
"B" 1] `withSetupDeps`
[ExFix
"B" 2]
1049 declareFlags bFlags
$
1055 [ExAny
"b-1-true-dep"]
1056 [ExAny
"b-1-false-dep"]
1059 declareFlags bFlags
$
1065 [ExAny
"b-2-true-dep"]
1066 [ExAny
"b-2-false-dep"]
1068 , Right
$ exAv
"b-1-true-dep" 1 []
1069 , Right
$ exAv
"b-1-false-dep" 1 []
1070 , Right
$ exAv
"b-2-true-dep" 1 []
1071 , Right
$ exAv
"b-2-false-dep" 1 []
1074 -- | A database similar to 'dbSetupDepWithManualFlag', except that the library
1075 -- and setup script both depend on B-1. B must be linked because of the Single
1076 -- Instance Restriction, and its flag can only have one value.
1077 dbLinkedSetupDepWithManualFlag
:: ExampleDb
1078 dbLinkedSetupDepWithManualFlag
=
1079 [ Right
$ exAv
"A" 1 [ExFix
"B" 1] `withSetupDeps`
[ExFix
"B" 1]
1081 declareFlags
[ExFlag
"flag" True Manual
] $
1087 [ExAny
"b-1-true-dep"]
1088 [ExAny
"b-1-false-dep"]
1090 , Right
$ exAv
"b-1-true-dep" 1 []
1091 , Right
$ exAv
"b-1-false-dep" 1 []
1094 -- | Some tests involving testsuites
1096 -- Note that in this test framework test suites are always enabled; if you
1097 -- want to test without test suites just set up a test database without
1100 -- * C depends on A (through its test suite)
1101 -- * D depends on B-2 (through its test suite), but B-2 is unavailable
1102 -- * E depends on A-1 directly and on A through its test suite. We prefer
1103 -- to use A-1 for the test suite in this case.
1104 -- * F depends on A-1 directly and on A-2 through its test suite. In this
1105 -- case we currently fail to install F, although strictly speaking
1106 -- test suites should be considered independent goals.
1107 -- * G is like E, but for version A-2. This means that if we cannot install
1108 -- E and G together, unless we regard them as independent goals.
1111 [ Right
$ exAv
"A" 1 []
1112 , Right
$ exAv
"A" 2 []
1113 , Right
$ exAv
"B" 1 []
1114 , Right
$ exAv
"C" 1 [] `withTest` exTest
"testC" [ExAny
"A"]
1115 , Right
$ exAv
"D" 1 [] `withTest` exTest
"testD" [ExFix
"B" 2]
1116 , Right
$ exAv
"E" 1 [ExFix
"A" 1] `withTest` exTest
"testE" [ExAny
"A"]
1117 , Right
$ exAv
"F" 1 [ExFix
"A" 1] `withTest` exTest
"testF" [ExFix
"A" 2]
1118 , Right
$ exAv
"G" 1 [ExFix
"A" 2] `withTest` exTest
"testG" [ExAny
"A"]
1121 -- Now the _dependencies_ have test suites
1124 -- * Installing C is a simple example. C wants version 1 of A, but depends on
1126 -- B, and B's testsuite depends on an any version of A. In this case we prefer
1127 -- to link (if we don't regard test suites as independent goals then of course
1128 -- linking here doesn't even come into it).
1130 -- * Installing [C, D] means that we prefer to link B -- depending on how we
1132 -- set things up, this means that we should also link their test suites.
1135 [ Right
$ exAv
"A" 1 []
1136 , Right
$ exAv
"A" 2 []
1137 , Right
$ exAv
"B" 1 [] `withTest` exTest
"testA" [ExAny
"A"]
1138 , Right
$ exAv
"C" 1 [ExFix
"A" 1, ExAny
"B"]
1139 , Right
$ exAv
"D" 1 [ExAny
"B"]
1142 -- | This test checks that the solver can backjump to disable a flag, even if
1143 -- the problematic dependency is also under a test suite. (issue #4390)
1145 -- The goal order forces the solver to choose the flag before enabling testing.
1146 -- Previously, the solver couldn't handle this case, because it only tried to
1147 -- disable testing, and when that failed, it backjumped past the flag choice.
1148 -- The solver should also try to set the flag to false, because that avoids the
1150 testTestSuiteWithFlag
:: String -> SolverTest
1151 testTestSuiteWithFlag name
=
1154 mkTest db name
["A", "B"] $
1155 solverSuccess
[("A", 1), ("B", 1)]
1161 `withTest` exTest
"test" [exFlagged
"flag" [ExFix
"B" 2] []]
1162 , Right
$ exAv
"B" 1 []
1165 goals
:: [ExampleVar
]
1169 , F QualNone
"A" "flag"
1170 , S QualNone
"A" TestStanzas
1173 -- Packages with setup dependencies
1177 -- * B: Simple example, just make sure setup deps are taken into account at all
1179 -- * C: Both the package and the setup script depend on any version of A.
1181 -- In this case we prefer to link
1183 -- * D: Variation on C.1 where the package requires a specific (not latest)
1185 -- version but the setup dependency is not fixed. Again, we prefer to
1186 -- link (picking the older version)
1188 -- * E: Variation on C.2 with the setup dependency the more inflexible.
1190 -- Currently, in this case we do not see the opportunity to link because
1191 -- we consider setup dependencies after normal dependencies; we will
1192 -- pick A.2 for E, then realize we cannot link E.setup.A to A.2, and pick
1193 -- A.1 instead. This isn't so easy to fix (if we want to fix it at all);
1194 -- in particular, considering setup dependencies _before_ other deps is
1195 -- not an improvement, because in general we would prefer to link setup
1196 -- setups to package deps, rather than the other way around. (For example,
1197 -- if we change this ordering then the test for D would start to install
1198 -- two versions of A).
1200 -- * F: The package and the setup script depend on different versions of A.
1202 -- This will only work if setup dependencies are considered independent.
1205 [ Right
$ exAv
"A" 1 []
1206 , Right
$ exAv
"A" 2 []
1207 , Right
$ exAv
"B" 1 [] `withSetupDeps`
[ExAny
"A"]
1208 , Right
$ exAv
"C" 1 [ExAny
"A"] `withSetupDeps`
[ExAny
"A"]
1209 , Right
$ exAv
"D" 1 [ExFix
"A" 1] `withSetupDeps`
[ExAny
"A"]
1210 , Right
$ exAv
"E" 1 [ExAny
"A"] `withSetupDeps`
[ExFix
"A" 1]
1211 , Right
$ exAv
"F" 1 [ExFix
"A" 2] `withSetupDeps`
[ExFix
"A" 1]
1214 -- If we install C and D together (not as independent goals), we need to build
1215 -- both B.1 and B.2, both of which depend on A.
1218 [ Right
$ exAv
"A" 1 []
1219 , Right
$ exAv
"B" 1 [ExAny
"A"]
1220 , Right
$ exAv
"B" 2 [ExAny
"A"]
1221 , Right
$ exAv
"C" 1 [] `withSetupDeps`
[ExFix
"B" 1]
1222 , Right
$ exAv
"D" 1 [] `withSetupDeps`
[ExFix
"B" 2]
1225 -- Extended version of `db8` so that we have nested setup dependencies
1229 ++ [ Right
$ exAv
"E" 1 [ExAny
"C"]
1230 , Right
$ exAv
"E" 2 [ExAny
"D"]
1231 , Right
$ exAv
"F" 1 [] `withSetupDeps`
[ExFix
"E" 1]
1232 , Right
$ exAv
"G" 1 [] `withSetupDeps`
[ExFix
"E" 2]
1235 -- Multiple already-installed packages with inter-dependencies, and one package
1236 -- (C) that depends on package A-1 for its setup script and package A-2 as a
1237 -- library dependency.
1240 let rts
= exInst
"rts" 1 "rts-inst" []
1241 ghc_prim
= exInst
"ghc-prim" 1 "ghc-prim-inst" [rts
]
1242 base
= exInst
"base" 1 "base-inst" [rts
, ghc_prim
]
1243 a1
= exInst
"A" 1 "A1-inst" [base
]
1244 a2
= exInst
"A" 2 "A2-inst" [base
]
1250 , Right
$ exAv
"C" 1 [ExFix
"A" 2] `withSetupDeps`
[ExFix
"A" 1]
1253 -- | This database tests that a package's setup dependencies are correctly
1254 -- linked when the package is linked. See pull request #3268.
1256 -- When A and B are installed as independent goals, their dependencies on C must
1257 -- be linked, due to the single instance restriction. Since C depends on D, 0.D
1258 -- and 1.D must be linked. C also has a setup dependency on D, so 0.C-setup.D
1259 -- and 1.C-setup.D must be linked. However, D's two link groups must remain
1260 -- independent. The solver should be able to choose D-1 for C's library and D-2
1261 -- for C's setup script.
1262 dbSetupDeps
:: ExampleDb
1264 [ Right
$ exAv
"A" 1 [ExAny
"C"]
1265 , Right
$ exAv
"B" 1 [ExAny
"C"]
1266 , Right
$ exAv
"C" 1 [ExFix
"D" 1] `withSetupDeps`
[ExFix
"D" 2]
1267 , Right
$ exAv
"D" 1 []
1268 , Right
$ exAv
"D" 2 []
1271 -- | Tests for dealing with base shims
1274 let base3
= exInst
"base" 3 "base-3-inst" [base4
]
1275 base4
= exInst
"base" 4 "base-4-inst" []
1278 , Right
$ exAv
"A" 1 [ExFix
"base" 3]
1281 -- | Slightly more realistic version of db11 where base-3 depends on syb
1282 -- This means that if a package depends on base-3 and on syb, then they MUST
1283 -- share the version of syb
1285 -- * Package A relies on base-3 (which relies on base-4)
1286 -- * Package B relies on base-4
1287 -- * Package C relies on both A and B
1288 -- * Package D relies on base-3 and on syb-2, which is not possible because
1289 -- base-3 has a dependency on syb-1 (non-inheritance of the Base qualifier)
1290 -- * Package E relies on base-4 and on syb-2, which is fine.
1293 let base3
= exInst
"base" 3 "base-3-inst" [base4
, syb1
]
1294 base4
= exInst
"base" 4 "base-4-inst" []
1295 syb1
= exInst
"syb" 1 "syb-1-inst" [base4
]
1299 , Right
$ exAv
"syb" 2 [ExFix
"base" 4]
1300 , Right
$ exAv
"A" 1 [ExFix
"base" 3, ExAny
"syb"]
1301 , Right
$ exAv
"B" 1 [ExFix
"base" 4, ExAny
"syb"]
1302 , Right
$ exAv
"C" 1 [ExAny
"A", ExAny
"B"]
1303 , Right
$ exAv
"D" 1 [ExFix
"base" 3, ExFix
"syb" 2]
1304 , Right
$ exAv
"E" 1 [ExFix
"base" 4, ExFix
"syb" 2]
1313 [ExAny
"ghc-prim", ExAny
"integer-simple", ExAny
"integer-gmp"]
1314 , Right
$ exAv
"ghc-prim" 1 []
1315 , Right
$ exAv
"integer-simple" 1 []
1316 , Right
$ exAv
"integer-gmp" 1 []
1319 dbNonupgrade
:: ExampleDb
1321 [ Left
$ exInst
"ghc" 1 "ghc-1" []
1322 , Right
$ exAv
"ghc" 2 []
1323 , Right
$ exAv
"ghci" 2 []
1324 , Right
$ exAv
"ghc-boot" 2 []
1325 , Right
$ exAv
"A" 1 [ExFix
"ghc" 2]
1326 , Right
$ exAv
"B" 1 [ExFix
"ghci" 2]
1327 , Right
$ exAv
"C" 1 [ExFix
"ghc-boot" 2]
1332 [ Right
$ exAv
"A" 1 []
1333 , Right
$ exAv
"A" 2 []
1334 , Right
$ exAv
"A" 3 []
1337 -- | A, B, and C have three different dependencies on D that can be set to
1338 -- different versions with qualified constraints. Each version of D can only
1339 -- be depended upon by one version of A, B, or C, so that the versions of A, B,
1340 -- and C in the install plan indicate which version of D was chosen for each
1341 -- dependency. The one-to-one correspondence between versions of A, B, and C and
1342 -- versions of D also prevents linking, which would complicate the solver's
1344 dbConstraints
:: ExampleDb
1346 [Right
$ exAv
"A" v
[ExFix
"D" v
] | v
<- [1, 4, 7]]
1347 ++ [Right
$ exAv
"B" v
[] `withSetupDeps`
[ExFix
"D" v
] | v
<- [2, 5, 8]]
1348 ++ [Right
$ exAv
"C" v
[] `withSetupDeps`
[ExFix
"D" v
] | v
<- [3, 6, 9]]
1349 ++ [Right
$ exAv
"D" v
[] | v
<- [1 .. 9]]
1351 dbStanzaPreferences1
:: ExampleDb
1352 dbStanzaPreferences1
=
1353 [ Right
$ exAv
"pkg" 1 [] `withTest` exTest
"test" [ExAny
"test-dep"]
1354 , Right
$ exAv
"test-dep" 1 []
1357 dbStanzaPreferences2
:: ExampleDb
1358 dbStanzaPreferences2
=
1359 [ Right
$ exAv
"pkg" 1 [] `withTest` exTest
"test" [ExAny
"unknown"]
1362 -- | This is a test case for a bug in stanza preferences (#3930). The solver
1363 -- should be able to install 'A' by enabling 'flag' and disabling testing. When
1364 -- it tries goals in the specified order and prefers testing, it encounters
1365 -- 'unknown-pkg2'. 'unknown-pkg2' is only introduced by testing and 'flag', so
1366 -- the conflict set should contain both of those variables. Before the fix, it
1367 -- only contained 'flag'. The solver backjumped past the choice to disable
1368 -- testing and failed to find the solution.
1369 testStanzaPreference
:: String -> TestTree
1370 testStanzaPreference name
=
1378 [ExAny
"unknown-pkg1"]
1384 [ExAny
"unknown-pkg2"]
1389 , F QualNone
"A" "flag"
1390 , S QualNone
"A" TestStanzas
1394 preferences
[ExStanzaPref
"A" [TestStanzas
]] $
1395 mkTest
[Right pkg
] name
["A"] $
1396 solverSuccess
[("A", 1)]
1398 -- | Database with some cycles
1400 -- * Simplest non-trivial cycle: A -> B and B -> A
1401 -- * There is a cycle C -> D -> C, but it can be broken by picking the
1402 -- right flag assignment.
1405 [ Right
$ exAv
"A" 1 [ExAny
"B"]
1406 , Right
$ exAv
"B" 1 [ExAny
"A"]
1407 , Right
$ exAv
"C" 1 [exFlagged
"flagC" [ExAny
"D"] [ExAny
"E"]]
1408 , Right
$ exAv
"D" 1 [ExAny
"C"]
1409 , Right
$ exAv
"E" 1 []
1412 -- | Cycles through setup dependencies
1414 -- The first cycle is unsolvable: package A has a setup dependency on B,
1415 -- B has a regular dependency on A, and we only have a single version available
1418 -- The second cycle can be broken by picking different versions: package C-2.0
1419 -- has a setup dependency on D, and D has a regular dependency on C-*. However,
1420 -- version C-1.0 is already available (perhaps it didn't have this setup dep).
1421 -- Thus, we should be able to break this cycle even if we are installing package
1422 -- E, which explicitly depends on C-2.0.
1425 [ -- First example (real cycle, no solution)
1426 Right
$ exAv
"A" 1 [] `withSetupDeps`
[ExAny
"B"]
1427 , Right
$ exAv
"B" 1 [ExAny
"A"]
1428 , -- Second example (cycle can be broken by picking versions carefully)
1429 Left
$ exInst
"C" 1 "C-1-inst" []
1430 , Right
$ exAv
"C" 2 [] `withSetupDeps`
[ExAny
"D"]
1431 , Right
$ exAv
"D" 1 [ExAny
"C"]
1432 , Right
$ exAv
"E" 1 [ExFix
"C" 2]
1435 -- | Detect a cycle between a package and its setup script.
1437 -- This type of cycle can easily occur when v2-build adds default setup
1438 -- dependencies to packages without custom-setup stanzas. For example, cabal
1439 -- adds 'time' as a setup dependency for 'time'. The solver should detect the
1440 -- cycle when it attempts to link the setup and non-setup instances of the
1441 -- package and then choose a different version for the setup dependency.
1442 issue4161
:: String -> SolverTest
1445 mkTest db name
["target"] $
1446 SolverResult checkFullLog
$
1447 Right
[("target", 1), ("time", 1), ("time", 2)]
1451 [ Right
$ exAv
"target" 1 [ExFix
"time" 2]
1452 , Right
$ exAv
"time" 2 [] `withSetupDeps`
[ExAny
"time"]
1453 , Right
$ exAv
"time" 1 []
1456 checkFullLog
:: [String] -> Bool
1460 "rejecting: time:setup.time~>time-2.0.0 (cyclic dependencies; "
1461 ++ "conflict set: time:setup.time)"
1463 -- | Packages pkg-A, pkg-B, and pkg-C form a cycle. The solver should backtrack
1464 -- as soon as it chooses the last package in the cycle, to avoid searching parts
1465 -- of the tree that have no solution. Since there is no way to break the cycle,
1466 -- it should fail with an error message describing the cycle.
1467 testCyclicDependencyErrorMessages
:: String -> SolverTest
1468 testCyclicDependencyErrorMessages name
=
1470 mkTest db name
["pkg-A"] $
1471 SolverResult checkFullLog
$
1472 Left checkSummarizedLog
1476 [ Right
$ exAv
"pkg-A" 1 [ExAny
"pkg-B"]
1477 , Right
$ exAv
"pkg-B" 1 [ExAny
"pkg-C"]
1478 , Right
$ exAv
"pkg-C" 1 [ExAny
"pkg-A", ExAny
"pkg-D"]
1479 , Right
$ exAv
"pkg-D" 1 [ExAny
"pkg-E"]
1480 , Right
$ exAv
"pkg-E" 1 []
1483 -- The solver should backtrack as soon as pkg-A, pkg-B, and pkg-C form a
1484 -- cycle. It shouldn't try pkg-D or pkg-E.
1485 checkFullLog
:: [String] -> Bool
1487 not . any (\l
-> "pkg-D" `isInfixOf` l ||
"pkg-E" `isInfixOf` l
)
1489 checkSummarizedLog
:: String -> Bool
1490 checkSummarizedLog
=
1491 isInfixOf
"rejecting: pkg-C-1.0.0 (cyclic dependencies; conflict set: pkg-A, pkg-B, pkg-C)"
1493 -- Solve for pkg-D and pkg-E last.
1494 goals
:: [ExampleVar
]
1495 goals
= [P QualNone
("pkg-" ++ [c
]) | c
<- ['A
' .. 'E
']]
1497 -- | Check that the solver can backtrack after encountering the SIR (issue #2843)
1499 -- When A and B are installed as independent goals, the single instance
1500 -- restriction prevents B from depending on C. This database tests that the
1501 -- solver can backtrack after encountering the single instance restriction and
1502 -- choose the only valid flag assignment (-flagA +flagB):
1504 -- > flagA flagB B depends on
1506 -- > Off On E-* <-- only valid flag assignment
1507 -- > Off Off D-2.0, C-*
1509 -- Since A depends on C-* and D-1.0, and C-1.0 depends on any version of D,
1510 -- we must build C-1.0 against D-1.0. Since B depends on D-2.0, we cannot have
1511 -- C in the transitive closure of B's dependencies, because that would mean we
1512 -- would need two instances of C: one built against D-1.0 and one built against
1516 [ Right
$ exAv
"A" 1 [ExAny
"C", ExFix
"D" 1]
1531 , Right
$ exAv
"C" 1 [ExAny
"D"]
1532 , Right
$ exAv
"D" 1 []
1533 , Right
$ exAv
"D" 2 []
1534 , Right
$ exAv
"E" 1 []
1537 -- Try to get the solver to backtrack while satisfying
1538 -- reject-unconstrained-dependencies: both the first and last versions of A
1539 -- require packages outside the closed set, so it will have to try the
1543 [ Right
$ exAv
"A" 1 [ExAny
"C"]
1544 , Right
$ exAv
"A" 2 [ExAny
"B"]
1545 , Right
$ exAv
"A" 3 [ExAny
"C"]
1546 , Right
$ exAv
"B" 1 []
1547 , Right
$ exAv
"C" 1 [ExAny
"B"]
1550 -- | This test checks that when the solver discovers a constraint on a
1551 -- package's version after choosing to link that package, it can backtrack to
1552 -- try alternative versions for the linked-to package. See pull request #3327.
1554 -- When A and B are installed as independent goals, their dependencies on C
1555 -- must be linked. Since C depends on D, A and B's dependencies on D must also
1556 -- be linked. This test fixes the goal order so that the solver chooses D-2 for
1557 -- both 0.D and 1.D before it encounters the test suites' constraints. The
1558 -- solver must backtrack to try D-1 for both 0.D and 1.D.
1559 testIndepGoals2
:: String -> SolverTest
1560 testIndepGoals2 name
=
1564 mkTest db name
["A", "B"] $
1565 solverSuccess
[("A", 1), ("B", 1), ("C", 1), ("D", 1)]
1569 [ Right
$ exAv
"A" 1 [ExAny
"C"] `withTest` exTest
"test" [ExFix
"D" 1]
1570 , Right
$ exAv
"B" 1 [ExAny
"C"] `withTest` exTest
"test" [ExFix
"D" 1]
1571 , Right
$ exAv
"C" 1 [ExAny
"D"]
1572 , Right
$ exAv
"D" 1 []
1573 , Right
$ exAv
"D" 2 []
1576 goals
:: [ExampleVar
]
1578 [ P
(QualIndep
"A") "A"
1579 , P
(QualIndep
"A") "C"
1580 , P
(QualIndep
"A") "D"
1581 , P
(QualIndep
"B") "B"
1582 , P
(QualIndep
"B") "C"
1583 , P
(QualIndep
"B") "D"
1584 , S
(QualIndep
"B") "B" TestStanzas
1585 , S
(QualIndep
"A") "A" TestStanzas
1589 -- When both A and B are installed as independent goals, their dependencies on
1590 -- C must be linked. The only combination of C's flags that is consistent with
1591 -- A and B's dependencies on D is -flagA +flagB. This database tests that the
1592 -- solver can backtrack to find the right combination of flags (requiring F, but
1593 -- not E or G) and apply it to both 0.C and 1.C.
1595 -- > flagA flagB C depends on
1597 -- > Off On F-* <-- Only valid choice
1598 -- > Off Off D-2, G-*
1600 -- The single instance restriction means we cannot have one instance of C
1601 -- built against D-1 and one instance built against D-2; since A depends on
1602 -- D-1, and B depends on C-2, it is therefore important that C cannot depend
1603 -- on any version of D.
1606 [ Right
$ exAv
"A" 1 [ExAny
"C", ExFix
"D" 1]
1607 , Right
$ exAv
"B" 1 [ExAny
"C", ExFix
"D" 2]
1614 [ExFix
"D" 1, ExAny
"E"]
1618 [ExFix
"D" 2, ExAny
"G"]
1621 , Right
$ exAv
"D" 1 []
1622 , Right
$ exAv
"D" 2 []
1623 , Right
$ exAv
"E" 1 []
1624 , Right
$ exAv
"F" 1 []
1625 , Right
$ exAv
"G" 1 []
1628 -- | When both values for flagA introduce package B, the solver should be able
1629 -- to choose B before choosing a value for flagA. It should try to choose a
1630 -- version for B that is in the union of the version ranges required by +flagA
1632 commonDependencyLogMessage
:: String -> SolverTest
1633 commonDependencyLogMessage name
=
1634 mkTest db name
["A"] $
1637 "[__0] trying: A-1.0.0 (user goal)\n"
1638 ++ "[__1] next goal: B (dependency of A +/-flagA)\n"
1639 ++ "[__1] rejecting: B-2.0.0 (conflict: A +/-flagA => B==1.0.0 || ==3.0.0)"
1652 , Right
$ exAv
"B" 2 []
1655 -- | Test lifting dependencies out of multiple levels of conditionals.
1656 twoLevelDeepCommonDependencyLogMessage
:: String -> SolverTest
1657 twoLevelDeepCommonDependencyLogMessage name
=
1658 mkTest db name
["A"] $
1661 "unknown package: B (dependency of A +/-flagA +/-flagB)"
1684 -- | Test handling nested conditionals that are controlled by the same flag.
1685 -- The solver should treat flagA as introducing 'unknown' with value true, not
1686 -- both true and false. That means that when +flagA causes a conflict, the
1687 -- solver should try flipping flagA to false to resolve the conflict, rather
1688 -- than backjumping past flagA.
1689 testBackjumpingWithCommonDependency
:: String -> SolverTest
1690 testBackjumpingWithCommonDependency name
=
1691 mkTest db name
["A"] $ solverSuccess
[("A", 1), ("B", 1)]
1708 , Right
$ exAv
"B" 1 []
1711 -- | Tricky test case with independent goals (issue #2842)
1713 -- Suppose we are installing D, E, and F as independent goals:
1715 -- * D depends on A-* and C-1, requiring A-1 to be built against C-1
1716 -- * E depends on B-* and C-2, requiring B-1 to be built against C-2
1717 -- * F depends on A-* and B-*; this means we need A-1 and B-1 both to be built
1718 -- against the same version of C, violating the single instance restriction.
1720 -- We can visualize this DB as:
1735 testIndepGoals3
:: String -> SolverTest
1736 testIndepGoals3 name
=
1739 mkTest db name
["D", "E", "F"] anySolverFailure
1743 [ Right
$ exAv
"A" 1 [ExAny
"C"]
1744 , Right
$ exAv
"B" 1 [ExAny
"C"]
1745 , Right
$ exAv
"C" 1 []
1746 , Right
$ exAv
"C" 2 []
1747 , Right
$ exAv
"D" 1 [ExAny
"A", ExFix
"C" 1]
1748 , Right
$ exAv
"E" 1 [ExAny
"B", ExFix
"C" 2]
1749 , Right
$ exAv
"F" 1 [ExAny
"A", ExAny
"B"]
1752 goals
:: [ExampleVar
]
1754 [ P
(QualIndep
"D") "D"
1755 , P
(QualIndep
"D") "C"
1756 , P
(QualIndep
"D") "A"
1757 , P
(QualIndep
"E") "E"
1758 , P
(QualIndep
"E") "C"
1759 , P
(QualIndep
"E") "B"
1760 , P
(QualIndep
"F") "F"
1761 , P
(QualIndep
"F") "B"
1762 , P
(QualIndep
"F") "C"
1763 , P
(QualIndep
"F") "A"
1766 -- | This test checks that the solver correctly backjumps when dependencies
1767 -- of linked packages are not linked. It is an example where the conflict set
1768 -- from enforcing the single instance restriction is not sufficient. See pull
1771 -- When A, B, and C are installed as independent goals with the specified goal
1772 -- order, the first choice that the solver makes for E is 0.E-2. Then, when it
1773 -- chooses dependencies for B and C, it links both 1.E and 2.E to 0.E. Finally,
1774 -- the solver discovers C's test's constraint on E. It must backtrack to try
1775 -- 1.E-1 and then link 2.E to 1.E. Backjumping all the way to 0.E does not lead
1776 -- to a solution, because 0.E's version is constrained by A and cannot be
1778 testIndepGoals4
:: String -> SolverTest
1779 testIndepGoals4 name
=
1783 mkTest db name
["A", "B", "C"] $
1784 solverSuccess
[("A", 1), ("B", 1), ("C", 1), ("D", 1), ("E", 1), ("E", 2)]
1788 [ Right
$ exAv
"A" 1 [ExFix
"E" 2]
1789 , Right
$ exAv
"B" 1 [ExAny
"D"]
1790 , Right
$ exAv
"C" 1 [ExAny
"D"] `withTest` exTest
"test" [ExFix
"E" 1]
1791 , Right
$ exAv
"D" 1 [ExAny
"E"]
1792 , Right
$ exAv
"E" 1 []
1793 , Right
$ exAv
"E" 2 []
1796 goals
:: [ExampleVar
]
1798 [ P
(QualIndep
"A") "A"
1799 , P
(QualIndep
"A") "E"
1800 , P
(QualIndep
"B") "B"
1801 , P
(QualIndep
"B") "D"
1802 , P
(QualIndep
"B") "E"
1803 , P
(QualIndep
"C") "C"
1804 , P
(QualIndep
"C") "D"
1805 , P
(QualIndep
"C") "E"
1806 , S
(QualIndep
"C") "C" TestStanzas
1809 -- | Test the trace messages that we get when a package refers to an unknown pkg
1811 -- TODO: Currently we don't actually test the trace messages, and this particular
1812 -- test still succeeds. The trace can only be verified by hand.
1815 [ Right
$ exAv
"A" 1 [ExAny
"B"]
1816 , Right
$ exAv
"A" 2 [ExAny
"C"] -- A-2.0 will be tried first, but C unknown
1817 , Right
$ exAv
"B" 1 []
1820 -- | A variant of 'db21', which actually fails.
1823 [ Right
$ exAv
"A" 1 [ExAny
"B"]
1824 , Right
$ exAv
"A" 2 [ExAny
"C"]
1827 -- | Another test for the unknown package message. This database tests that
1828 -- filtering out redundant conflict set messages in the solver log doesn't
1829 -- interfere with generating a message about a missing package (part of issue
1830 -- #3617). The conflict set for the missing package is {A, B}. That conflict set
1831 -- is propagated up the tree to the level of A. Since the conflict set is the
1832 -- same at both levels, the solver only keeps one of the backjumping messages.
1835 [ Right
$ exAv
"A" 1 [ExAny
"B"]
1838 -- | Database for (unsuccessfully) trying to expose a bug in the handling
1839 -- of implied linking constraints. The question is whether an implied linking
1840 -- constraint should only have the introducing package in its conflict set,
1841 -- or also its link target.
1843 -- It turns out that as long as the Single Instance Restriction is in place,
1844 -- it does not matter, because there will always be an option that is failing
1845 -- due to the SIR, which contains the link target in its conflict set.
1847 -- Even if the SIR is not in place, if there is a solution, one will always
1848 -- be found, because without the SIR, linking is always optional, but never
1850 testIndepGoals5
:: String -> GoalOrder
-> SolverTest
1851 testIndepGoals5 name fixGoalOrder
=
1852 case fixGoalOrder
of
1853 FixedGoalOrder
-> goalOrder goals test
1854 DefaultGoalOrder
-> test
1859 mkTest db name
["X", "Y"] $
1861 [("A", 1), ("A", 2), ("B", 1), ("C", 1), ("C", 2), ("X", 1), ("Y", 1)]
1865 [ Right
$ exAv
"X" 1 [ExFix
"C" 2, ExAny
"A"]
1866 , Right
$ exAv
"Y" 1 [ExFix
"C" 1, ExFix
"A" 2]
1867 , Right
$ exAv
"A" 1 []
1868 , Right
$ exAv
"A" 2 [ExAny
"B"]
1869 , Right
$ exAv
"B" 1 [ExAny
"C"]
1870 , Right
$ exAv
"C" 1 []
1871 , Right
$ exAv
"C" 2 []
1874 goals
:: [ExampleVar
]
1876 [ P
(QualIndep
"X") "X"
1877 , P
(QualIndep
"X") "A"
1878 , P
(QualIndep
"X") "B"
1879 , P
(QualIndep
"X") "C"
1880 , P
(QualIndep
"Y") "Y"
1881 , P
(QualIndep
"Y") "A"
1882 , P
(QualIndep
"Y") "B"
1883 , P
(QualIndep
"Y") "C"
1886 -- | A simplified version of 'testIndepGoals5'.
1887 testIndepGoals6
:: String -> GoalOrder
-> SolverTest
1888 testIndepGoals6 name fixGoalOrder
=
1889 case fixGoalOrder
of
1890 FixedGoalOrder
-> goalOrder goals test
1891 DefaultGoalOrder
-> test
1896 mkTest db name
["X", "Y"] $
1898 [("A", 1), ("A", 2), ("B", 1), ("B", 2), ("X", 1), ("Y", 1)]
1902 [ Right
$ exAv
"X" 1 [ExFix
"B" 2, ExAny
"A"]
1903 , Right
$ exAv
"Y" 1 [ExFix
"B" 1, ExFix
"A" 2]
1904 , Right
$ exAv
"A" 1 []
1905 , Right
$ exAv
"A" 2 [ExAny
"B"]
1906 , Right
$ exAv
"B" 1 []
1907 , Right
$ exAv
"B" 2 []
1910 goals
:: [ExampleVar
]
1912 [ P
(QualIndep
"X") "X"
1913 , P
(QualIndep
"X") "A"
1914 , P
(QualIndep
"X") "B"
1915 , P
(QualIndep
"Y") "Y"
1916 , P
(QualIndep
"Y") "A"
1917 , P
(QualIndep
"Y") "B"
1920 dbExts1
:: ExampleDb
1922 [ Right
$ exAv
"A" 1 [ExExt
(EnableExtension RankNTypes
)]
1923 , Right
$ exAv
"B" 1 [ExExt
(EnableExtension CPP
), ExAny
"A"]
1924 , Right
$ exAv
"C" 1 [ExAny
"B"]
1925 , Right
$ exAv
"D" 1 [ExExt
(DisableExtension CPP
), ExAny
"B"]
1926 , Right
$ exAv
"E" 1 [ExExt
(UnknownExtension
"custom"), ExAny
"C"]
1929 dbLangs1
:: ExampleDb
1931 [ Right
$ exAv
"A" 1 [ExLang Haskell2010
]
1932 , Right
$ exAv
"B" 1 [ExLang Haskell98
, ExAny
"A"]
1933 , Right
$ exAv
"C" 1 [ExLang
(UnknownLanguage
"Haskell3000"), ExAny
"B"]
1936 -- | cabal must set enable-exe to false in order to avoid the unavailable
1937 -- dependency. Flags are true by default. The flag choice causes "pkg" to
1938 -- depend on "false-dep".
1939 testBuildable
:: String -> ExampleDependency
-> TestTree
1940 testBuildable testName unavailableDep
=
1942 mkTestExtLangPC
(Just
[]) (Just
[Haskell98
]) (Just
[]) db testName
["pkg"] expected
1944 expected
= solverSuccess
[("false-dep", 1), ("pkg", 1)]
1958 , ExFlagged
"enable-exe" (dependencies
[]) unbuildableDependencies
1960 , Right
$ exAv
"true-dep" 1 []
1961 , Right
$ exAv
"false-dep" 1 []
1964 -- | cabal must choose -flag1 +flag2 for "pkg", which requires packages
1965 -- "flag1-false" and "flag2-true".
1966 dbBuildable1
:: ExampleDb
1972 [ exFlagged
"flag1" [ExAny
"flag1-true"] [ExAny
"flag1-false"]
1973 , exFlagged
"flag2" [ExAny
"flag2-true"] [ExAny
"flag2-false"]
1978 , ExFlagged
"flag1" (dependencies
[]) unbuildableDependencies
1979 , ExFlagged
"flag2" (dependencies
[]) unbuildableDependencies
1987 (dependencies
[ExFlagged
"flag2" unbuildableDependencies
(dependencies
[])])
1990 , Right
$ exAv
"flag1-true" 1 []
1991 , Right
$ exAv
"flag1-false" 1 []
1992 , Right
$ exAv
"flag2-true" 1 []
1993 , Right
$ exAv
"flag2-false" 1 []
1996 -- | cabal must pick B-2 to avoid the unknown dependency.
1997 dbBuildable2
:: ExampleDb
1999 [ Right
$ exAv
"A" 1 [ExAny
"B"]
2000 , Right
$ exAv
"B" 1 [ExAny
"unknown"]
2006 , ExFlagged
"disable-exe" unbuildableDependencies
(dependencies
[])
2008 , Right
$ exAv
"B" 3 [ExAny
"unknown"]
2011 -- | Package databases for testing @pkg-config@ dependencies.
2012 -- when no pkgconfig db is present, cabal must pick flag1 false and flag2 true to avoid the pkg dependency.
2015 [ Right
$ exAv
"A" 1 [ExPkg
("pkgA", 1)]
2016 , Right
$ exAv
"B" 1 [ExPkg
("pkgB", 1), ExAny
"A"]
2017 , Right
$ exAv
"B" 2 [ExPkg
("pkgB", 2), ExAny
"A"]
2018 , Right
$ exAv
"C" 1 [ExAny
"B"]
2019 , Right
$ exAv
"D" 1 [exFlagged
"flag1" [ExAny
"A"] [], exFlagged
"flag2" [] [ExAny
"A"]]
2022 -- | Test for the solver's summarized log. The final conflict set is {A, F},
2023 -- though the goal order forces the solver to find the (avoidable) conflict
2024 -- between B and C first. When the solver reaches the backjump limit, it should
2025 -- only show the log to the first conflict. When the backjump limit is high
2026 -- enough to allow an exhaustive search, the solver should make use of the final
2027 -- conflict set to only show the conflict between A and F in the summarized log.
2028 testSummarizedLog
:: String -> Maybe Int -> String -> TestTree
2029 testSummarizedLog testName mbj expectedMsg
=
2033 mkTest db testName
["A"] $
2034 solverFailure
(== expectedMsg
)
2037 [ Right
$ exAv
"A" 1 [ExAny
"B", ExAny
"F"]
2038 , Right
$ exAv
"B" 3 [ExAny
"C"]
2039 , Right
$ exAv
"B" 2 [ExAny
"D"]
2040 , Right
$ exAv
"B" 1 [ExAny
"E"]
2041 , Right
$ exAv
"E" 1 []
2044 goals
:: [ExampleVar
]
2045 goals
= [P QualNone pkg | pkg
<- ["A", "B", "C", "D", "E", "F"]]
2047 dbMinimizeConflictSet
:: ExampleDb
2048 dbMinimizeConflictSet
=
2049 [ Right
$ exAv
"A" 3 [ExFix
"B" 2, ExFix
"C" 1, ExFix
"D" 2]
2050 , Right
$ exAv
"A" 2 [ExFix
"B" 1, ExFix
"C" 2, ExFix
"D" 2]
2051 , Right
$ exAv
"A" 1 [ExFix
"B" 1, ExFix
"C" 1, ExFix
"D" 2]
2052 , Right
$ exAv
"B" 1 []
2053 , Right
$ exAv
"C" 1 []
2054 , Right
$ exAv
"D" 1 []
2057 -- | Test that the solver can find a minimal conflict set with
2058 -- --minimize-conflict-set. In the first run, the goal order causes the solver
2059 -- to find that A-3 conflicts with B, A-2 conflicts with C, and A-1 conflicts
2060 -- with D. The full log should show that the original final conflict set is
2061 -- {A, B, C, D}. Then the solver should be able to reduce the conflict set to
2062 -- {A, D}, since all versions of A conflict with D. The summarized log should
2063 -- only mention A and D.
2064 testMinimizeConflictSet
:: String -> TestTree
2065 testMinimizeConflictSet testName
=
2067 minimizeConflictSet
$
2070 mkTest dbMinimizeConflictSet testName
["A"] $
2071 SolverResult checkFullLog
(Left
(== expectedMsg
))
2073 checkFullLog
:: [String] -> Bool
2076 [ "[__0] fail (backjumping, conflict set: A, B, C, D)"
2077 , "Found no solution after exhaustively searching the dependency tree. "
2078 ++ "Rerunning the dependency solver to minimize the conflict set ({A, B, C, D})."
2079 , "Trying to remove variable \"A\" from the conflict set."
2080 , "Failed to remove \"A\" from the conflict set. Continuing with {A, B, C, D}."
2081 , "Trying to remove variable \"B\" from the conflict set."
2082 , "Successfully removed \"B\" from the conflict set. Continuing with {A, D}."
2083 , "Trying to remove variable \"D\" from the conflict set."
2084 , "Failed to remove \"D\" from the conflict set. Continuing with {A, D}."
2088 "Could not resolve dependencies:\n"
2089 ++ "[__0] trying: A-3.0.0 (user goal)\n"
2090 ++ "[__1] next goal: D (dependency of A)\n"
2091 ++ "[__1] rejecting: D-1.0.0 (conflict: A => D==2.0.0)\n"
2092 ++ "[__1] fail (backjumping, conflict set: A, D)\n"
2093 ++ "After searching the rest of the dependency tree exhaustively, these "
2094 ++ "were the goals I've had most trouble fulfilling: A (5), D (4)"
2096 goals
:: [ExampleVar
]
2097 goals
= [P QualNone pkg | pkg
<- ["A", "B", "C", "D"]]
2099 -- | This test uses the same packages and goal order as testMinimizeConflictSet,
2100 -- but it doesn't set --minimize-conflict-set. The solver should print the
2101 -- original final conflict set and the conflict between A and B. It should also
2102 -- suggest rerunning with --minimize-conflict-set.
2103 testNoMinimizeConflictSet
:: String -> TestTree
2104 testNoMinimizeConflictSet testName
=
2108 mkTest dbMinimizeConflictSet testName
["A"] $
2109 solverFailure
(== expectedMsg
)
2112 "Could not resolve dependencies:\n"
2113 ++ "[__0] trying: A-3.0.0 (user goal)\n"
2114 ++ "[__1] next goal: B (dependency of A)\n"
2115 ++ "[__1] rejecting: B-1.0.0 (conflict: A => B==2.0.0)\n"
2116 ++ "[__1] fail (backjumping, conflict set: A, B)\n"
2117 ++ "After searching the rest of the dependency tree exhaustively, "
2118 ++ "these were the goals I've had most trouble fulfilling: "
2119 ++ "A (7), B (2), C (2), D (2)\n"
2120 ++ "Try running with --minimize-conflict-set to improve the error message."
2122 goals
:: [ExampleVar
]
2123 goals
= [P QualNone pkg | pkg
<- ["A", "B", "C", "D"]]
2125 {-------------------------------------------------------------------------------
2126 Simple databases for the illustrations for the backjumping blog post
2127 -------------------------------------------------------------------------------}
2129 -- | Motivate conflict sets
2132 [ Right
$ exAv
"A" 1 [ExFix
"B" 1]
2133 , Right
$ exAv
"A" 2 [ExFix
"B" 2]
2134 , Right
$ exAv
"B" 1 []
2137 -- | Show that we can skip some decisions
2140 [ Right
$ exAv
"A" 1 [ExFix
"B" 1]
2141 , Right
$ exAv
"A" 2 [ExFix
"B" 2, ExAny
"C"]
2142 , Right
$ exAv
"B" 1 []
2143 , Right
$ exAv
"C" 1 []
2144 , Right
$ exAv
"C" 2 []
2147 -- | Motivate why both A and B need to be in the conflict set
2150 [ Right
$ exAv
"A" 1 [ExFix
"B" 1]
2151 , Right
$ exAv
"B" 1 []
2152 , Right
$ exAv
"B" 2 []
2155 -- | Motivate the need for accumulating conflict sets while we walk the tree
2158 [ Right
$ exAv
"A" 1 [ExFix
"B" 1]
2159 , Right
$ exAv
"A" 2 [ExFix
"B" 2]
2160 , Right
$ exAv
"B" 1 [ExFix
"C" 1]
2161 , Right
$ exAv
"B" 2 [ExFix
"C" 2]
2162 , Right
$ exAv
"C" 1 []
2165 -- | Motivate the need for `QGoalReason`
2168 [ Right
$ exAv
"A" 1 [ExAny
"Ba"]
2169 , Right
$ exAv
"A" 2 [ExAny
"Bb"]
2170 , Right
$ exAv
"Ba" 1 [ExFix
"C" 1]
2171 , Right
$ exAv
"Bb" 1 [ExFix
"C" 2]
2172 , Right
$ exAv
"C" 1 []
2175 -- | `QGOalReason` not unique
2178 [ Right
$ exAv
"A" 1 [ExAny
"B", ExAny
"C"]
2179 , Right
$ exAv
"B" 1 [ExAny
"C"]
2180 , Right
$ exAv
"C" 1 []
2183 -- | Flags are represented somewhat strangely in the tree
2185 -- This example probably won't be in the blog post itself but as a separate
2186 -- bug report (#3409)
2189 [ Right
$ exAv
"A" 1 [exFlagged
"flagA" [ExFix
"B" 1] [ExFix
"C" 1]]
2190 , Right
$ exAv
"B" 1 [ExFix
"D" 1]
2191 , Right
$ exAv
"C" 1 [ExFix
"D" 2]
2192 , Right
$ exAv
"D" 1 []
2195 -- | Conflict sets for cycles
2198 [ Right
$ exAv
"A" 1 [ExAny
"B"]
2199 , Right
$ exAv
"B" 1 []
2200 , Right
$ exAv
"B" 2 [ExAny
"C"]
2201 , Right
$ exAv
"C" 1 [ExAny
"A"]
2204 -- | Conflicts not unique
2207 [ Right
$ exAv
"A" 1 [ExAny
"B", ExFix
"C" 1]
2208 , Right
$ exAv
"B" 1 [ExFix
"C" 1]
2209 , Right
$ exAv
"C" 1 []
2210 , Right
$ exAv
"C" 2 []
2213 -- | Conflict sets for SIR (C shared subgoal of independent goals A, B)
2216 [ Right
$ exAv
"A" 1 [ExAny
"C"]
2217 , Right
$ exAv
"B" 1 [ExAny
"C"]
2218 , Right
$ exAv
"C" 1 []
2221 {-------------------------------------------------------------------------------
2222 Databases for build-tool-depends
2223 -------------------------------------------------------------------------------}
2225 -- | Multiple packages depending on exes from 'bt-pkg'.
2226 dbBuildTools
:: ExampleDb
2228 [ Right
$ exAv
"A" 1 [ExBuildToolAny
"bt-pkg" "exe1"]
2236 [ExBuildToolAny
"bt-pkg" "exe1"]
2238 , Right
$ exAv
"C" 1 [] `withTest` exTest
"testC" [ExBuildToolAny
"bt-pkg" "exe1"]
2239 , Right
$ exAv
"D" 1 [ExBuildToolAny
"bt-pkg" "unknown-exe"]
2240 , Right
$ exAv
"E" 1 [ExBuildToolAny
"unknown-pkg" "exe1"]
2247 [ExBuildToolAny
"bt-pkg" "unknown-exe"]
2250 , Right
$ exAv
"G" 1 [] `withTest` exTest
"testG" [ExBuildToolAny
"bt-pkg" "unknown-exe"]
2251 , Right
$ exAv
"H" 1 [ExBuildToolFix
"bt-pkg" "exe1" 3]
2252 , Right
$ exAv
"bt-pkg" 4 []
2253 , Right
$ exAv
"bt-pkg" 3 [] `withExe` exExe
"exe2" []
2254 , Right
$ exAv
"bt-pkg" 2 [] `withExe` exExe
"exe1" []
2255 , Right
$ exAv
"bt-pkg" 1 []
2258 -- The solver should never choose an installed package for a build tool
2260 rejectInstalledBuildToolPackage
:: String -> SolverTest
2261 rejectInstalledBuildToolPackage name
=
2262 mkTest db name
["A"] $
2265 "rejecting: A:B:exe.B-1.0.0/installed-1 "
2266 ++ "(does not contain executable 'exe', which is required by A)"
2270 [ Right
$ exAv
"A" 1 [ExBuildToolAny
"B" "exe"]
2271 , Left
$ exInst
"B" 1 "B-1" []
2274 -- | This test forces the solver to choose B as a build-tool dependency before
2275 -- it sees the dependency on executable exe2 from B. The solver needs to check
2276 -- that the version that it already chose for B contains the necessary
2277 -- executable. This order causes a different "missing executable" error message
2278 -- than when the solver checks for the executable in the same step that it
2279 -- chooses the build-tool package.
2281 -- This case may become impossible if we ever add the executable name to the
2282 -- build-tool goal qualifier. Then this test would involve two qualified goals
2283 -- for B, one for exe1 and another for exe2.
2284 chooseExeAfterBuildToolsPackage
:: Bool -> String -> SolverTest
2285 chooseExeAfterBuildToolsPackage shouldSucceed name
=
2287 mkTest db name
["A"] $
2289 then solverSuccess
[("A", 1), ("B", 1)]
2293 "rejecting: A:+flagA (requires executable 'exe2' from A:B:exe.B, "
2294 ++ "but the component does not exist)"
2302 [ ExBuildToolAny
"B" "exe1"
2305 [ExBuildToolAny
"B" "exe2"]
2310 `withExes`
[exExe exe
[] | exe
<- if shouldSucceed
then ["exe1", "exe2"] else ["exe1"]]
2313 goals
:: [ExampleVar
]
2316 , P
(QualExe
"A" "B") "B"
2317 , F QualNone
"A" "flagA"
2320 -- | Test that when one package depends on two executables from another package,
2321 -- both executables must come from the same instance of that package. We could
2322 -- lift this restriction in the future by adding the executable name to the goal
2324 requireConsistentBuildToolVersions
:: String -> SolverTest
2325 requireConsistentBuildToolVersions name
=
2326 mkTest db name
["A"] $
2329 "[__1] rejecting: A:B:exe.B-2.0.0 (conflict: A => A:B:exe.B (exe exe1)==1.0.0)\n"
2330 ++ "[__1] rejecting: A:B:exe.B-1.0.0 (conflict: A => A:B:exe.B (exe exe2)==2.0.0)"
2338 [ ExBuildToolFix
"B" "exe1" 1
2339 , ExBuildToolFix
"B" "exe2" 2
2341 , Right
$ exAv
"B" 2 [] `withExes` exes
2342 , Right
$ exAv
"B" 1 [] `withExes` exes
2345 exes
= [exExe
"exe1" [], exExe
"exe2" []]
2347 -- | This test is similar to the failure case for
2348 -- chooseExeAfterBuildToolsPackage, except that the build tool is unbuildable
2349 -- instead of missing.
2350 chooseUnbuildableExeAfterBuildToolsPackage
:: String -> SolverTest
2351 chooseUnbuildableExeAfterBuildToolsPackage name
=
2352 constraints
[ExFlagConstraint
(ScopeAnyQualifier
"B") "build-bt2" False] $
2354 mkTest db name
["A"] $
2357 "rejecting: A:+use-bt2 (requires executable 'bt2' from A:B:exe.B, but "
2358 ++ "the component is not buildable in the current environment)"
2366 [ ExBuildToolAny
"B" "bt1"
2369 [ExBuildToolAny
"B" "bt2"]
2374 `withExes`
[ exExe
"bt1" []
2375 , exExe
"bt2" [ExFlagged
"build-bt2" (dependencies
[]) unbuildableDependencies
]
2379 goals
:: [ExampleVar
]
2382 , P
(QualExe
"A" "B") "B"
2383 , F QualNone
"A" "use-bt2"
2386 {-------------------------------------------------------------------------------
2387 Databases for legacy build-tools
2388 -------------------------------------------------------------------------------}
2389 dbLegacyBuildTools1
:: ExampleDb
2390 dbLegacyBuildTools1
=
2391 [ Right
$ exAv
"alex" 1 [] `withExe` exExe
"alex" []
2392 , Right
$ exAv
"A" 1 [ExLegacyBuildToolAny
"alex"]
2395 -- Test that a recognized build tool dependency specifies the name of both the
2396 -- package and the executable. This db has no solution.
2397 dbLegacyBuildTools2
:: ExampleDb
2398 dbLegacyBuildTools2
=
2399 [ Right
$ exAv
"alex" 1 [] `withExe` exExe
"other-exe" []
2400 , Right
$ exAv
"other-package" 1 [] `withExe` exExe
"alex" []
2401 , Right
$ exAv
"A" 1 [ExLegacyBuildToolAny
"alex"]
2404 -- Test that build-tools on a random thing doesn't matter (only
2405 -- the ones we recognize need to be in db)
2406 dbLegacyBuildTools3
:: ExampleDb
2407 dbLegacyBuildTools3
=
2408 [ Right
$ exAv
"A" 1 [ExLegacyBuildToolAny
"otherdude"]
2411 -- Test that we can solve for different versions of executables
2412 dbLegacyBuildTools4
:: ExampleDb
2413 dbLegacyBuildTools4
=
2414 [ Right
$ exAv
"alex" 1 [] `withExe` exExe
"alex" []
2415 , Right
$ exAv
"alex" 2 [] `withExe` exExe
"alex" []
2416 , Right
$ exAv
"A" 1 [ExLegacyBuildToolFix
"alex" 1]
2417 , Right
$ exAv
"B" 1 [ExLegacyBuildToolFix
"alex" 2]
2418 , Right
$ exAv
"C" 1 [ExAny
"A", ExAny
"B"]
2421 -- Test that exe is not related to library choices
2422 dbLegacyBuildTools5
:: ExampleDb
2423 dbLegacyBuildTools5
=
2424 [ Right
$ exAv
"alex" 1 [ExFix
"A" 1] `withExe` exExe
"alex" []
2425 , Right
$ exAv
"A" 1 []
2426 , Right
$ exAv
"A" 2 []
2427 , Right
$ exAv
"B" 1 [ExLegacyBuildToolFix
"alex" 1, ExFix
"A" 2]
2430 -- Test that build-tools on build-tools works
2431 dbLegacyBuildTools6
:: ExampleDb
2432 dbLegacyBuildTools6
=
2433 [ Right
$ exAv
"alex" 1 [] `withExe` exExe
"alex" []
2434 , Right
$ exAv
"happy" 1 [ExLegacyBuildToolAny
"alex"] `withExe` exExe
"happy" []
2435 , Right
$ exAv
"A" 1 [ExLegacyBuildToolAny
"happy"]
2438 -- Test that build-depends on library/executable package works.
2439 -- Extracted from https://github.com/haskell/cabal/issues/3775
2440 dbIssue3775
:: ExampleDb
2442 [ Right
$ exAv
"warp" 1 []
2443 , -- NB: the warp build-depends refers to the package, not the internal
2445 Right
$ exAv
"A" 2 [ExFix
"warp" 1] `withExe` exExe
"warp" [ExAny
"A"]
2446 , Right
$ exAv
"B" 2 [ExAny
"A", ExAny
"warp"]
2449 -- | Returns true if the second list contains all elements of the first list, in
2451 containsInOrder
:: Eq a
=> [a
] -> [a
] -> Bool
2452 containsInOrder
[] _
= True
2453 containsInOrder _
[] = False
2454 containsInOrder
(x
: xs
) (y
: ys
)
2455 | x
== y
= containsInOrder xs ys
2456 |
otherwise = containsInOrder
(x
: xs
) ys