-
Notifications
You must be signed in to change notification settings - Fork 704
/
Copy pathTestCaseUtils.hs
283 lines (247 loc) · 10.8 KB
/
TestCaseUtils.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
{-# LANGUAGE RecordWildCards #-}
-- | Utilities for creating HUnit test cases with the solver DSL.
module UnitTests.Distribution.Solver.Modular.DSL.TestCaseUtils (
SolverTest
, SolverResult(..)
, maxBackjumps
, disableFineGrainedConflicts
, minimizeConflictSet
, independentGoals
, allowBootLibInstalls
, onlyConstrained
, disableBackjumping
, disableSolveExecutables
, goalOrder
, constraints
, preferences
, setVerbose
, enableAllTests
, solverSuccess
, solverFailure
, anySolverFailure
, mkTest
, mkTestExts
, mkTestLangs
, mkTestPCDepends
, mkTestExtLangPC
, runTest
) where
import Prelude ()
import Distribution.Solver.Compat.Prelude
import Data.List (elemIndex)
-- test-framework
import Test.Tasty as TF
import Test.Tasty.HUnit (testCase, assertEqual, assertBool)
-- Cabal
import qualified Distribution.PackageDescription as C
import Language.Haskell.Extension (Extension(..), Language(..))
import Distribution.Verbosity
-- cabal-install
import qualified Distribution.Solver.Types.PackagePath as P
import Distribution.Solver.Types.PkgConfigDb (PkgConfigDb, pkgConfigDbFromList)
import Distribution.Solver.Types.Settings
import Distribution.Solver.Types.Variable
import Distribution.Client.Dependency (foldProgress)
import UnitTests.Distribution.Solver.Modular.DSL
import UnitTests.Options
maxBackjumps :: Maybe Int -> SolverTest -> SolverTest
maxBackjumps mbj test = test { testMaxBackjumps = mbj }
disableFineGrainedConflicts :: SolverTest -> SolverTest
disableFineGrainedConflicts test =
test { testFineGrainedConflicts = FineGrainedConflicts False }
minimizeConflictSet :: SolverTest -> SolverTest
minimizeConflictSet test =
test { testMinimizeConflictSet = MinimizeConflictSet True }
-- | Combinator to turn on --independent-goals behavior, i.e. solve
-- for the goals as if we were solving for each goal independently.
independentGoals :: SolverTest -> SolverTest
independentGoals test = test { testIndepGoals = IndependentGoals True }
allowBootLibInstalls :: SolverTest -> SolverTest
allowBootLibInstalls test =
test { testAllowBootLibInstalls = AllowBootLibInstalls True }
onlyConstrained :: SolverTest -> SolverTest
onlyConstrained test =
test { testOnlyConstrained = OnlyConstrainedAll }
disableBackjumping :: SolverTest -> SolverTest
disableBackjumping test =
test { testEnableBackjumping = EnableBackjumping False }
disableSolveExecutables :: SolverTest -> SolverTest
disableSolveExecutables test =
test { testSolveExecutables = SolveExecutables False }
goalOrder :: [ExampleVar] -> SolverTest -> SolverTest
goalOrder order test = test { testGoalOrder = Just order }
constraints :: [ExConstraint] -> SolverTest -> SolverTest
constraints cs test = test { testConstraints = cs }
preferences :: [ExPreference] -> SolverTest -> SolverTest
preferences prefs test = test { testSoftConstraints = prefs }
-- | Increase the solver's verbosity. This is necessary for test cases that
-- check the contents of the verbose log.
setVerbose :: SolverTest -> SolverTest
setVerbose test = test { testVerbosity = verbose }
enableAllTests :: SolverTest -> SolverTest
enableAllTests test = test { testEnableAllTests = EnableAllTests True }
{-------------------------------------------------------------------------------
Solver tests
-------------------------------------------------------------------------------}
data SolverTest = SolverTest {
testLabel :: String
, testTargets :: [String]
, testResult :: SolverResult
, testMaxBackjumps :: Maybe Int
, testFineGrainedConflicts :: FineGrainedConflicts
, testMinimizeConflictSet :: MinimizeConflictSet
, testIndepGoals :: IndependentGoals
, testAllowBootLibInstalls :: AllowBootLibInstalls
, testOnlyConstrained :: OnlyConstrained
, testEnableBackjumping :: EnableBackjumping
, testSolveExecutables :: SolveExecutables
, testGoalOrder :: Maybe [ExampleVar]
, testConstraints :: [ExConstraint]
, testSoftConstraints :: [ExPreference]
, testVerbosity :: Verbosity
, testDb :: ExampleDb
, testSupportedExts :: Maybe [Extension]
, testSupportedLangs :: Maybe [Language]
, testPkgConfigDb :: PkgConfigDb
, testEnableAllTests :: EnableAllTests
}
-- | Expected result of a solver test.
data SolverResult = SolverResult {
-- | The solver's log should satisfy this predicate. Note that we also print
-- the log, so evaluating a large log here can cause a space leak.
resultLogPredicate :: [String] -> Bool,
-- | Fails with an error message satisfying the predicate, or succeeds with
-- the given plan.
resultErrorMsgPredicateOrPlan :: Either (String -> Bool) [(String, Int)]
}
solverSuccess :: [(String, Int)] -> SolverResult
solverSuccess = SolverResult (const True) . Right
solverFailure :: (String -> Bool) -> SolverResult
solverFailure = SolverResult (const True) . Left
-- | Can be used for test cases where we just want to verify that
-- they fail, but do not care about the error message.
anySolverFailure :: SolverResult
anySolverFailure = solverFailure (const True)
-- | Makes a solver test case, consisting of the following components:
--
-- 1. An 'ExampleDb', representing the package database (both
-- installed and remote) we are doing dependency solving over,
-- 2. A 'String' name for the test,
-- 3. A list '[String]' of package names to solve for
-- 4. The expected result, either 'Nothing' if there is no
-- satisfying solution, or a list '[(String, Int)]' of
-- packages to install, at which versions.
--
-- See 'UnitTests.Distribution.Solver.Modular.DSL' for how
-- to construct an 'ExampleDb', as well as definitions of 'db1' etc.
-- in this file.
mkTest :: ExampleDb
-> String
-> [String]
-> SolverResult
-> SolverTest
mkTest = mkTestExtLangPC Nothing Nothing []
mkTestExts :: [Extension]
-> ExampleDb
-> String
-> [String]
-> SolverResult
-> SolverTest
mkTestExts exts = mkTestExtLangPC (Just exts) Nothing []
mkTestLangs :: [Language]
-> ExampleDb
-> String
-> [String]
-> SolverResult
-> SolverTest
mkTestLangs langs = mkTestExtLangPC Nothing (Just langs) []
mkTestPCDepends :: [(String, String)]
-> ExampleDb
-> String
-> [String]
-> SolverResult
-> SolverTest
mkTestPCDepends pkgConfigDb = mkTestExtLangPC Nothing Nothing pkgConfigDb
mkTestExtLangPC :: Maybe [Extension]
-> Maybe [Language]
-> [(String, String)]
-> ExampleDb
-> String
-> [String]
-> SolverResult
-> SolverTest
mkTestExtLangPC exts langs pkgConfigDb db label targets result = SolverTest {
testLabel = label
, testTargets = targets
, testResult = result
, testMaxBackjumps = Nothing
, testFineGrainedConflicts = FineGrainedConflicts True
, testMinimizeConflictSet = MinimizeConflictSet False
, testIndepGoals = IndependentGoals False
, testAllowBootLibInstalls = AllowBootLibInstalls False
, testOnlyConstrained = OnlyConstrainedNone
, testEnableBackjumping = EnableBackjumping True
, testSolveExecutables = SolveExecutables True
, testGoalOrder = Nothing
, testConstraints = []
, testSoftConstraints = []
, testVerbosity = normal
, testDb = db
, testSupportedExts = exts
, testSupportedLangs = langs
, testPkgConfigDb = pkgConfigDbFromList pkgConfigDb
, testEnableAllTests = EnableAllTests False
}
runTest :: SolverTest -> TF.TestTree
runTest SolverTest{..} = askOption $ \(OptionShowSolverLog showSolverLog) ->
testCase testLabel $ do
let progress = exResolve testDb testSupportedExts
testSupportedLangs testPkgConfigDb testTargets
testMaxBackjumps (CountConflicts True)
testFineGrainedConflicts testMinimizeConflictSet
testIndepGoals (ReorderGoals False) testAllowBootLibInstalls
testOnlyConstrained testEnableBackjumping testSolveExecutables
(sortGoals <$> testGoalOrder) testConstraints
testSoftConstraints testVerbosity testEnableAllTests
printMsg msg = when showSolverLog $ putStrLn msg
msgs = foldProgress (:) (const []) (const []) progress
assertBool ("Unexpected solver log:\n" ++ unlines msgs) $
resultLogPredicate testResult $ concatMap lines msgs
result <- foldProgress ((>>) . printMsg) (return . Left) (return . Right) progress
case result of
Left err -> assertBool ("Unexpected error:\n" ++ err)
(checkErrorMsg testResult err)
Right plan -> assertEqual "" (toMaybe testResult) (Just (extractInstallPlan plan))
where
toMaybe :: SolverResult -> Maybe [(String, Int)]
toMaybe = either (const Nothing) Just . resultErrorMsgPredicateOrPlan
checkErrorMsg :: SolverResult -> String -> Bool
checkErrorMsg result msg =
case resultErrorMsgPredicateOrPlan result of
Left f -> f msg
Right _ -> False
sortGoals :: [ExampleVar]
-> Variable P.QPN -> Variable P.QPN -> Ordering
sortGoals = orderFromList . map toVariable
-- Sort elements in the list ahead of elements not in the list. Otherwise,
-- follow the order in the list.
orderFromList :: Eq a => [a] -> a -> a -> Ordering
orderFromList xs =
comparing $ \x -> let i = elemIndex x xs in (isNothing i, i)
toVariable :: ExampleVar -> Variable P.QPN
toVariable (P q pn) = PackageVar (toQPN q pn)
toVariable (F q pn fn) = FlagVar (toQPN q pn) (C.mkFlagName fn)
toVariable (S q pn stanza) = StanzaVar (toQPN q pn) stanza
toQPN :: ExampleQualifier -> ExamplePkgName -> P.QPN
toQPN q pn = P.Q pp (C.mkPackageName pn)
where
pp = case q of
QualNone -> P.PackagePath P.DefaultNamespace P.QualToplevel
QualIndep p -> P.PackagePath (P.Independent $ C.mkPackageName p)
P.QualToplevel
QualSetup s -> P.PackagePath P.DefaultNamespace
(P.QualSetup (C.mkPackageName s))
QualIndepSetup p s -> P.PackagePath (P.Independent $ C.mkPackageName p)
(P.QualSetup (C.mkPackageName s))
QualExe p1 p2 -> P.PackagePath P.DefaultNamespace
(P.QualExe (C.mkPackageName p1) (C.mkPackageName p2))