Skip to content

Commit 66e657b

Browse files
committed
Add unit tests for qualified constraints.
1 parent 353dcfe commit 66e657b

File tree

2 files changed

+44
-1
lines changed

2 files changed

+44
-1
lines changed

cabal-install/tests/UnitTests/Distribution/Solver/Modular/DSL.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ module UnitTests.Distribution.Solver.Modular.DSL (
3030
, withExe
3131
, withExes
3232
, runProgress
33+
, mkVersionRange
3334
) where
3435

3536
import Prelude ()

cabal-install/tests/UnitTests/Distribution/Solver/Modular/Solver.hs

Lines changed: 43 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE OverloadedStrings #-}
12
-- | This is a set of unit tests for the dependency solver,
23
-- which uses the solver DSL ("UnitTests.Distribution.Solver.Modular.DSL")
34
-- to more conveniently create package databases to run the solver tests on.
@@ -18,6 +19,8 @@ import Language.Haskell.Extension ( Extension(..)
1819

1920
-- cabal-install
2021
import Distribution.Solver.Types.OptionalStanza
22+
import Distribution.Solver.Types.PackageConstraint
23+
import Distribution.Solver.Types.PackagePath
2124
import UnitTests.Distribution.Solver.Modular.DSL
2225
import UnitTests.Distribution.Solver.Modular.DSL.TestCaseUtils
2326

@@ -109,7 +112,30 @@ tests = [
109112
, runTest $ mkTestLangs [Haskell98] dbLangs1 "unsupportedIndirect" ["B"] anySolverFailure
110113
, runTest $ mkTestLangs [Haskell98, Haskell2010, UnknownLanguage "Haskell3000"] dbLangs1 "supportedUnknown" ["C"] (solverSuccess [("A",1),("B",1),("C",1)])
111114
]
112-
115+
, testGroup "Qualified Package Constraints" [
116+
runTest $ mkTest dbConstraints "install latest versions without constraints" ["A", "B", "C"] $
117+
solverSuccess [("A", 10), ("B", 11), ("C", 12), ("D", 10), ("D", 11), ("D", 12)]
118+
119+
, let cs = [ ExConstraint (ScopeAnyQualifier "D") $ mkvrOrEarlier 3 ]
120+
in runTest $ constraints cs $
121+
mkTest dbConstraints "force older versions with unqualified constraint" ["A", "B", "C"] $
122+
solverSuccess [("A", 1), ("B", 2), ("C", 3), ("D", 1), ("D", 2), ("D", 3)]
123+
124+
, let cs = [ ExConstraint (ScopeQualified QualToplevel "D") $ mkVersionRange 1 4
125+
, ExConstraint (ScopeQualified (QualSetup "B") "D") $ mkVersionRange 4 7
126+
, ExConstraint (ScopeQualified (QualSetup "C") "D") $ mkVersionRange 7 10
127+
]
128+
in runTest $ constraints cs $
129+
mkTest dbConstraints "force multiple versions with qualified constraints" ["A", "B", "C"] $
130+
solverSuccess [("A", 1), ("B", 5), ("C", 9), ("D", 1), ("D", 5), ("D", 9)]
131+
132+
, let cs = [ ExConstraint (ScopeQualified QualToplevel "D") $ mkVersionRange 1 4
133+
, ExConstraint (ScopeAnySetupQualifier "D") $ mkVersionRange 4 7
134+
]
135+
in runTest $ constraints cs $
136+
mkTest dbConstraints "force multiple versions with setup qualified constraint" ["A", "B", "C"] $
137+
solverSuccess [("A", 1), ("B", 5), ("C", 6), ("D", 1), ("D", 5), ("D", 6)]
138+
]
113139
, testGroup "Package Preferences" [
114140
runTest $ preferences [ ExPkgPref "A" $ mkvrThis 1] $ mkTest db13 "selectPreferredVersionSimple" ["A"] (solverSuccess [("A", 1)])
115141
, runTest $ preferences [ ExPkgPref "A" $ mkvrOrEarlier 2] $ mkTest db13 "selectPreferredVersionSimple2" ["A"] (solverSuccess [("A", 2)])
@@ -185,6 +211,8 @@ tests = [
185211
-- See issue #3203. The solver should only choose a version for A once.
186212
runTest $
187213
let db = [Right $ exAv "A" 1 []]
214+
215+
p :: [String] -> Bool
188216
p lg = elem "targets: A" lg
189217
&& length (filter ("trying: A" `isInfixOf`) lg) == 1
190218
in mkTest db "deduplicate targets" ["A", "A"] $
@@ -468,6 +496,20 @@ db13 = [
468496
, Right $ exAv "A" 3 []
469497
]
470498

499+
-- | A, B, and C have three different dependencies on D that can be set to
500+
-- different versions with qualified constraints. Each version of D can only
501+
-- be depended upon by one version of A, B, or C, so that the versions of A, B,
502+
-- and C in the install plan indicate which version of D was chosen for each
503+
-- dependency. The one-to-one correspondence between versions of A, B, and C and
504+
-- versions of D also prevents linking, which would complicate the solver's
505+
-- behavior.
506+
dbConstraints :: ExampleDb
507+
dbConstraints =
508+
[Right $ exAv "A" v [ExFix "D" v] | v <- [1, 4, 7, 10]]
509+
++ [Right $ exAv "B" v [] `withSetupDeps` [ExFix "D" v] | v <- [2, 5, 8, 11]]
510+
++ [Right $ exAv "C" v [] `withSetupDeps` [ExFix "D" v] | v <- [3, 6, 9, 12]]
511+
++ [Right $ exAv "D" v [] | v <- [1..12]]
512+
471513
dbStanzaPreferences1 :: ExampleDb
472514
dbStanzaPreferences1 = [
473515
Right $ exAv "pkg" 1 [] `withTest` ExTest "test" [ExAny "test-dep"]

0 commit comments

Comments
 (0)