`cabal check`: clearly mark Errors (#8908)
[cabal.git] / cabal-install / tests / IntegrationTests2.hs
blob1fe4104619a69d40814b55633932218b282a16be
1 {- FOURMOLU_DISABLE -}
2 {-# LANGUAGE CPP #-}
3 {-# LANGUAGE BangPatterns #-}
4 {-# LANGUAGE DeriveDataTypeable #-}
5 {-# LANGUAGE RankNTypes #-}
6 {-# LANGUAGE ScopedTypeVariables #-}
7 {-# LANGUAGE OverloadedStrings #-}
9 -- For the handy instance IsString PackageIdentifier
10 {-# OPTIONS_GHC -fno-warn-orphans #-}
12 module Main where
14 import Distribution.Client.Compat.Prelude
15 import Prelude ()
17 import Distribution.Client.DistDirLayout
18 import Distribution.Client.ProjectConfig
19 import Distribution.Client.HttpUtils
20 import Distribution.Client.TargetSelector hiding (DirActions(..))
21 import qualified Distribution.Client.TargetSelector as TS (DirActions(..))
22 import Distribution.Client.ProjectPlanning
23 import Distribution.Client.ProjectPlanning.Types
24 import Distribution.Client.ProjectBuilding
25 import Distribution.Client.ProjectOrchestration
26 ( resolveTargets, distinctTargetComponents )
27 import Distribution.Client.TargetProblem
28 ( TargetProblem', TargetProblem (..) )
29 import Distribution.Client.Types
30 ( PackageLocation(..), UnresolvedSourcePackage
31 , PackageSpecifier(..) )
32 import Distribution.Client.Targets
33 ( UserConstraint(..), UserConstraintScope(UserAnyQualifier) )
34 import qualified Distribution.Client.InstallPlan as InstallPlan
35 import Distribution.Solver.Types.SourcePackage as SP
36 import Distribution.Solver.Types.ConstraintSource
37 ( ConstraintSource(ConstraintSourceUnknown) )
38 import Distribution.Solver.Types.PackageConstraint
39 ( PackageProperty(PackagePropertySource) )
41 import qualified Distribution.Client.CmdBuild as CmdBuild
42 import qualified Distribution.Client.CmdRepl as CmdRepl
43 import qualified Distribution.Client.CmdRun as CmdRun
44 import qualified Distribution.Client.CmdTest as CmdTest
45 import qualified Distribution.Client.CmdBench as CmdBench
46 import qualified Distribution.Client.CmdHaddock as CmdHaddock
47 import qualified Distribution.Client.CmdListBin as CmdListBin
49 import Distribution.Package
50 import Distribution.PackageDescription
51 import Distribution.InstalledPackageInfo (InstalledPackageInfo)
52 import Distribution.Simple.Setup (toFlag, HaddockFlags(..), defaultHaddockFlags)
53 import Distribution.Client.Setup (globalCommand)
54 import Distribution.Client.Config (loadConfig, SavedConfig(savedGlobalFlags), createDefaultConfigFile)
55 import Distribution.Simple.Compiler
56 import Distribution.Simple.Command
57 import qualified Distribution.Simple.Flag as Flag
58 import Distribution.System
59 import Distribution.Version
60 import Distribution.ModuleName (ModuleName)
61 import Distribution.Text
62 import Distribution.Utils.Path
64 import qualified Data.Map as Map
65 import qualified Data.Set as Set
66 import Data.List (isInfixOf)
68 import Control.Monad
69 import Control.Concurrent (threadDelay)
70 import Control.Exception hiding (assert)
71 import System.FilePath
72 import System.Directory
73 import System.IO (hPutStrLn, stderr)
75 import Test.Tasty
76 import Test.Tasty.HUnit
77 import Test.Tasty.Options
78 import Data.Tagged (Tagged(..))
79 import qualified Data.List as L
81 import qualified Data.ByteString as BS
82 import Distribution.Client.GlobalFlags (GlobalFlags, globalNix)
83 import Distribution.Simple.Flag (Flag (Flag, NoFlag))
84 import Data.Maybe (fromJust)
86 #if !MIN_VERSION_directory(1,2,7)
87 removePathForcibly :: FilePath -> IO ()
88 removePathForcibly = removeDirectoryRecursive
89 #endif
91 main :: IO ()
92 main =
93 defaultMainWithIngredients
94 (defaultIngredients ++ [includingOptions projectConfigOptionDescriptions])
95 (withProjectConfig $ \config ->
96 testGroup "Integration tests (internal)"
97 (tests config))
100 tests :: ProjectConfig -> [TestTree]
101 tests config =
102 --TODO: tests for:
103 -- * normal success
104 -- * dry-run tests with changes
105 [ testGroup "Discovery and planning" $
106 [ testCase "no package" (testExceptionInFindingPackage config)
107 , testCase "no package2" (testExceptionInFindingPackage2 config)
108 , testCase "proj conf1" (testExceptionInProjectConfig config)
110 , testGroup "Target selectors" $
111 [ testCaseSteps "valid" testTargetSelectors
112 , testCase "bad syntax" testTargetSelectorBadSyntax
113 , testCaseSteps "ambiguous syntax" testTargetSelectorAmbiguous
114 , testCase "no current pkg" testTargetSelectorNoCurrentPackage
115 , testCase "no targets" testTargetSelectorNoTargets
116 , testCase "project empty" testTargetSelectorProjectEmpty
117 , testCase "canonicalized path" testTargetSelectorCanonicalizedPath
118 , testCase "problems (common)" (testTargetProblemsCommon config)
119 , testCaseSteps "problems (build)" (testTargetProblemsBuild config)
120 , testCaseSteps "problems (repl)" (testTargetProblemsRepl config)
121 , testCaseSteps "problems (run)" (testTargetProblemsRun config)
122 , testCaseSteps "problems (list-bin)" (testTargetProblemsListBin config)
123 , testCaseSteps "problems (test)" (testTargetProblemsTest config)
124 , testCaseSteps "problems (bench)" (testTargetProblemsBench config)
125 , testCaseSteps "problems (haddock)" (testTargetProblemsHaddock config)
127 , testGroup "Exceptions during building (local inplace)" $
128 [ testCase "configure" (testExceptionInConfigureStep config)
129 , testCase "build" (testExceptionInBuildStep config)
130 -- , testCase "register" testExceptionInRegisterStep
132 --TODO: need to repeat for packages for the store
133 --TODO: need to check we can build sub-libs, foreign libs and exes
134 -- components for non-local packages / packages in the store.
136 , testGroup "Successful builds" $
137 [ testCaseSteps "Setup script styles" (testSetupScriptStyles config)
138 , testCase "keep-going" (testBuildKeepGoing config)
139 #ifndef mingw32_HOST_OS
140 -- disabled because https://github.com/haskell/cabal/issues/6272
141 , testCase "local tarball" (testBuildLocalTarball config)
142 #endif
145 , testGroup "Regression tests" $
146 [ testCase "issue #3324" (testRegressionIssue3324 config)
147 , testCase "program options scope all" (testProgramOptionsAll config)
148 , testCase "program options scope local" (testProgramOptionsLocal config)
149 , testCase "program options scope specific" (testProgramOptionsSpecific config)
151 , testGroup "Flag tests" $
153 testCase "Test Nix Flag" testNixFlags,
154 testCase "Test Config options for commented options" testConfigOptionComments,
155 testCase "Test Ignore Project Flag" testIgnoreProjectFlag
159 testTargetSelectors :: (String -> IO ()) -> Assertion
160 testTargetSelectors reportSubCase = do
161 (_, _, _, localPackages, _) <- configureProject testdir config
162 let readTargetSelectors' = readTargetSelectorsWith (dirActions testdir)
163 localPackages
164 Nothing
166 reportSubCase "cwd"
167 do Right ts <- readTargetSelectors' []
168 ts @?= [TargetPackage TargetImplicitCwd ["p-0.1"] Nothing]
170 reportSubCase "all"
171 do Right ts <- readTargetSelectors'
172 ["all", ":all"]
173 ts @?= replicate 2 (TargetAllPackages Nothing)
175 reportSubCase "filter"
176 do Right ts <- readTargetSelectors'
177 [ "libs", ":cwd:libs"
178 , "flibs", ":cwd:flibs"
179 , "exes", ":cwd:exes"
180 , "tests", ":cwd:tests"
181 , "benchmarks", ":cwd:benchmarks"]
182 zipWithM_ (@?=) ts
183 [ TargetPackage TargetImplicitCwd ["p-0.1"] (Just kind)
184 | kind <- concatMap (replicate 2) [LibKind .. ]
187 reportSubCase "all:filter"
188 do Right ts <- readTargetSelectors'
189 [ "all:libs", ":all:libs"
190 , "all:flibs", ":all:flibs"
191 , "all:exes", ":all:exes"
192 , "all:tests", ":all:tests"
193 , "all:benchmarks", ":all:benchmarks"]
194 zipWithM_ (@?=) ts
195 [ TargetAllPackages (Just kind)
196 | kind <- concatMap (replicate 2) [LibKind .. ]
199 reportSubCase "pkg"
200 do Right ts <- readTargetSelectors'
201 [ ":pkg:p", ".", "./", "p.cabal"
202 , "q", ":pkg:q", "q/", "./q/", "q/q.cabal"]
203 ts @?= replicate 4 (mkTargetPackage "p-0.1")
204 ++ replicate 5 (mkTargetPackage "q-0.1")
206 reportSubCase "pkg:filter"
207 do Right ts <- readTargetSelectors'
208 [ "p:libs", ".:libs", ":pkg:p:libs"
209 , "p:flibs", ".:flibs", ":pkg:p:flibs"
210 , "p:exes", ".:exes", ":pkg:p:exes"
211 , "p:tests", ".:tests", ":pkg:p:tests"
212 , "p:benchmarks", ".:benchmarks", ":pkg:p:benchmarks"
213 , "q:libs", "q/:libs", ":pkg:q:libs"
214 , "q:flibs", "q/:flibs", ":pkg:q:flibs"
215 , "q:exes", "q/:exes", ":pkg:q:exes"
216 , "q:tests", "q/:tests", ":pkg:q:tests"
217 , "q:benchmarks", "q/:benchmarks", ":pkg:q:benchmarks"]
218 zipWithM_ (@?=) ts $
219 [ TargetPackage TargetExplicitNamed ["p-0.1"] (Just kind)
220 | kind <- concatMap (replicate 3) [LibKind .. ]
221 ] ++
222 [ TargetPackage TargetExplicitNamed ["q-0.1"] (Just kind)
223 | kind <- concatMap (replicate 3) [LibKind .. ]
226 reportSubCase "component"
227 do Right ts <- readTargetSelectors'
228 [ "p", "lib:p", "p:lib:p", ":pkg:p:lib:p"
229 , "lib:q", "q:lib:q", ":pkg:q:lib:q" ]
230 ts @?= replicate 4 (TargetComponent "p-0.1" (CLibName LMainLibName) WholeComponent)
231 ++ replicate 3 (TargetComponent "q-0.1" (CLibName LMainLibName) WholeComponent)
233 reportSubCase "module"
234 do Right ts <- readTargetSelectors'
235 [ "P", "lib:p:P", "p:p:P", ":pkg:p:lib:p:module:P"
236 , "QQ", "lib:q:QQ", "q:q:QQ", ":pkg:q:lib:q:module:QQ"
237 , "pexe:PMain" -- p:P or q:QQ would be ambiguous here
238 , "qexe:QMain" -- package p vs component p
240 ts @?= replicate 4 (TargetComponent "p-0.1" (CLibName LMainLibName) (ModuleTarget "P"))
241 ++ replicate 4 (TargetComponent "q-0.1" (CLibName LMainLibName) (ModuleTarget "QQ"))
242 ++ [ TargetComponent "p-0.1" (CExeName "pexe") (ModuleTarget "PMain")
243 , TargetComponent "q-0.1" (CExeName "qexe") (ModuleTarget "QMain")
246 reportSubCase "file"
247 do Right ts <- readTargetSelectors'
248 [ "./P.hs", "p:P.lhs", "lib:p:P.hsc", "p:p:P.hsc",
249 ":pkg:p:lib:p:file:P.y"
250 , "q/QQ.hs", "q:QQ.lhs", "lib:q:QQ.hsc", "q:q:QQ.hsc",
251 ":pkg:q:lib:q:file:QQ.y"
252 , "q/Q.hs", "q:Q.lhs", "lib:q:Q.hsc", "q:q:Q.hsc",
253 ":pkg:q:lib:q:file:Q.y"
254 , "app/Main.hs", "p:app/Main.hs", "exe:ppexe:app/Main.hs", "p:ppexe:app/Main.hs",
255 ":pkg:p:exe:ppexe:file:app/Main.hs"
257 ts @?= replicate 5 (TargetComponent "p-0.1" (CLibName LMainLibName) (FileTarget "P"))
258 ++ replicate 5 (TargetComponent "q-0.1" (CLibName LMainLibName) (FileTarget "QQ"))
259 ++ replicate 5 (TargetComponent "q-0.1" (CLibName LMainLibName) (FileTarget "Q"))
260 ++ replicate 5 (TargetComponent "p-0.1" (CExeName "ppexe") (FileTarget ("app" </> "Main.hs")))
261 -- Note there's a bit of an inconsistency here: for the single-part
262 -- syntax the target has to point to a file that exists, whereas for
263 -- all the other forms we don't require that.
265 cleanProject testdir
266 where
267 testdir = "targets/simple"
268 config = mempty
271 testTargetSelectorBadSyntax :: Assertion
272 testTargetSelectorBadSyntax = do
273 (_, _, _, localPackages, _) <- configureProject testdir config
274 let targets = [ "foo bar", " foo"
275 , "foo:", "foo::bar"
276 , "foo: ", "foo: :bar"
277 , "a:b:c:d:e:f", "a:b:c:d:e:f:g:h" ]
278 Left errs <- readTargetSelectors localPackages Nothing targets
279 zipWithM_ (@?=) errs (map TargetSelectorUnrecognised targets)
280 cleanProject testdir
281 where
282 testdir = "targets/empty"
283 config = mempty
286 testTargetSelectorAmbiguous :: (String -> IO ()) -> Assertion
287 testTargetSelectorAmbiguous reportSubCase = do
289 -- 'all' is ambiguous with packages and cwd components
290 reportSubCase "ambiguous: all vs pkg"
291 assertAmbiguous "all"
292 [mkTargetPackage "all", mkTargetAllPackages]
293 [mkpkg "all" []]
295 reportSubCase "ambiguous: all vs cwd component"
296 assertAmbiguous "all"
297 [mkTargetComponent "other" (CExeName "all"), mkTargetAllPackages]
298 [mkpkg "other" [mkexe "all"]]
300 -- but 'all' is not ambiguous with non-cwd components, modules or files
301 reportSubCase "unambiguous: all vs non-cwd comp, mod, file"
302 assertUnambiguous "All"
303 mkTargetAllPackages
304 [ mkpkgAt "foo" [mkexe "All"] "foo"
305 , mkpkg "bar" [ mkexe "bar" `withModules` ["All"]
306 , mkexe "baz" `withCFiles` ["All"] ]
309 -- filters 'libs', 'exes' etc are ambiguous with packages and
310 -- local components
311 reportSubCase "ambiguous: cwd-pkg filter vs pkg"
312 assertAmbiguous "libs"
313 [ mkTargetPackage "libs"
314 , TargetPackage TargetImplicitCwd ["libs"] (Just LibKind) ]
315 [mkpkg "libs" []]
317 reportSubCase "ambiguous: filter vs cwd component"
318 assertAmbiguous "exes"
319 [ mkTargetComponent "other" (CExeName "exes")
320 , TargetPackage TargetImplicitCwd ["other"] (Just ExeKind) ]
321 [mkpkg "other" [mkexe "exes"]]
323 -- but filters are not ambiguous with non-cwd components, modules or files
324 reportSubCase "unambiguous: filter vs non-cwd comp, mod, file"
325 assertUnambiguous "Libs"
326 (TargetPackage TargetImplicitCwd ["bar"] (Just LibKind))
327 [ mkpkgAt "foo" [mkexe "Libs"] "foo"
328 , mkpkg "bar" [ mkexe "bar" `withModules` ["Libs"]
329 , mkexe "baz" `withCFiles` ["Libs"] ]
332 -- local components shadow packages and other components
333 reportSubCase "unambiguous: cwd comp vs pkg, non-cwd comp"
334 assertUnambiguous "foo"
335 (mkTargetComponent "other" (CExeName "foo"))
336 [ mkpkg "other" [mkexe "foo"]
337 , mkpkgAt "other2" [mkexe "foo"] "other2" -- shadows non-local foo
338 , mkpkg "foo" [] ] -- shadows package foo
340 -- local components shadow modules and files
341 reportSubCase "unambiguous: cwd comp vs module, file"
342 assertUnambiguous "Foo"
343 (mkTargetComponent "bar" (CExeName "Foo"))
344 [ mkpkg "bar" [mkexe "Foo"]
345 , mkpkg "other" [ mkexe "other" `withModules` ["Foo"]
346 , mkexe "other2" `withCFiles` ["Foo"] ]
349 -- packages shadow non-local components
350 reportSubCase "unambiguous: pkg vs non-cwd comp"
351 assertUnambiguous "foo"
352 (mkTargetPackage "foo")
353 [ mkpkg "foo" []
354 , mkpkgAt "other" [mkexe "foo"] "other" -- shadows non-local foo
357 -- packages shadow modules and files
358 reportSubCase "unambiguous: pkg vs module, file"
359 assertUnambiguous "Foo"
360 (mkTargetPackage "Foo")
361 [ mkpkgAt "Foo" [] "foo"
362 , mkpkg "other" [ mkexe "other" `withModules` ["Foo"]
363 , mkexe "other2" `withCFiles` ["Foo"] ]
366 -- File target is ambiguous, part of multiple components
367 reportSubCase "ambiguous: file in multiple comps"
368 assertAmbiguous "Bar.hs"
369 [ mkTargetFile "foo" (CExeName "bar") "Bar"
370 , mkTargetFile "foo" (CExeName "bar2") "Bar"
372 [ mkpkg "foo" [ mkexe "bar" `withModules` ["Bar"]
373 , mkexe "bar2" `withModules` ["Bar"] ]
375 reportSubCase "ambiguous: file in multiple comps with path"
376 assertAmbiguous ("src" </> "Bar.hs")
377 [ mkTargetFile "foo" (CExeName "bar") ("src" </> "Bar")
378 , mkTargetFile "foo" (CExeName "bar2") ("src" </> "Bar")
380 [ mkpkg "foo" [ mkexe "bar" `withModules` ["Bar"] `withHsSrcDirs` ["src"]
381 , mkexe "bar2" `withModules` ["Bar"] `withHsSrcDirs` ["src"] ]
384 -- non-exact case packages and components are ambiguous
385 reportSubCase "ambiguous: non-exact-case pkg names"
386 assertAmbiguous "Foo"
387 [ mkTargetPackage "foo", mkTargetPackage "FOO" ]
388 [ mkpkg "foo" [], mkpkg "FOO" [] ]
389 reportSubCase "ambiguous: non-exact-case comp names"
390 assertAmbiguous "Foo"
391 [ mkTargetComponent "bar" (CExeName "foo")
392 , mkTargetComponent "bar" (CExeName "FOO") ]
393 [ mkpkg "bar" [mkexe "foo", mkexe "FOO"] ]
395 -- exact-case Module or File over non-exact case package or component
396 reportSubCase "unambiguous: module vs non-exact-case pkg, comp"
397 assertUnambiguous "Baz"
398 (mkTargetModule "other" (CExeName "other") "Baz")
399 [ mkpkg "baz" [mkexe "BAZ"]
400 , mkpkg "other" [ mkexe "other" `withModules` ["Baz"] ]
402 reportSubCase "unambiguous: file vs non-exact-case pkg, comp"
403 assertUnambiguous "Baz"
404 (mkTargetFile "other" (CExeName "other") "Baz")
405 [ mkpkg "baz" [mkexe "BAZ"]
406 , mkpkg "other" [ mkexe "other" `withCFiles` ["Baz"] ]
408 where
409 assertAmbiguous :: String
410 -> [TargetSelector]
411 -> [SourcePackage (PackageLocation a)]
412 -> Assertion
413 assertAmbiguous str tss pkgs = do
414 res <- readTargetSelectorsWith
415 fakeDirActions
416 (map SpecificSourcePackage pkgs)
417 Nothing
418 [str]
419 case res of
420 Left [TargetSelectorAmbiguous _ tss'] ->
421 sort (map snd tss') @?= sort tss
422 _ -> assertFailure $ "expected Left [TargetSelectorAmbiguous _ _], "
423 ++ "got " ++ show res
425 assertUnambiguous :: String
426 -> TargetSelector
427 -> [SourcePackage (PackageLocation a)]
428 -> Assertion
429 assertUnambiguous str ts pkgs = do
430 res <- readTargetSelectorsWith
431 fakeDirActions
432 (map SpecificSourcePackage pkgs)
433 Nothing
434 [str]
435 case res of
436 Right [ts'] -> ts' @?= ts
437 _ -> assertFailure $ "expected Right [Target...], "
438 ++ "got " ++ show res
440 fakeDirActions = TS.DirActions {
441 TS.doesFileExist = \_p -> return True,
442 TS.doesDirectoryExist = \_p -> return True,
443 TS.canonicalizePath = \p -> return ("/" </> p), -- FilePath.Unix.</> ?
444 TS.getCurrentDirectory = return "/"
447 mkpkg :: String -> [Executable] -> SourcePackage (PackageLocation a)
448 mkpkg pkgidstr exes = mkpkgAt pkgidstr exes ""
450 mkpkgAt :: String -> [Executable] -> FilePath
451 -> SourcePackage (PackageLocation a)
452 mkpkgAt pkgidstr exes loc =
453 SourcePackage {
454 srcpkgPackageId = pkgid,
455 srcpkgSource = LocalUnpackedPackage loc,
456 srcpkgDescrOverride = Nothing,
457 srcpkgDescription = GenericPackageDescription {
458 packageDescription = emptyPackageDescription { package = pkgid },
459 gpdScannedVersion = Nothing,
460 genPackageFlags = [],
461 condLibrary = Nothing,
462 condSubLibraries = [],
463 condForeignLibs = [],
464 condExecutables = [ ( exeName exe, CondNode exe [] [] )
465 | exe <- exes ],
466 condTestSuites = [],
467 condBenchmarks = []
470 where
471 pkgid = fromMaybe (error $ "failed to parse " ++ pkgidstr) $ simpleParse pkgidstr
473 mkexe :: String -> Executable
474 mkexe name = mempty { exeName = fromString name }
476 withModules :: Executable -> [String] -> Executable
477 withModules exe mods =
478 exe { buildInfo = (buildInfo exe) { otherModules = map fromString mods } }
480 withCFiles :: Executable -> [FilePath] -> Executable
481 withCFiles exe files =
482 exe { buildInfo = (buildInfo exe) { cSources = files } }
484 withHsSrcDirs :: Executable -> [FilePath] -> Executable
485 withHsSrcDirs exe srcDirs =
486 exe { buildInfo = (buildInfo exe) { hsSourceDirs = map unsafeMakeSymbolicPath srcDirs }}
489 mkTargetPackage :: PackageId -> TargetSelector
490 mkTargetPackage pkgid =
491 TargetPackage TargetExplicitNamed [pkgid] Nothing
493 mkTargetComponent :: PackageId -> ComponentName -> TargetSelector
494 mkTargetComponent pkgid cname =
495 TargetComponent pkgid cname WholeComponent
497 mkTargetModule :: PackageId -> ComponentName -> ModuleName -> TargetSelector
498 mkTargetModule pkgid cname mname =
499 TargetComponent pkgid cname (ModuleTarget mname)
501 mkTargetFile :: PackageId -> ComponentName -> String -> TargetSelector
502 mkTargetFile pkgid cname fname =
503 TargetComponent pkgid cname (FileTarget fname)
505 mkTargetAllPackages :: TargetSelector
506 mkTargetAllPackages = TargetAllPackages Nothing
508 instance IsString PackageIdentifier where
509 fromString pkgidstr = pkgid
510 where pkgid = fromMaybe (error $ "fromString @PackageIdentifier " ++ show pkgidstr) $ simpleParse pkgidstr
513 testTargetSelectorNoCurrentPackage :: Assertion
514 testTargetSelectorNoCurrentPackage = do
515 (_, _, _, localPackages, _) <- configureProject testdir config
516 let readTargetSelectors' = readTargetSelectorsWith (dirActions testdir)
517 localPackages
518 Nothing
519 targets = [ "libs", ":cwd:libs"
520 , "flibs", ":cwd:flibs"
521 , "exes", ":cwd:exes"
522 , "tests", ":cwd:tests"
523 , "benchmarks", ":cwd:benchmarks"]
524 Left errs <- readTargetSelectors' targets
525 zipWithM_ (@?=) errs
526 [ TargetSelectorNoCurrentPackage ts
527 | target <- targets
528 , let ts = fromMaybe (error $ "failed to parse target string " ++ target) $ parseTargetString target
530 cleanProject testdir
531 where
532 testdir = "targets/complex"
533 config = mempty
536 testTargetSelectorNoTargets :: Assertion
537 testTargetSelectorNoTargets = do
538 (_, _, _, localPackages, _) <- configureProject testdir config
539 Left errs <- readTargetSelectors localPackages Nothing []
540 errs @?= [TargetSelectorNoTargetsInCwd True]
541 cleanProject testdir
542 where
543 testdir = "targets/complex"
544 config = mempty
547 testTargetSelectorProjectEmpty :: Assertion
548 testTargetSelectorProjectEmpty = do
549 (_, _, _, localPackages, _) <- configureProject testdir config
550 Left errs <- readTargetSelectors localPackages Nothing []
551 errs @?= [TargetSelectorNoTargetsInProject]
552 cleanProject testdir
553 where
554 testdir = "targets/empty"
555 config = mempty
558 -- | Ensure we don't miss primary package and produce
559 -- TargetSelectorNoTargetsInCwd error due to symlink or
560 -- drive capitalisation mismatch when no targets are given
561 testTargetSelectorCanonicalizedPath :: Assertion
562 testTargetSelectorCanonicalizedPath = do
563 (_, _, _, localPackages, _) <- configureProject testdir config
564 cwd <- getCurrentDirectory
565 let virtcwd = cwd </> basedir </> symlink
566 -- Check that the symlink is there before running test as on Windows
567 -- some versions/configurations of git won't pull down/create the symlink
568 canRunTest <- doesDirectoryExist virtcwd
569 when canRunTest (do
570 let dirActions' = (dirActions symlink) { TS.getCurrentDirectory = return virtcwd }
571 Right ts <- readTargetSelectorsWith dirActions' localPackages Nothing []
572 ts @?= [TargetPackage TargetImplicitCwd ["p-0.1"] Nothing])
573 cleanProject testdir
574 where
575 testdir = "targets/simple"
576 symlink = "targets/symbolic-link-to-simple"
577 config = mempty
580 testTargetProblemsCommon :: ProjectConfig -> Assertion
581 testTargetProblemsCommon config0 = do
582 (_,elaboratedPlan,_) <- planProject testdir config
584 let pkgIdMap :: Map.Map PackageName PackageId
585 pkgIdMap = Map.fromList
586 [ (packageName p, packageId p)
587 | p <- InstallPlan.toList elaboratedPlan ]
589 cases :: [( TargetSelector -> TargetProblem'
590 , TargetSelector
592 cases =
593 [ -- Cannot resolve packages outside of the project
594 ( \_ -> TargetProblemNoSuchPackage "foobar"
595 , mkTargetPackage "foobar" )
597 -- We cannot currently build components like testsuites or
598 -- benchmarks from packages that are not local to the project
599 , ( \_ -> TargetComponentNotProjectLocal
600 (pkgIdMap Map.! "filepath") (CTestName "filepath-tests")
601 WholeComponent
602 , mkTargetComponent (pkgIdMap Map.! "filepath")
603 (CTestName "filepath-tests") )
605 -- Components can be explicitly @buildable: False@
606 , ( \_ -> TargetComponentNotBuildable "q-0.1" (CExeName "buildable-false") WholeComponent
607 , mkTargetComponent "q-0.1" (CExeName "buildable-false") )
609 -- Testsuites and benchmarks can be disabled by the solver if it
610 -- cannot satisfy deps
611 , ( \_ -> TargetOptionalStanzaDisabledBySolver "q-0.1" (CTestName "solver-disabled") WholeComponent
612 , mkTargetComponent "q-0.1" (CTestName "solver-disabled") )
614 -- Testsuites and benchmarks can be disabled explicitly by the
615 -- user via config
616 , ( \_ -> TargetOptionalStanzaDisabledByUser
617 "q-0.1" (CBenchName "user-disabled") WholeComponent
618 , mkTargetComponent "q-0.1" (CBenchName "user-disabled") )
620 -- An unknown package. The target selector resolution should only
621 -- produce known packages, so this should not happen with the
622 -- output from 'readTargetSelectors'.
623 , ( \_ -> TargetProblemNoSuchPackage "foobar"
624 , mkTargetPackage "foobar" )
626 -- An unknown component of a known package. The target selector
627 -- resolution should only produce known packages, so this should
628 -- not happen with the output from 'readTargetSelectors'.
629 , ( \_ -> TargetProblemNoSuchComponent "q-0.1" (CExeName "no-such")
630 , mkTargetComponent "q-0.1" (CExeName "no-such") )
632 assertTargetProblems
633 elaboratedPlan
634 CmdBuild.selectPackageTargets
635 CmdBuild.selectComponentTarget
636 cases
637 where
638 testdir = "targets/complex"
639 config = config0 {
640 projectConfigLocalPackages = (projectConfigLocalPackages config0) {
641 packageConfigBenchmarks = toFlag False
643 , projectConfigShared = (projectConfigShared config0) {
644 projectConfigConstraints =
645 [( UserConstraint (UserAnyQualifier "filepath") PackagePropertySource
646 , ConstraintSourceUnknown )]
651 testTargetProblemsBuild :: ProjectConfig -> (String -> IO ()) -> Assertion
652 testTargetProblemsBuild config reportSubCase = do
654 reportSubCase "empty-pkg"
655 assertProjectTargetProblems
656 "targets/empty-pkg" config
657 CmdBuild.selectPackageTargets
658 CmdBuild.selectComponentTarget
659 [ ( TargetProblemNoTargets, mkTargetPackage "p-0.1" )
662 reportSubCase "all-disabled"
663 assertProjectTargetProblems
664 "targets/all-disabled"
665 config {
666 projectConfigLocalPackages = (projectConfigLocalPackages config) {
667 packageConfigBenchmarks = toFlag False
670 CmdBuild.selectPackageTargets
671 CmdBuild.selectComponentTarget
672 [ ( flip TargetProblemNoneEnabled
673 [ AvailableTarget "p-0.1" (CBenchName "user-disabled")
674 TargetDisabledByUser True
675 , AvailableTarget "p-0.1" (CTestName "solver-disabled")
676 TargetDisabledBySolver True
677 , AvailableTarget "p-0.1" (CExeName "buildable-false")
678 TargetNotBuildable True
679 , AvailableTarget "p-0.1" (CLibName LMainLibName)
680 TargetNotBuildable True
682 , mkTargetPackage "p-0.1" )
685 reportSubCase "enabled component kinds"
686 -- When we explicitly enable all the component kinds then selecting the
687 -- whole package selects those component kinds too
688 do (_,elaboratedPlan,_) <- planProject "targets/variety" config {
689 projectConfigLocalPackages = (projectConfigLocalPackages config) {
690 packageConfigTests = toFlag True,
691 packageConfigBenchmarks = toFlag True
694 assertProjectDistinctTargets
695 elaboratedPlan
696 CmdBuild.selectPackageTargets
697 CmdBuild.selectComponentTarget
698 [ mkTargetPackage "p-0.1" ]
699 [ ("p-0.1-inplace", (CLibName LMainLibName))
700 , ("p-0.1-inplace-a-benchmark", CBenchName "a-benchmark")
701 , ("p-0.1-inplace-a-testsuite", CTestName "a-testsuite")
702 , ("p-0.1-inplace-an-exe", CExeName "an-exe")
703 , ("p-0.1-inplace-libp", CFLibName "libp")
706 reportSubCase "disabled component kinds"
707 -- When we explicitly disable all the component kinds then selecting the
708 -- whole package only selects the library, foreign lib and exes
709 do (_,elaboratedPlan,_) <- planProject "targets/variety" config {
710 projectConfigLocalPackages = (projectConfigLocalPackages config) {
711 packageConfigTests = toFlag False,
712 packageConfigBenchmarks = toFlag False
715 assertProjectDistinctTargets
716 elaboratedPlan
717 CmdBuild.selectPackageTargets
718 CmdBuild.selectComponentTarget
719 [ mkTargetPackage "p-0.1" ]
720 [ ("p-0.1-inplace", (CLibName LMainLibName))
721 , ("p-0.1-inplace-an-exe", CExeName "an-exe")
722 , ("p-0.1-inplace-libp", CFLibName "libp")
725 reportSubCase "requested component kinds"
726 -- When we selecting the package with an explicit filter then we get those
727 -- components even though we did not explicitly enable tests/benchmarks
728 do (_,elaboratedPlan,_) <- planProject "targets/variety" config
729 assertProjectDistinctTargets
730 elaboratedPlan
731 CmdBuild.selectPackageTargets
732 CmdBuild.selectComponentTarget
733 [ TargetPackage TargetExplicitNamed ["p-0.1"] (Just TestKind)
734 , TargetPackage TargetExplicitNamed ["p-0.1"] (Just BenchKind)
736 [ ("p-0.1-inplace-a-benchmark", CBenchName "a-benchmark")
737 , ("p-0.1-inplace-a-testsuite", CTestName "a-testsuite")
741 testTargetProblemsRepl :: ProjectConfig -> (String -> IO ()) -> Assertion
742 testTargetProblemsRepl config reportSubCase = do
744 reportSubCase "multiple-libs"
745 assertProjectTargetProblems
746 "targets/multiple-libs" config
747 (CmdRepl.selectPackageTargets (CmdRepl.MultiReplDecision Nothing False))
748 CmdRepl.selectComponentTarget
749 [ ( flip (CmdRepl.matchesMultipleProblem (CmdRepl.MultiReplDecision Nothing False))
750 [ AvailableTarget "p-0.1" (CLibName LMainLibName)
751 (TargetBuildable () TargetRequestedByDefault) True
752 , AvailableTarget "q-0.1" (CLibName LMainLibName)
753 (TargetBuildable () TargetRequestedByDefault) True
755 , mkTargetAllPackages )
758 reportSubCase "multiple-exes"
759 assertProjectTargetProblems
760 "targets/multiple-exes" config
761 (CmdRepl.selectPackageTargets (CmdRepl.MultiReplDecision Nothing False))
762 CmdRepl.selectComponentTarget
763 [ ( flip (CmdRepl.matchesMultipleProblem (CmdRepl.MultiReplDecision Nothing False))
764 [ AvailableTarget "p-0.1" (CExeName "p2")
765 (TargetBuildable () TargetRequestedByDefault) True
766 , AvailableTarget "p-0.1" (CExeName "p1")
767 (TargetBuildable () TargetRequestedByDefault) True
769 , mkTargetPackage "p-0.1" )
772 reportSubCase "multiple-tests"
773 assertProjectTargetProblems
774 "targets/multiple-tests" config
775 (CmdRepl.selectPackageTargets (CmdRepl.MultiReplDecision Nothing False))
776 CmdRepl.selectComponentTarget
777 [ ( flip (CmdRepl.matchesMultipleProblem (CmdRepl.MultiReplDecision Nothing False))
778 [ AvailableTarget "p-0.1" (CTestName "p2")
779 (TargetBuildable () TargetNotRequestedByDefault) True
780 , AvailableTarget "p-0.1" (CTestName "p1")
781 (TargetBuildable () TargetNotRequestedByDefault) True
783 , TargetPackage TargetExplicitNamed ["p-0.1"] (Just TestKind) )
786 reportSubCase "multiple targets"
787 do (_,elaboratedPlan,_) <- planProject "targets/multiple-exes" config
788 assertProjectDistinctTargets
789 elaboratedPlan
790 (CmdRepl.selectPackageTargets (CmdRepl.MultiReplDecision Nothing False))
791 CmdRepl.selectComponentTarget
792 [ mkTargetComponent "p-0.1" (CExeName "p1")
793 , mkTargetComponent "p-0.1" (CExeName "p2")
795 [ ("p-0.1-inplace-p1", CExeName "p1")
796 , ("p-0.1-inplace-p2", CExeName "p2")
799 reportSubCase "libs-disabled"
800 assertProjectTargetProblems
801 "targets/libs-disabled" config
802 (CmdRepl.selectPackageTargets (CmdRepl.MultiReplDecision Nothing False))
803 CmdRepl.selectComponentTarget
804 [ ( flip TargetProblemNoneEnabled
805 [ AvailableTarget "p-0.1" (CLibName LMainLibName) TargetNotBuildable True ]
806 , mkTargetPackage "p-0.1" )
809 reportSubCase "exes-disabled"
810 assertProjectTargetProblems
811 "targets/exes-disabled" config
812 (CmdRepl.selectPackageTargets (CmdRepl.MultiReplDecision Nothing False))
813 CmdRepl.selectComponentTarget
814 [ ( flip TargetProblemNoneEnabled
815 [ AvailableTarget "p-0.1" (CExeName "p") TargetNotBuildable True
817 , mkTargetPackage "p-0.1" )
820 reportSubCase "test-only"
821 assertProjectTargetProblems
822 "targets/test-only" config
823 (CmdRepl.selectPackageTargets (CmdRepl.MultiReplDecision Nothing False))
824 CmdRepl.selectComponentTarget
825 [ ( flip TargetProblemNoneEnabled
826 [ AvailableTarget "p-0.1" (CTestName "pexe")
827 (TargetBuildable () TargetNotRequestedByDefault) True
829 , mkTargetPackage "p-0.1" )
832 reportSubCase "empty-pkg"
833 assertProjectTargetProblems
834 "targets/empty-pkg" config
835 (CmdRepl.selectPackageTargets (CmdRepl.MultiReplDecision Nothing False))
836 CmdRepl.selectComponentTarget
837 [ ( TargetProblemNoTargets, mkTargetPackage "p-0.1" )
840 reportSubCase "requested component kinds"
841 do (_,elaboratedPlan,_) <- planProject "targets/variety" config
842 -- by default we only get the lib
843 assertProjectDistinctTargets
844 elaboratedPlan
845 (CmdRepl.selectPackageTargets (CmdRepl.MultiReplDecision Nothing False))
846 CmdRepl.selectComponentTarget
847 [ TargetPackage TargetExplicitNamed ["p-0.1"] Nothing ]
848 [ ("p-0.1-inplace", (CLibName LMainLibName)) ]
849 -- When we select the package with an explicit filter then we get those
850 -- components even though we did not explicitly enable tests/benchmarks
851 assertProjectDistinctTargets
852 elaboratedPlan
853 (CmdRepl.selectPackageTargets (CmdRepl.MultiReplDecision Nothing False))
854 CmdRepl.selectComponentTarget
855 [ TargetPackage TargetExplicitNamed ["p-0.1"] (Just TestKind) ]
856 [ ("p-0.1-inplace-a-testsuite", CTestName "a-testsuite") ]
857 assertProjectDistinctTargets
858 elaboratedPlan
859 (CmdRepl.selectPackageTargets (CmdRepl.MultiReplDecision Nothing False))
860 CmdRepl.selectComponentTarget
861 [ TargetPackage TargetExplicitNamed ["p-0.1"] (Just BenchKind) ]
862 [ ("p-0.1-inplace-a-benchmark", CBenchName "a-benchmark") ]
864 testTargetProblemsListBin :: ProjectConfig -> (String -> IO ()) -> Assertion
865 testTargetProblemsListBin config reportSubCase = do
866 reportSubCase "one-of-each"
867 do (_,elaboratedPlan,_) <- planProject "targets/one-of-each" config
868 assertProjectDistinctTargets
869 elaboratedPlan
870 CmdListBin.selectPackageTargets
871 CmdListBin.selectComponentTarget
872 [ TargetPackage TargetExplicitNamed ["p-0.1"] Nothing
874 [ ("p-0.1-inplace-p1", CExeName "p1")
877 reportSubCase "multiple-exes"
878 assertProjectTargetProblems
879 "targets/multiple-exes" config
880 CmdListBin.selectPackageTargets
881 CmdListBin.selectComponentTarget
882 [ ( flip CmdListBin.matchesMultipleProblem
883 [ AvailableTarget "p-0.1" (CExeName "p2")
884 (TargetBuildable () TargetRequestedByDefault) True
885 , AvailableTarget "p-0.1" (CExeName "p1")
886 (TargetBuildable () TargetRequestedByDefault) True
888 , mkTargetPackage "p-0.1" )
891 reportSubCase "multiple targets"
892 do (_,elaboratedPlan,_) <- planProject "targets/multiple-exes" config
893 assertProjectDistinctTargets
894 elaboratedPlan
895 CmdListBin.selectPackageTargets
896 CmdListBin.selectComponentTarget
897 [ mkTargetComponent "p-0.1" (CExeName "p1")
898 , mkTargetComponent "p-0.1" (CExeName "p2")
900 [ ("p-0.1-inplace-p1", CExeName "p1")
901 , ("p-0.1-inplace-p2", CExeName "p2")
904 reportSubCase "exes-disabled"
905 assertProjectTargetProblems
906 "targets/exes-disabled" config
907 CmdListBin.selectPackageTargets
908 CmdListBin.selectComponentTarget
909 [ ( flip TargetProblemNoneEnabled
910 [ AvailableTarget "p-0.1" (CExeName "p") TargetNotBuildable True
912 , mkTargetPackage "p-0.1" )
915 reportSubCase "empty-pkg"
916 assertProjectTargetProblems
917 "targets/empty-pkg" config
918 CmdListBin.selectPackageTargets
919 CmdListBin.selectComponentTarget
920 [ ( TargetProblemNoTargets, mkTargetPackage "p-0.1" )
923 reportSubCase "lib-only"
924 assertProjectTargetProblems
925 "targets/lib-only" config
926 CmdListBin.selectPackageTargets
927 CmdListBin.selectComponentTarget
928 [ (CmdListBin.noComponentsProblem, mkTargetPackage "p-0.1" )
931 testTargetProblemsRun :: ProjectConfig -> (String -> IO ()) -> Assertion
932 testTargetProblemsRun config reportSubCase = do
933 reportSubCase "one-of-each"
934 do (_,elaboratedPlan,_) <- planProject "targets/one-of-each" config
935 assertProjectDistinctTargets
936 elaboratedPlan
937 CmdRun.selectPackageTargets
938 CmdRun.selectComponentTarget
939 [ TargetPackage TargetExplicitNamed ["p-0.1"] Nothing
941 [ ("p-0.1-inplace-p1", CExeName "p1")
944 reportSubCase "multiple-exes"
945 assertProjectTargetProblems
946 "targets/multiple-exes" config
947 CmdRun.selectPackageTargets
948 CmdRun.selectComponentTarget
949 [ ( flip CmdRun.matchesMultipleProblem
950 [ AvailableTarget "p-0.1" (CExeName "p2")
951 (TargetBuildable () TargetRequestedByDefault) True
952 , AvailableTarget "p-0.1" (CExeName "p1")
953 (TargetBuildable () TargetRequestedByDefault) True
955 , mkTargetPackage "p-0.1" )
958 reportSubCase "multiple targets"
959 do (_,elaboratedPlan,_) <- planProject "targets/multiple-exes" config
960 assertProjectDistinctTargets
961 elaboratedPlan
962 CmdRun.selectPackageTargets
963 CmdRun.selectComponentTarget
964 [ mkTargetComponent "p-0.1" (CExeName "p1")
965 , mkTargetComponent "p-0.1" (CExeName "p2")
967 [ ("p-0.1-inplace-p1", CExeName "p1")
968 , ("p-0.1-inplace-p2", CExeName "p2")
971 reportSubCase "exes-disabled"
972 assertProjectTargetProblems
973 "targets/exes-disabled" config
974 CmdRun.selectPackageTargets
975 CmdRun.selectComponentTarget
976 [ ( flip TargetProblemNoneEnabled
977 [ AvailableTarget "p-0.1" (CExeName "p") TargetNotBuildable True
979 , mkTargetPackage "p-0.1" )
982 reportSubCase "empty-pkg"
983 assertProjectTargetProblems
984 "targets/empty-pkg" config
985 CmdRun.selectPackageTargets
986 CmdRun.selectComponentTarget
987 [ ( TargetProblemNoTargets, mkTargetPackage "p-0.1" )
990 reportSubCase "lib-only"
991 assertProjectTargetProblems
992 "targets/lib-only" config
993 CmdRun.selectPackageTargets
994 CmdRun.selectComponentTarget
995 [ (CmdRun.noExesProblem, mkTargetPackage "p-0.1" )
999 testTargetProblemsTest :: ProjectConfig -> (String -> IO ()) -> Assertion
1000 testTargetProblemsTest config reportSubCase = do
1002 reportSubCase "disabled by config"
1003 assertProjectTargetProblems
1004 "targets/tests-disabled"
1005 config {
1006 projectConfigLocalPackages = (projectConfigLocalPackages config) {
1007 packageConfigTests = toFlag False
1010 CmdTest.selectPackageTargets
1011 CmdTest.selectComponentTarget
1012 [ ( flip TargetProblemNoneEnabled
1013 [ AvailableTarget "p-0.1" (CTestName "user-disabled")
1014 TargetDisabledByUser True
1015 , AvailableTarget "p-0.1" (CTestName "solver-disabled")
1016 TargetDisabledByUser True
1018 , mkTargetPackage "p-0.1" )
1021 reportSubCase "disabled by solver & buildable false"
1022 assertProjectTargetProblems
1023 "targets/tests-disabled"
1024 config
1025 CmdTest.selectPackageTargets
1026 CmdTest.selectComponentTarget
1027 [ ( flip TargetProblemNoneEnabled
1028 [ AvailableTarget "p-0.1" (CTestName "user-disabled")
1029 TargetDisabledBySolver True
1030 , AvailableTarget "p-0.1" (CTestName "solver-disabled")
1031 TargetDisabledBySolver True
1033 , mkTargetPackage "p-0.1" )
1035 , ( flip TargetProblemNoneEnabled
1036 [ AvailableTarget "q-0.1" (CTestName "buildable-false")
1037 TargetNotBuildable True
1039 , mkTargetPackage "q-0.1" )
1042 reportSubCase "empty-pkg"
1043 assertProjectTargetProblems
1044 "targets/empty-pkg" config
1045 CmdTest.selectPackageTargets
1046 CmdTest.selectComponentTarget
1047 [ ( TargetProblemNoTargets, mkTargetPackage "p-0.1" )
1050 reportSubCase "no tests"
1051 assertProjectTargetProblems
1052 "targets/simple"
1053 config
1054 CmdTest.selectPackageTargets
1055 CmdTest.selectComponentTarget
1056 [ ( CmdTest.noTestsProblem, mkTargetPackage "p-0.1" )
1057 , ( CmdTest.noTestsProblem, mkTargetPackage "q-0.1" )
1060 reportSubCase "not a test"
1061 assertProjectTargetProblems
1062 "targets/variety"
1063 config
1064 CmdTest.selectPackageTargets
1065 CmdTest.selectComponentTarget $
1066 [ ( const (CmdTest.notTestProblem
1067 "p-0.1" (CLibName LMainLibName))
1068 , mkTargetComponent "p-0.1" (CLibName LMainLibName) )
1070 , ( const (CmdTest.notTestProblem
1071 "p-0.1" (CExeName "an-exe"))
1072 , mkTargetComponent "p-0.1" (CExeName "an-exe") )
1074 , ( const (CmdTest.notTestProblem
1075 "p-0.1" (CFLibName "libp"))
1076 , mkTargetComponent "p-0.1" (CFLibName "libp") )
1078 , ( const (CmdTest.notTestProblem
1079 "p-0.1" (CBenchName "a-benchmark"))
1080 , mkTargetComponent "p-0.1" (CBenchName "a-benchmark") )
1081 ] ++
1082 [ ( const (CmdTest.isSubComponentProblem
1083 "p-0.1" cname (ModuleTarget modname))
1084 , mkTargetModule "p-0.1" cname modname )
1085 | (cname, modname) <- [ (CTestName "a-testsuite", "TestModule")
1086 , (CBenchName "a-benchmark", "BenchModule")
1087 , (CExeName "an-exe", "ExeModule")
1088 , ((CLibName LMainLibName), "P")
1090 ] ++
1091 [ ( const (CmdTest.isSubComponentProblem
1092 "p-0.1" cname (FileTarget fname))
1093 , mkTargetFile "p-0.1" cname fname)
1094 | (cname, fname) <- [ (CTestName "a-testsuite", "Test.hs")
1095 , (CBenchName "a-benchmark", "Bench.hs")
1096 , (CExeName "an-exe", "Main.hs")
1101 testTargetProblemsBench :: ProjectConfig -> (String -> IO ()) -> Assertion
1102 testTargetProblemsBench config reportSubCase = do
1104 reportSubCase "disabled by config"
1105 assertProjectTargetProblems
1106 "targets/benchmarks-disabled"
1107 config {
1108 projectConfigLocalPackages = (projectConfigLocalPackages config) {
1109 packageConfigBenchmarks = toFlag False
1112 CmdBench.selectPackageTargets
1113 CmdBench.selectComponentTarget
1114 [ ( flip TargetProblemNoneEnabled
1115 [ AvailableTarget "p-0.1" (CBenchName "user-disabled")
1116 TargetDisabledByUser True
1117 , AvailableTarget "p-0.1" (CBenchName "solver-disabled")
1118 TargetDisabledByUser True
1120 , mkTargetPackage "p-0.1" )
1123 reportSubCase "disabled by solver & buildable false"
1124 assertProjectTargetProblems
1125 "targets/benchmarks-disabled"
1126 config
1127 CmdBench.selectPackageTargets
1128 CmdBench.selectComponentTarget
1129 [ ( flip TargetProblemNoneEnabled
1130 [ AvailableTarget "p-0.1" (CBenchName "user-disabled")
1131 TargetDisabledBySolver True
1132 , AvailableTarget "p-0.1" (CBenchName "solver-disabled")
1133 TargetDisabledBySolver True
1135 , mkTargetPackage "p-0.1" )
1137 , ( flip TargetProblemNoneEnabled
1138 [ AvailableTarget "q-0.1" (CBenchName "buildable-false")
1139 TargetNotBuildable True
1141 , mkTargetPackage "q-0.1" )
1144 reportSubCase "empty-pkg"
1145 assertProjectTargetProblems
1146 "targets/empty-pkg" config
1147 CmdBench.selectPackageTargets
1148 CmdBench.selectComponentTarget
1149 [ ( TargetProblemNoTargets, mkTargetPackage "p-0.1" )
1152 reportSubCase "no benchmarks"
1153 assertProjectTargetProblems
1154 "targets/simple"
1155 config
1156 CmdBench.selectPackageTargets
1157 CmdBench.selectComponentTarget
1158 [ ( CmdBench.noBenchmarksProblem, mkTargetPackage "p-0.1" )
1159 , ( CmdBench.noBenchmarksProblem, mkTargetPackage "q-0.1" )
1162 reportSubCase "not a benchmark"
1163 assertProjectTargetProblems
1164 "targets/variety"
1165 config
1166 CmdBench.selectPackageTargets
1167 CmdBench.selectComponentTarget $
1168 [ ( const (CmdBench.componentNotBenchmarkProblem
1169 "p-0.1" (CLibName LMainLibName))
1170 , mkTargetComponent "p-0.1" (CLibName LMainLibName) )
1172 , ( const (CmdBench.componentNotBenchmarkProblem
1173 "p-0.1" (CExeName "an-exe"))
1174 , mkTargetComponent "p-0.1" (CExeName "an-exe") )
1176 , ( const (CmdBench.componentNotBenchmarkProblem
1177 "p-0.1" (CFLibName "libp"))
1178 , mkTargetComponent "p-0.1" (CFLibName "libp") )
1180 , ( const (CmdBench.componentNotBenchmarkProblem
1181 "p-0.1" (CTestName "a-testsuite"))
1182 , mkTargetComponent "p-0.1" (CTestName "a-testsuite") )
1183 ] ++
1184 [ ( const (CmdBench.isSubComponentProblem
1185 "p-0.1" cname (ModuleTarget modname))
1186 , mkTargetModule "p-0.1" cname modname )
1187 | (cname, modname) <- [ (CTestName "a-testsuite", "TestModule")
1188 , (CBenchName "a-benchmark", "BenchModule")
1189 , (CExeName "an-exe", "ExeModule")
1190 , ((CLibName LMainLibName), "P")
1192 ] ++
1193 [ ( const (CmdBench.isSubComponentProblem
1194 "p-0.1" cname (FileTarget fname))
1195 , mkTargetFile "p-0.1" cname fname)
1196 | (cname, fname) <- [ (CTestName "a-testsuite", "Test.hs")
1197 , (CBenchName "a-benchmark", "Bench.hs")
1198 , (CExeName "an-exe", "Main.hs")
1203 testTargetProblemsHaddock :: ProjectConfig -> (String -> IO ()) -> Assertion
1204 testTargetProblemsHaddock config reportSubCase = do
1206 reportSubCase "all-disabled"
1207 assertProjectTargetProblems
1208 "targets/all-disabled"
1209 config
1210 (let haddockFlags = mkHaddockFlags False True True False
1211 in CmdHaddock.selectPackageTargets haddockFlags)
1212 CmdHaddock.selectComponentTarget
1213 [ ( flip TargetProblemNoneEnabled
1214 [ AvailableTarget "p-0.1" (CBenchName "user-disabled")
1215 TargetDisabledByUser True
1216 , AvailableTarget "p-0.1" (CTestName "solver-disabled")
1217 TargetDisabledBySolver True
1218 , AvailableTarget "p-0.1" (CExeName "buildable-false")
1219 TargetNotBuildable True
1220 , AvailableTarget "p-0.1" (CLibName LMainLibName)
1221 TargetNotBuildable True
1223 , mkTargetPackage "p-0.1" )
1226 reportSubCase "empty-pkg"
1227 assertProjectTargetProblems
1228 "targets/empty-pkg" config
1229 (let haddockFlags = mkHaddockFlags False False False False
1230 in CmdHaddock.selectPackageTargets haddockFlags)
1231 CmdHaddock.selectComponentTarget
1232 [ ( TargetProblemNoTargets, mkTargetPackage "p-0.1" )
1235 reportSubCase "enabled component kinds"
1236 -- When we explicitly enable all the component kinds then selecting the
1237 -- whole package selects those component kinds too
1238 (_,elaboratedPlan,_) <- planProject "targets/variety" config
1239 let haddockFlags = mkHaddockFlags True True True True
1240 in assertProjectDistinctTargets
1241 elaboratedPlan
1242 (CmdHaddock.selectPackageTargets haddockFlags)
1243 CmdHaddock.selectComponentTarget
1244 [ mkTargetPackage "p-0.1" ]
1245 [ ("p-0.1-inplace", (CLibName LMainLibName))
1246 , ("p-0.1-inplace-a-benchmark", CBenchName "a-benchmark")
1247 , ("p-0.1-inplace-a-testsuite", CTestName "a-testsuite")
1248 , ("p-0.1-inplace-an-exe", CExeName "an-exe")
1249 , ("p-0.1-inplace-libp", CFLibName "libp")
1252 reportSubCase "disabled component kinds"
1253 -- When we explicitly disable all the component kinds then selecting the
1254 -- whole package only selects the library
1255 let haddockFlags = mkHaddockFlags False False False False
1256 in assertProjectDistinctTargets
1257 elaboratedPlan
1258 (CmdHaddock.selectPackageTargets haddockFlags)
1259 CmdHaddock.selectComponentTarget
1260 [ mkTargetPackage "p-0.1" ]
1261 [ ("p-0.1-inplace", (CLibName LMainLibName)) ]
1263 reportSubCase "requested component kinds"
1264 -- When we selecting the package with an explicit filter then it does not
1265 -- matter if the config was to disable all the component kinds
1266 let haddockFlags = mkHaddockFlags False False False False
1267 in assertProjectDistinctTargets
1268 elaboratedPlan
1269 (CmdHaddock.selectPackageTargets haddockFlags)
1270 CmdHaddock.selectComponentTarget
1271 [ TargetPackage TargetExplicitNamed ["p-0.1"] (Just FLibKind)
1272 , TargetPackage TargetExplicitNamed ["p-0.1"] (Just ExeKind)
1273 , TargetPackage TargetExplicitNamed ["p-0.1"] (Just TestKind)
1274 , TargetPackage TargetExplicitNamed ["p-0.1"] (Just BenchKind)
1276 [ ("p-0.1-inplace-a-benchmark", CBenchName "a-benchmark")
1277 , ("p-0.1-inplace-a-testsuite", CTestName "a-testsuite")
1278 , ("p-0.1-inplace-an-exe", CExeName "an-exe")
1279 , ("p-0.1-inplace-libp", CFLibName "libp")
1281 where
1282 mkHaddockFlags flib exe test bench =
1283 defaultHaddockFlags {
1284 haddockForeignLibs = toFlag flib,
1285 haddockExecutables = toFlag exe,
1286 haddockTestSuites = toFlag test,
1287 haddockBenchmarks = toFlag bench
1290 assertProjectDistinctTargets
1291 :: forall err. (Eq err, Show err) =>
1292 ElaboratedInstallPlan
1293 -> (forall k. TargetSelector -> [AvailableTarget k] -> Either (TargetProblem err) [k])
1294 -> (forall k. SubComponentTarget -> AvailableTarget k -> Either (TargetProblem err) k )
1295 -> [TargetSelector]
1296 -> [(UnitId, ComponentName)]
1297 -> Assertion
1298 assertProjectDistinctTargets elaboratedPlan
1299 selectPackageTargets
1300 selectComponentTarget
1301 targetSelectors
1302 expectedTargets
1303 | Right targets <- results
1304 = distinctTargetComponents targets @?= Set.fromList expectedTargets
1306 | otherwise
1307 = assertFailure $ "assertProjectDistinctTargets: expected "
1308 ++ "(Right targets) but got " ++ show results
1309 where
1310 results = resolveTargets
1311 selectPackageTargets
1312 selectComponentTarget
1313 elaboratedPlan
1314 Nothing
1315 targetSelectors
1318 assertProjectTargetProblems
1319 :: forall err. (Eq err, Show err) =>
1320 FilePath -> ProjectConfig
1321 -> (forall k. TargetSelector
1322 -> [AvailableTarget k]
1323 -> Either (TargetProblem err) [k])
1324 -> (forall k. SubComponentTarget
1325 -> AvailableTarget k
1326 -> Either (TargetProblem err) k )
1327 -> [(TargetSelector -> TargetProblem err, TargetSelector)]
1328 -> Assertion
1329 assertProjectTargetProblems testdir config
1330 selectPackageTargets
1331 selectComponentTarget
1332 cases = do
1333 (_,elaboratedPlan,_) <- planProject testdir config
1334 assertTargetProblems
1335 elaboratedPlan
1336 selectPackageTargets
1337 selectComponentTarget
1338 cases
1341 assertTargetProblems
1342 :: forall err. (Eq err, Show err) =>
1343 ElaboratedInstallPlan
1344 -> (forall k. TargetSelector -> [AvailableTarget k] -> Either (TargetProblem err) [k])
1345 -> (forall k. SubComponentTarget -> AvailableTarget k -> Either (TargetProblem err) k )
1346 -> [(TargetSelector -> TargetProblem err, TargetSelector)]
1347 -> Assertion
1348 assertTargetProblems elaboratedPlan selectPackageTargets selectComponentTarget =
1349 mapM_ (uncurry assertTargetProblem)
1350 where
1351 assertTargetProblem expected targetSelector =
1352 let res = resolveTargets selectPackageTargets selectComponentTarget
1353 elaboratedPlan Nothing
1354 [targetSelector] in
1355 case res of
1356 Left [problem] ->
1357 problem @?= expected targetSelector
1359 unexpected ->
1360 assertFailure $ "expected resolveTargets result: (Left [problem]) "
1361 ++ "but got: " ++ show unexpected
1364 testExceptionInFindingPackage :: ProjectConfig -> Assertion
1365 testExceptionInFindingPackage config = do
1366 BadPackageLocations _ locs <- expectException "BadPackageLocations" $
1367 void $ planProject testdir config
1368 case locs of
1369 [BadLocGlobEmptyMatch "./*.cabal"] -> return ()
1370 _ -> assertFailure "expected BadLocGlobEmptyMatch"
1371 cleanProject testdir
1372 where
1373 testdir = "exception/no-pkg"
1376 testExceptionInFindingPackage2 :: ProjectConfig -> Assertion
1377 testExceptionInFindingPackage2 config = do
1378 BadPackageLocations _ locs <- expectException "BadPackageLocations" $
1379 void $ planProject testdir config
1380 case locs of
1381 [BadPackageLocationFile (BadLocDirNoCabalFile ".")] -> return ()
1382 _ -> assertFailure $ "expected BadLocDirNoCabalFile, got " ++ show locs
1383 cleanProject testdir
1384 where
1385 testdir = "exception/no-pkg2"
1388 testExceptionInProjectConfig :: ProjectConfig -> Assertion
1389 testExceptionInProjectConfig config = do
1390 BadPerPackageCompilerPaths ps <- expectException "BadPerPackageCompilerPaths" $
1391 void $ planProject testdir config
1392 case ps of
1393 [(pn,"ghc")] | "foo" == pn -> return ()
1394 _ -> assertFailure $ "expected (PackageName \"foo\",\"ghc\"), got "
1395 ++ show ps
1396 cleanProject testdir
1397 where
1398 testdir = "exception/bad-config"
1401 testExceptionInConfigureStep :: ProjectConfig -> Assertion
1402 testExceptionInConfigureStep config = do
1403 (plan, res) <- executePlan =<< planProject testdir config
1404 (_pkga1, failure) <- expectPackageFailed plan res pkgidA1
1405 case buildFailureReason failure of
1406 ConfigureFailed _ -> return ()
1407 _ -> assertFailure $ "expected ConfigureFailed, got " ++ show failure
1408 cleanProject testdir
1409 where
1410 testdir = "exception/configure"
1411 pkgidA1 = PackageIdentifier "a" (mkVersion [1])
1414 testExceptionInBuildStep :: ProjectConfig -> Assertion
1415 testExceptionInBuildStep config = do
1416 (plan, res) <- executePlan =<< planProject testdir config
1417 (_pkga1, failure) <- expectPackageFailed plan res pkgidA1
1418 expectBuildFailed failure
1419 where
1420 testdir = "exception/build"
1421 pkgidA1 = PackageIdentifier "a" (mkVersion [1])
1423 testSetupScriptStyles :: ProjectConfig -> (String -> IO ()) -> Assertion
1424 testSetupScriptStyles config reportSubCase = do
1426 reportSubCase (show SetupCustomExplicitDeps)
1428 plan0@(_,_,sharedConfig) <- planProject testdir1 config
1430 let isOSX (Platform _ OSX) = True
1431 isOSX _ = False
1432 -- Skip the Custom tests when the shipped Cabal library is buggy
1433 unless (isOSX (pkgConfigPlatform sharedConfig)
1434 && compilerVersion (pkgConfigCompiler sharedConfig) < mkVersion [7,10]) $ do
1436 (plan1, res1) <- executePlan plan0
1437 pkg1 <- expectPackageInstalled plan1 res1 pkgidA
1438 elabSetupScriptStyle pkg1 @?= SetupCustomExplicitDeps
1439 hasDefaultSetupDeps pkg1 @?= Just False
1440 marker1 <- readFile (basedir </> testdir1 </> "marker")
1441 marker1 @?= "ok"
1442 removeFile (basedir </> testdir1 </> "marker")
1444 -- implicit deps implies 'Cabal < 2' which conflicts w/ GHC 8.2 or later
1445 when (compilerVersion (pkgConfigCompiler sharedConfig) < mkVersion [8,2]) $ do
1446 reportSubCase (show SetupCustomImplicitDeps)
1447 (plan2, res2) <- executePlan =<< planProject testdir2 config
1448 pkg2 <- expectPackageInstalled plan2 res2 pkgidA
1449 elabSetupScriptStyle pkg2 @?= SetupCustomImplicitDeps
1450 hasDefaultSetupDeps pkg2 @?= Just True
1451 marker2 <- readFile (basedir </> testdir2 </> "marker")
1452 marker2 @?= "ok"
1453 removeFile (basedir </> testdir2 </> "marker")
1455 reportSubCase (show SetupNonCustomInternalLib)
1456 (plan3, res3) <- executePlan =<< planProject testdir3 config
1457 pkg3 <- expectPackageInstalled plan3 res3 pkgidA
1458 elabSetupScriptStyle pkg3 @?= SetupNonCustomInternalLib
1460 --TODO: the SetupNonCustomExternalLib case is hard to test since it
1461 -- requires a version of Cabal that's later than the one we're testing
1462 -- e.g. needs a .cabal file that specifies cabal-version: >= 2.0
1463 -- and a corresponding Cabal package that we can use to try and build a
1464 -- default Setup.hs.
1465 reportSubCase (show SetupNonCustomExternalLib)
1466 (plan4, res4) <- executePlan =<< planProject testdir4 config
1467 pkg4 <- expectPackageInstalled plan4 res4 pkgidA
1468 pkgSetupScriptStyle pkg4 @?= SetupNonCustomExternalLib
1470 where
1471 testdir1 = "build/setup-custom1"
1472 testdir2 = "build/setup-custom2"
1473 testdir3 = "build/setup-simple"
1474 pkgidA = PackageIdentifier "a" (mkVersion [0,1])
1475 -- The solver fills in default setup deps explicitly, but marks them as such
1476 hasDefaultSetupDeps = fmap defaultSetupDepends
1477 . setupBuildInfo . elabPkgDescription
1479 -- | Test the behaviour with and without @--keep-going@
1481 testBuildKeepGoing :: ProjectConfig -> Assertion
1482 testBuildKeepGoing config = do
1483 -- P is expected to fail, Q does not depend on P but without
1484 -- parallel build and without keep-going then we don't build Q yet.
1485 (plan1, res1) <- executePlan =<< planProject testdir (config `mappend` keepGoing False)
1486 (_, failure1) <- expectPackageFailed plan1 res1 "p-0.1"
1487 expectBuildFailed failure1
1488 _ <- expectPackageConfigured plan1 res1 "q-0.1"
1490 -- With keep-going then we should go on to successfully build Q
1491 (plan2, res2) <- executePlan
1492 =<< planProject testdir (config `mappend` keepGoing True)
1493 (_, failure2) <- expectPackageFailed plan2 res2 "p-0.1"
1494 expectBuildFailed failure2
1495 _ <- expectPackageInstalled plan2 res2 "q-0.1"
1496 return ()
1497 where
1498 testdir = "build/keep-going"
1499 keepGoing kg =
1500 mempty {
1501 projectConfigBuildOnly = mempty {
1502 projectConfigKeepGoing = toFlag kg
1506 -- | Test we can successfully build packages from local tarball files.
1508 testBuildLocalTarball :: ProjectConfig -> Assertion
1509 testBuildLocalTarball config = do
1510 -- P is a tarball package, Q is a local dir package that depends on it.
1511 (plan, res) <- executePlan =<< planProject testdir config
1512 _ <- expectPackageInstalled plan res "p-0.1"
1513 _ <- expectPackageInstalled plan res "q-0.1"
1514 return ()
1515 where
1516 testdir = "build/local-tarball"
1518 -- | See <https://github.com/haskell/cabal/issues/3324>
1520 -- This test just doesn't seem to work on Windows,
1521 -- due filesystem woes.
1523 testRegressionIssue3324 :: ProjectConfig -> Assertion
1524 testRegressionIssue3324 config = when (buildOS /= Windows) $ do
1525 -- expected failure first time due to missing dep
1526 (plan1, res1) <- executePlan =<< planProject testdir config
1527 (_pkgq, failure) <- expectPackageFailed plan1 res1 "q-0.1"
1528 expectBuildFailed failure
1530 -- add the missing dep, now it should work
1531 let qcabal = basedir </> testdir </> "q" </> "q.cabal"
1532 withFileFinallyRestore qcabal $ do
1533 tryFewTimes $ BS.appendFile qcabal (" build-depends: p\n")
1534 (plan2, res2) <- executePlan =<< planProject testdir config
1535 _ <- expectPackageInstalled plan2 res2 "p-0.1"
1536 _ <- expectPackageInstalled plan2 res2 "q-0.1"
1537 return ()
1538 where
1539 testdir = "regression/3324"
1541 -- | Test global program options are propagated correctly
1542 -- from ProjectConfig to ElaboratedInstallPlan
1543 testProgramOptionsAll :: ProjectConfig -> Assertion
1544 testProgramOptionsAll config0 = do
1545 -- P is a tarball package, Q is a local dir package that depends on it.
1546 (_, elaboratedPlan, _) <- planProject testdir config
1547 let packages = filterConfiguredPackages $ InstallPlan.toList elaboratedPlan
1549 assertEqual "q"
1550 (Just [ghcFlag])
1551 (getProgArgs packages "q")
1552 assertEqual "p"
1553 (Just [ghcFlag])
1554 (getProgArgs packages "p")
1555 where
1556 testdir = "regression/program-options"
1557 programArgs = MapMappend (Map.fromList [("ghc", [ghcFlag])])
1558 ghcFlag = "-fno-full-laziness"
1560 -- Insert flag into global config
1561 config = config0 {
1562 projectConfigAllPackages = (projectConfigAllPackages config0) {
1563 packageConfigProgramArgs = programArgs
1567 -- | Test local program options are propagated correctly
1568 -- from ProjectConfig to ElaboratedInstallPlan
1569 testProgramOptionsLocal :: ProjectConfig -> Assertion
1570 testProgramOptionsLocal config0 = do
1571 (_, elaboratedPlan, _) <- planProject testdir config
1572 let localPackages = filterConfiguredPackages $ InstallPlan.toList elaboratedPlan
1574 assertEqual "q"
1575 (Just [ghcFlag])
1576 (getProgArgs localPackages "q")
1577 assertEqual "p"
1578 Nothing
1579 (getProgArgs localPackages "p")
1580 where
1581 testdir = "regression/program-options"
1582 programArgs = MapMappend (Map.fromList [("ghc", [ghcFlag])])
1583 ghcFlag = "-fno-full-laziness"
1585 -- Insert flag into local config
1586 config = config0 {
1587 projectConfigLocalPackages = (projectConfigLocalPackages config0) {
1588 packageConfigProgramArgs = programArgs
1592 -- | Test package specific program options are propagated correctly
1593 -- from ProjectConfig to ElaboratedInstallPlan
1594 testProgramOptionsSpecific :: ProjectConfig -> Assertion
1595 testProgramOptionsSpecific config0 = do
1596 (_, elaboratedPlan, _) <- planProject testdir config
1597 let packages = filterConfiguredPackages $ InstallPlan.toList elaboratedPlan
1599 assertEqual "q"
1600 (Nothing)
1601 (getProgArgs packages "q")
1602 assertEqual "p"
1603 (Just [ghcFlag])
1604 (getProgArgs packages "p")
1605 where
1606 testdir = "regression/program-options"
1607 programArgs = MapMappend (Map.fromList [("ghc", [ghcFlag])])
1608 ghcFlag = "-fno-full-laziness"
1610 -- Insert flag into package "p" config
1611 config = config0 {
1612 projectConfigSpecificPackage = MapMappend (Map.fromList [(mkPackageName "p", configArgs)])
1614 configArgs = mempty {
1615 packageConfigProgramArgs = programArgs
1618 filterConfiguredPackages :: [ElaboratedPlanPackage] -> [ElaboratedConfiguredPackage]
1619 filterConfiguredPackages [] = []
1620 filterConfiguredPackages (InstallPlan.PreExisting _ : pkgs) = filterConfiguredPackages pkgs
1621 filterConfiguredPackages (InstallPlan.Installed elab : pkgs) = elab : filterConfiguredPackages pkgs
1622 filterConfiguredPackages (InstallPlan.Configured elab : pkgs) = elab : filterConfiguredPackages pkgs
1624 getProgArgs :: [ElaboratedConfiguredPackage] -> String -> Maybe [String]
1625 getProgArgs [] _ = Nothing
1626 getProgArgs (elab : pkgs) name
1627 | pkgName (elabPkgSourceId elab) == mkPackageName name
1628 = Map.lookup "ghc" (elabProgramArgs elab)
1629 | otherwise
1630 = getProgArgs pkgs name
1632 ---------------------------------
1633 -- Test utils to plan and build
1636 basedir :: FilePath
1637 basedir = "tests" </> "IntegrationTests2"
1639 dirActions :: FilePath -> TS.DirActions IO
1640 dirActions testdir =
1641 defaultDirActions {
1642 TS.doesFileExist = \p ->
1643 TS.doesFileExist defaultDirActions (virtcwd </> p),
1645 TS.doesDirectoryExist = \p ->
1646 TS.doesDirectoryExist defaultDirActions (virtcwd </> p),
1648 TS.canonicalizePath = \p ->
1649 TS.canonicalizePath defaultDirActions (virtcwd </> p),
1651 TS.getCurrentDirectory =
1652 TS.canonicalizePath defaultDirActions virtcwd
1654 where
1655 virtcwd = basedir </> testdir
1657 type ProjDetails = (DistDirLayout,
1658 CabalDirLayout,
1659 ProjectConfig,
1660 [PackageSpecifier UnresolvedSourcePackage],
1661 BuildTimeSettings)
1663 configureProject :: FilePath -> ProjectConfig -> IO ProjDetails
1664 configureProject testdir cliConfig = do
1665 cabalDirLayout <- defaultCabalDirLayout
1667 projectRootDir <- canonicalizePath (basedir </> testdir)
1668 isexplict <- doesFileExist (projectRootDir </> defaultProjectFile)
1670 let projectRoot
1671 | isexplict = ProjectRootExplicit projectRootDir defaultProjectFile
1672 | otherwise = ProjectRootImplicit projectRootDir
1673 distDirLayout = defaultDistDirLayout projectRoot Nothing Nothing
1675 -- Clear state between test runs. The state remains if the previous run
1676 -- ended in an exception (as we leave the files to help with debugging).
1677 cleanProject testdir
1679 httpTransport <- configureTransport verbosity [] Nothing
1681 (projectConfig, localPackages) <-
1682 rebuildProjectConfig verbosity
1683 httpTransport
1684 distDirLayout
1685 cliConfig
1687 let buildSettings = resolveBuildTimeSettings
1688 verbosity cabalDirLayout
1689 projectConfig
1691 return (distDirLayout,
1692 cabalDirLayout,
1693 projectConfig,
1694 localPackages,
1695 buildSettings)
1697 type PlanDetails = (ProjDetails,
1698 ElaboratedInstallPlan,
1699 ElaboratedSharedConfig)
1701 planProject :: FilePath -> ProjectConfig -> IO PlanDetails
1702 planProject testdir cliConfig = do
1704 projDetails@(
1705 distDirLayout,
1706 cabalDirLayout,
1707 projectConfig,
1708 localPackages,
1709 _buildSettings) <- configureProject testdir cliConfig
1711 (elaboratedPlan, _, elaboratedShared, _, _) <-
1712 rebuildInstallPlan verbosity
1713 distDirLayout cabalDirLayout
1714 projectConfig
1715 localPackages
1716 Nothing
1718 return (projDetails,
1719 elaboratedPlan,
1720 elaboratedShared)
1722 executePlan :: PlanDetails -> IO (ElaboratedInstallPlan, BuildOutcomes)
1723 executePlan ((distDirLayout, cabalDirLayout, config, _, buildSettings),
1724 elaboratedPlan,
1725 elaboratedShared) = do
1727 let targets :: Map.Map UnitId [ComponentTarget]
1728 targets =
1729 Map.fromList
1730 [ (unitid, [ComponentTarget cname WholeComponent])
1731 | ts <- Map.elems (availableTargets elaboratedPlan)
1732 , AvailableTarget {
1733 availableTargetStatus = TargetBuildable (unitid, cname) _
1734 } <- ts
1736 elaboratedPlan' = pruneInstallPlanToTargets
1737 TargetActionBuild targets
1738 elaboratedPlan
1740 pkgsBuildStatus <-
1741 rebuildTargetsDryRun distDirLayout elaboratedShared
1742 elaboratedPlan'
1744 let elaboratedPlan'' = improveInstallPlanWithUpToDatePackages
1745 pkgsBuildStatus elaboratedPlan'
1747 buildOutcomes <-
1748 rebuildTargets verbosity
1749 config
1750 distDirLayout
1751 (cabalStoreDirLayout cabalDirLayout)
1752 elaboratedPlan''
1753 elaboratedShared
1754 pkgsBuildStatus
1755 -- Avoid trying to use act-as-setup mode:
1756 buildSettings { buildSettingNumJobs = 1 }
1758 return (elaboratedPlan'', buildOutcomes)
1760 cleanProject :: FilePath -> IO ()
1761 cleanProject testdir = do
1762 alreadyExists <- doesDirectoryExist distDir
1763 when alreadyExists $ removePathForcibly distDir
1764 where
1765 projectRoot = ProjectRootImplicit (basedir </> testdir)
1766 distDirLayout = defaultDistDirLayout projectRoot Nothing Nothing
1767 distDir = distDirectory distDirLayout
1770 verbosity :: Verbosity
1771 verbosity = minBound --normal --verbose --maxBound --minBound
1775 -------------------------------------------
1776 -- Tasty integration to adjust the config
1779 withProjectConfig :: (ProjectConfig -> TestTree) -> TestTree
1780 withProjectConfig testtree =
1781 askOption $ \ghcPath ->
1782 testtree (mkProjectConfig ghcPath)
1784 mkProjectConfig :: GhcPath -> ProjectConfig
1785 mkProjectConfig (GhcPath ghcPath) =
1786 mempty {
1787 projectConfigShared = mempty {
1788 projectConfigHcPath = maybeToFlag ghcPath
1790 projectConfigBuildOnly = mempty {
1791 projectConfigNumJobs = toFlag (Just 1)
1794 where
1795 maybeToFlag = maybe mempty toFlag
1798 data GhcPath = GhcPath (Maybe FilePath)
1799 deriving Typeable
1801 instance IsOption GhcPath where
1802 defaultValue = GhcPath Nothing
1803 optionName = Tagged "with-ghc"
1804 optionHelp = Tagged "The ghc compiler to use"
1805 parseValue = Just . GhcPath . Just
1807 projectConfigOptionDescriptions :: [OptionDescription]
1808 projectConfigOptionDescriptions = [Option (Proxy :: Proxy GhcPath)]
1811 ---------------------------------------
1812 -- HUint style utils for this context
1815 expectException :: Exception e => String -> IO a -> IO e
1816 expectException expected action = do
1817 res <- try action
1818 case res of
1819 Left e -> return e
1820 Right _ -> throwIO $ HUnitFailure Nothing $ "expected an exception " ++ expected
1822 expectPackagePreExisting :: ElaboratedInstallPlan -> BuildOutcomes -> PackageId
1823 -> IO InstalledPackageInfo
1824 expectPackagePreExisting plan buildOutcomes pkgid = do
1825 planpkg <- expectPlanPackage plan pkgid
1826 case (planpkg, InstallPlan.lookupBuildOutcome planpkg buildOutcomes) of
1827 (InstallPlan.PreExisting pkg, Nothing)
1828 -> return pkg
1829 (_, buildResult) -> unexpectedBuildResult "PreExisting" planpkg buildResult
1831 expectPackageConfigured :: ElaboratedInstallPlan -> BuildOutcomes -> PackageId
1832 -> IO ElaboratedConfiguredPackage
1833 expectPackageConfigured plan buildOutcomes pkgid = do
1834 planpkg <- expectPlanPackage plan pkgid
1835 case (planpkg, InstallPlan.lookupBuildOutcome planpkg buildOutcomes) of
1836 (InstallPlan.Configured pkg, Nothing)
1837 -> return pkg
1838 (_, buildResult) -> unexpectedBuildResult "Configured" planpkg buildResult
1840 expectPackageInstalled :: ElaboratedInstallPlan -> BuildOutcomes -> PackageId
1841 -> IO ElaboratedConfiguredPackage
1842 expectPackageInstalled plan buildOutcomes pkgid = do
1843 planpkg <- expectPlanPackage plan pkgid
1844 case (planpkg, InstallPlan.lookupBuildOutcome planpkg buildOutcomes) of
1845 (InstallPlan.Configured pkg, Just (Right _result)) -- result isn't used by any test
1846 -> return pkg
1847 -- package can be installed in the global .store!
1848 -- (when installing from tarball!)
1849 (InstallPlan.Installed pkg, Nothing)
1850 -> return pkg
1851 (_, buildResult) -> unexpectedBuildResult "Installed" planpkg buildResult
1853 expectPackageFailed :: ElaboratedInstallPlan -> BuildOutcomes -> PackageId
1854 -> IO (ElaboratedConfiguredPackage, BuildFailure)
1855 expectPackageFailed plan buildOutcomes pkgid = do
1856 planpkg <- expectPlanPackage plan pkgid
1857 case (planpkg, InstallPlan.lookupBuildOutcome planpkg buildOutcomes) of
1858 (InstallPlan.Configured pkg, Just (Left failure))
1859 -> return (pkg, failure)
1860 (_, buildResult) -> unexpectedBuildResult "Failed" planpkg buildResult
1862 unexpectedBuildResult :: String -> ElaboratedPlanPackage
1863 -> Maybe (Either BuildFailure BuildResult) -> IO a
1864 unexpectedBuildResult expected planpkg buildResult =
1865 throwIO $ HUnitFailure Nothing $
1866 "expected to find " ++ display (packageId planpkg) ++ " in the "
1867 ++ expected ++ " state, but it is actually in the " ++ actual ++ " state."
1868 where
1869 actual = case (buildResult, planpkg) of
1870 (Nothing, InstallPlan.PreExisting{}) -> "PreExisting"
1871 (Nothing, InstallPlan.Configured{}) -> "Configured"
1872 (Just (Right _), InstallPlan.Configured{}) -> "Installed"
1873 (Just (Left _), InstallPlan.Configured{}) -> "Failed"
1874 (Nothing, InstallPlan.Installed{}) -> "Installed globally"
1875 _ -> "Impossible! " ++ show buildResult ++ show planpkg
1877 expectPlanPackage :: ElaboratedInstallPlan -> PackageId
1878 -> IO ElaboratedPlanPackage
1879 expectPlanPackage plan pkgid =
1880 case [ pkg
1881 | pkg <- InstallPlan.toList plan
1882 , packageId pkg == pkgid ] of
1883 [pkg] -> return pkg
1884 [] -> throwIO $ HUnitFailure Nothing $
1885 "expected to find " ++ display pkgid
1886 ++ " in the install plan but it's not there"
1887 _ -> throwIO $ HUnitFailure Nothing $
1888 "expected to find only one instance of " ++ display pkgid
1889 ++ " in the install plan but there's several"
1891 expectBuildFailed :: BuildFailure -> IO ()
1892 expectBuildFailed (BuildFailure _ (BuildFailed _)) = return ()
1893 expectBuildFailed (BuildFailure _ reason) =
1894 assertFailure $ "expected BuildFailed, got " ++ show reason
1896 ---------------------------------------
1897 -- Other utils
1900 -- | Allow altering a file during a test, but then restore it afterwards
1902 -- We read into the memory, as filesystems are tricky. (especially Windows)
1904 withFileFinallyRestore :: FilePath -> IO a -> IO a
1905 withFileFinallyRestore file action = do
1906 originalContents <- BS.readFile file
1907 action `finally` handle onIOError (tryFewTimes $ BS.writeFile file originalContents)
1908 where
1909 onIOError :: IOException -> IO ()
1910 onIOError e = putStrLn $ "WARNING: Cannot restore " ++ file ++ "; " ++ show e
1912 -- Hopefully works around some Windows file-locking things.
1913 -- Use with care:
1915 -- Try action 4 times, with small sleep in between,
1916 -- retrying if it fails for 'IOException' reason.
1918 tryFewTimes :: forall a. IO a -> IO a
1919 tryFewTimes action = go (3 :: Int) where
1920 go :: Int -> IO a
1921 go !n | n <= 0 = action
1922 | otherwise = action `catch` onIOError n
1924 onIOError :: Int -> IOException -> IO a
1925 onIOError n e = do
1926 hPutStrLn stderr $ "Trying " ++ show n ++ " after " ++ show e
1927 threadDelay 10000
1928 go (n - 1)
1930 testNixFlags :: Assertion
1931 testNixFlags = do
1932 let gc = globalCommand []
1933 -- changing from the v1 to v2 build command does not change whether the "--enable-nix" flag
1934 -- sets the globalNix param of the GlobalFlags type to True even though the v2 command doesn't use it
1935 let nixEnabledFlags = getFlags gc . commandParseArgs gc True $ ["--enable-nix", "build"]
1936 let nixDisabledFlags = getFlags gc . commandParseArgs gc True $ ["--disable-nix", "build"]
1937 let nixDefaultFlags = getFlags gc . commandParseArgs gc True $ ["build"]
1938 True @=? isJust nixDefaultFlags
1939 True @=? isJust nixEnabledFlags
1940 True @=? isJust nixDisabledFlags
1941 Just True @=? (fromFlag . globalNix . fromJust $ nixEnabledFlags)
1942 Just False @=? (fromFlag . globalNix . fromJust $ nixDisabledFlags)
1943 Nothing @=? (fromFlag . globalNix . fromJust $ nixDefaultFlags)
1945 -- Config file options
1946 trueConfig <- loadConfig verbosity (Flag (basedir </> "nix-config/nix-true"))
1947 falseConfig <- loadConfig verbosity (Flag (basedir </> "nix-config/nix-false"))
1949 Just True @=? (fromFlag . globalNix . savedGlobalFlags $ trueConfig)
1950 Just False @=? (fromFlag . globalNix . savedGlobalFlags $ falseConfig)
1952 where
1953 fromFlag :: Flag Bool -> Maybe Bool
1954 fromFlag (Flag x) = Just x
1955 fromFlag NoFlag = Nothing
1956 getFlags :: CommandUI GlobalFlags -> CommandParse (GlobalFlags -> GlobalFlags, [String]) -> Maybe GlobalFlags
1957 getFlags cui (CommandReadyToGo (mkflags, _)) = Just . mkflags . commandDefaultFlags $ cui
1958 getFlags _ _ = Nothing
1960 -- Tests whether config options are commented or not
1961 testConfigOptionComments :: Assertion
1962 testConfigOptionComments = do
1963 _ <- createDefaultConfigFile verbosity [] (basedir </> "config/default-config")
1964 defaultConfigFile <- readFile (basedir </> "config/default-config")
1966 " url" @=? findLineWith False "url" defaultConfigFile
1967 " -- secure" @=? findLineWith True "secure" defaultConfigFile
1968 " -- root-keys" @=? findLineWith True "root-keys" defaultConfigFile
1969 " -- key-threshold" @=? findLineWith True "key-threshold" defaultConfigFile
1971 "-- ignore-expiry" @=? findLineWith True "ignore-expiry" defaultConfigFile
1972 "-- http-transport" @=? findLineWith True "http-transport" defaultConfigFile
1973 "-- nix" @=? findLineWith True "nix" defaultConfigFile
1974 "-- store-dir" @=? findLineWith True "store-dir" defaultConfigFile
1975 "-- active-repositories" @=? findLineWith True "active-repositories" defaultConfigFile
1976 "-- local-no-index-repo" @=? findLineWith True "local-no-index-repo" defaultConfigFile
1977 "remote-repo-cache" @=? findLineWith False "remote-repo-cache" defaultConfigFile
1978 "-- logs-dir" @=? findLineWith True "logs-dir" defaultConfigFile
1979 "-- default-user-config" @=? findLineWith True "default-user-config" defaultConfigFile
1980 "-- verbose" @=? findLineWith True "verbose" defaultConfigFile
1981 "-- compiler" @=? findLineWith True "compiler" defaultConfigFile
1982 "-- cabal-file" @=? findLineWith True "cabal-file" defaultConfigFile
1983 "-- with-compiler" @=? findLineWith True "with-compiler" defaultConfigFile
1984 "-- with-hc-pkg" @=? findLineWith True "with-hc-pkg" defaultConfigFile
1985 "-- program-prefix" @=? findLineWith True "program-prefix" defaultConfigFile
1986 "-- program-suffix" @=? findLineWith True "program-suffix" defaultConfigFile
1987 "-- library-vanilla" @=? findLineWith True "library-vanilla" defaultConfigFile
1988 "-- library-profiling" @=? findLineWith True "library-profiling" defaultConfigFile
1989 "-- shared" @=? findLineWith True "shared" defaultConfigFile
1990 "-- static" @=? findLineWith True "static" defaultConfigFile
1991 "-- executable-dynamic" @=? findLineWith True "executable-dynamic" defaultConfigFile
1992 "-- executable-static" @=? findLineWith True "executable-static" defaultConfigFile
1993 "-- profiling" @=? findLineWith True "profiling" defaultConfigFile
1994 "-- executable-profiling" @=? findLineWith True "executable-profiling" defaultConfigFile
1995 "-- profiling-detail" @=? findLineWith True "profiling-detail" defaultConfigFile
1996 "-- library-profiling-detail" @=? findLineWith True "library-profiling-detail" defaultConfigFile
1997 "-- optimization" @=? findLineWith True "optimization" defaultConfigFile
1998 "-- debug-info" @=? findLineWith True "debug-info" defaultConfigFile
1999 "-- build-info" @=? findLineWith True "build-info" defaultConfigFile
2000 "-- library-for-ghci" @=? findLineWith True "library-for-ghci" defaultConfigFile
2001 "-- split-sections" @=? findLineWith True "split-sections" defaultConfigFile
2002 "-- split-objs" @=? findLineWith True "split-objs" defaultConfigFile
2003 "-- executable-stripping" @=? findLineWith True "executable-stripping" defaultConfigFile
2004 "-- library-stripping" @=? findLineWith True "library-stripping" defaultConfigFile
2005 "-- configure-option" @=? findLineWith True "configure-option" defaultConfigFile
2006 "-- user-install" @=? findLineWith True "user-install" defaultConfigFile
2007 "-- package-db" @=? findLineWith True "package-db" defaultConfigFile
2008 "-- flags" @=? findLineWith True "flags" defaultConfigFile
2009 "-- extra-include-dirs" @=? findLineWith True "extra-include-dirs" defaultConfigFile
2010 "-- deterministic" @=? findLineWith True "deterministic" defaultConfigFile
2011 "-- cid" @=? findLineWith True "cid" defaultConfigFile
2012 "-- extra-lib-dirs" @=? findLineWith True "extra-lib-dirs" defaultConfigFile
2013 "-- extra-lib-dirs-static" @=? findLineWith True "extra-lib-dirs-static" defaultConfigFile
2014 "-- extra-framework-dirs" @=? findLineWith True "extra-framework-dirs" defaultConfigFile
2015 "extra-prog-path" @=? findLineWith False "extra-prog-path" defaultConfigFile
2016 "-- instantiate-with" @=? findLineWith True "instantiate-with" defaultConfigFile
2017 "-- tests" @=? findLineWith True "tests" defaultConfigFile
2018 "-- coverage" @=? findLineWith True "coverage" defaultConfigFile
2019 "-- library-coverage" @=? findLineWith True "library-coverage" defaultConfigFile
2020 "-- exact-configuration" @=? findLineWith True "exact-configuration" defaultConfigFile
2021 "-- benchmarks" @=? findLineWith True "benchmarks" defaultConfigFile
2022 "-- relocatable" @=? findLineWith True "relocatable" defaultConfigFile
2023 "-- response-files" @=? findLineWith True "response-files" defaultConfigFile
2024 "-- allow-depending-on-private-libs" @=? findLineWith True "allow-depending-on-private-libs" defaultConfigFile
2025 "-- cabal-lib-version" @=? findLineWith True "cabal-lib-version" defaultConfigFile
2026 "-- append" @=? findLineWith True "append" defaultConfigFile
2027 "-- backup" @=? findLineWith True "backup" defaultConfigFile
2028 "-- constraint" @=? findLineWith True "constraint" defaultConfigFile
2029 "-- preference" @=? findLineWith True "preference" defaultConfigFile
2030 "-- solver" @=? findLineWith True "solver" defaultConfigFile
2031 "-- allow-older" @=? findLineWith True "allow-older" defaultConfigFile
2032 "-- allow-newer" @=? findLineWith True "allow-newer" defaultConfigFile
2033 "-- write-ghc-environment-files" @=? findLineWith True "write-ghc-environment-files" defaultConfigFile
2034 "-- documentation" @=? findLineWith True "documentation" defaultConfigFile
2035 "-- doc-index-file" @=? findLineWith True "doc-index-file" defaultConfigFile
2036 "-- only-download" @=? findLineWith True "only-download" defaultConfigFile
2037 "-- target-package-db" @=? findLineWith True "target-package-db" defaultConfigFile
2038 "-- max-backjumps" @=? findLineWith True "max-backjumps" defaultConfigFile
2039 "-- reorder-goals" @=? findLineWith True "reorder-goals" defaultConfigFile
2040 "-- count-conflicts" @=? findLineWith True "count-conflicts" defaultConfigFile
2041 "-- fine-grained-conflicts" @=? findLineWith True "fine-grained-conflicts" defaultConfigFile
2042 "-- minimize-conflict-set" @=? findLineWith True "minimize-conflict-set" defaultConfigFile
2043 "-- independent-goals" @=? findLineWith True "independent-goals" defaultConfigFile
2044 "-- prefer-oldest" @=? findLineWith True "prefer-oldest" defaultConfigFile
2045 "-- shadow-installed-packages" @=? findLineWith True "shadow-installed-packages" defaultConfigFile
2046 "-- strong-flags" @=? findLineWith True "strong-flags" defaultConfigFile
2047 "-- allow-boot-library-installs" @=? findLineWith True "allow-boot-library-installs" defaultConfigFile
2048 "-- reject-unconstrained-dependencies" @=? findLineWith True "reject-unconstrained-dependencies" defaultConfigFile
2049 "-- reinstall" @=? findLineWith True "reinstall" defaultConfigFile
2050 "-- avoid-reinstalls" @=? findLineWith True "avoid-reinstalls" defaultConfigFile
2051 "-- force-reinstalls" @=? findLineWith True "force-reinstalls" defaultConfigFile
2052 "-- upgrade-dependencies" @=? findLineWith True "upgrade-dependencies" defaultConfigFile
2053 "-- index-state" @=? findLineWith True "index-state" defaultConfigFile
2054 "-- root-cmd" @=? findLineWith True "root-cmd" defaultConfigFile
2055 "-- symlink-bindir" @=? findLineWith True "symlink-bindir" defaultConfigFile
2056 "build-summary" @=? findLineWith False "build-summary" defaultConfigFile
2057 "-- build-log" @=? findLineWith True "build-log" defaultConfigFile
2058 "remote-build-reporting" @=? findLineWith False "remote-build-reporting" defaultConfigFile
2059 "-- report-planning-failure" @=? findLineWith True "report-planning-failure" defaultConfigFile
2060 "-- per-component" @=? findLineWith True "per-component" defaultConfigFile
2061 "-- run-tests" @=? findLineWith True "run-tests" defaultConfigFile
2062 "jobs" @=? findLineWith False "jobs" defaultConfigFile
2063 "-- keep-going" @=? findLineWith True "keep-going" defaultConfigFile
2064 "-- offline" @=? findLineWith True "offline" defaultConfigFile
2065 "-- lib" @=? findLineWith True "lib" defaultConfigFile
2066 "-- package-env" @=? findLineWith True "package-env" defaultConfigFile
2067 "-- overwrite-policy" @=? findLineWith True "overwrite-policy" defaultConfigFile
2068 "-- install-method" @=? findLineWith True "install-method" defaultConfigFile
2069 "installdir" @=? findLineWith False "installdir" defaultConfigFile
2070 "-- username" @=? findLineWith True "username" defaultConfigFile
2071 "-- password" @=? findLineWith True "password" defaultConfigFile
2072 "-- password-command" @=? findLineWith True "password-command" defaultConfigFile
2073 "-- builddir" @=? findLineWith True "builddir" defaultConfigFile
2075 " -- keep-temp-files" @=? findLineWith True "keep-temp-files" defaultConfigFile
2076 " -- hoogle" @=? findLineWith True "hoogle" defaultConfigFile
2077 " -- html" @=? findLineWith True "html" defaultConfigFile
2078 " -- html-location" @=? findLineWith True "html-location" defaultConfigFile
2079 " -- executables" @=? findLineWith True "executables" defaultConfigFile
2080 " -- foreign-libraries" @=? findLineWith True "foreign-libraries" defaultConfigFile
2081 " -- all" @=? findLineWith True "all" defaultConfigFile
2082 " -- internal" @=? findLineWith True "internal" defaultConfigFile
2083 " -- css" @=? findLineWith True "css" defaultConfigFile
2084 " -- hyperlink-source" @=? findLineWith True "hyperlink-source" defaultConfigFile
2085 " -- quickjump" @=? findLineWith True "quickjump" defaultConfigFile
2086 " -- hscolour-css" @=? findLineWith True "hscolour-css" defaultConfigFile
2087 " -- contents-location" @=? findLineWith True "contents-location" defaultConfigFile
2088 " -- index-location" @=? findLineWith True "index-location" defaultConfigFile
2089 " -- base-url" @=? findLineWith True "base-url" defaultConfigFile
2090 " -- output-dir" @=? findLineWith True "output-dir" defaultConfigFile
2092 " -- interactive" @=? findLineWith True "interactive" defaultConfigFile
2093 " -- quiet" @=? findLineWith True "quiet" defaultConfigFile
2094 " -- no-comments" @=? findLineWith True "no-comments" defaultConfigFile
2095 " -- minimal" @=? findLineWith True "minimal" defaultConfigFile
2096 " -- cabal-version" @=? findLineWith True "cabal-version" defaultConfigFile
2097 " -- license" @=? findLineWith True "license" defaultConfigFile
2098 " -- extra-doc-file" @=? findLineWith True "extra-doc-file" defaultConfigFile
2099 " -- test-dir" @=? findLineWith True "test-dir" defaultConfigFile
2100 " -- simple" @=? findLineWith True "simple" defaultConfigFile
2101 " -- language" @=? findLineWith True "language" defaultConfigFile
2102 " -- application-dir" @=? findLineWith True "application-dir" defaultConfigFile
2103 " -- source-dir" @=? findLineWith True "source-dir" defaultConfigFile
2105 " -- prefix" @=? findLineWith True "prefix" defaultConfigFile
2106 " -- bindir"@=? findLineWith True "bindir" defaultConfigFile
2107 " -- libdir" @=? findLineWith True "libdir" defaultConfigFile
2108 " -- libsubdir" @=? findLineWith True "libsubdir" defaultConfigFile
2109 " -- dynlibdir" @=? findLineWith True "dynlibdir" defaultConfigFile
2110 " -- libexecdir" @=? findLineWith True "libexecdir" defaultConfigFile
2111 " -- libexecsubdir" @=? findLineWith True "libexecsubdir" defaultConfigFile
2112 " -- datadir" @=? findLineWith True "datadir" defaultConfigFile
2113 " -- datasubdir" @=? findLineWith True "datasubdir" defaultConfigFile
2114 " -- docdir" @=? findLineWith True "docdir" defaultConfigFile
2115 " -- htmldir" @=? findLineWith True "htmldir" defaultConfigFile
2116 " -- haddockdir" @=? findLineWith True "haddockdir" defaultConfigFile
2117 " -- sysconfdir" @=? findLineWith True "sysconfdir" defaultConfigFile
2119 " -- alex-location" @=? findLineWith True "alex-location" defaultConfigFile
2120 " -- ar-location" @=? findLineWith True "ar-location" defaultConfigFile
2121 " -- c2hs-location" @=? findLineWith True "c2hs-location" defaultConfigFile
2122 " -- cpphs-location" @=? findLineWith True "cpphs-location" defaultConfigFile
2123 " -- doctest-location" @=? findLineWith True "doctest-location" defaultConfigFile
2124 " -- gcc-location" @=? findLineWith True "gcc-location" defaultConfigFile
2125 " -- ghc-location" @=? findLineWith True "ghc-location" defaultConfigFile
2126 " -- ghc-pkg-location" @=? findLineWith True "ghc-pkg-location" defaultConfigFile
2127 " -- ghcjs-location" @=? findLineWith True "ghcjs-location" defaultConfigFile
2128 " -- ghcjs-pkg-location" @=? findLineWith True "ghcjs-pkg-location" defaultConfigFile
2129 " -- greencard-location" @=? findLineWith True "greencard-location" defaultConfigFile
2130 " -- haddock-location" @=? findLineWith True "haddock-location" defaultConfigFile
2131 " -- happy-location" @=? findLineWith True "happy-location" defaultConfigFile
2132 " -- haskell-suite-location" @=? findLineWith True "haskell-suite-location" defaultConfigFile
2133 " -- haskell-suite-pkg-location" @=? findLineWith True "haskell-suite-pkg-location" defaultConfigFile
2134 " -- hmake-location" @=? findLineWith True "hmake-location" defaultConfigFile
2135 " -- hpc-location" @=? findLineWith True "hpc-location" defaultConfigFile
2136 " -- hscolour-location" @=? findLineWith True "hscolour-location" defaultConfigFile
2137 " -- jhc-location" @=? findLineWith True "jhc-location" defaultConfigFile
2138 " -- ld-location" @=? findLineWith True "ld-location" defaultConfigFile
2139 " -- pkg-config-location" @=? findLineWith True "pkg-config-location" defaultConfigFile
2140 " -- runghc-location" @=? findLineWith True "runghc-location" defaultConfigFile
2141 " -- strip-location" @=? findLineWith True "strip-location" defaultConfigFile
2142 " -- tar-location" @=? findLineWith True "tar-location" defaultConfigFile
2143 " -- uhc-location" @=? findLineWith True "uhc-location" defaultConfigFile
2145 " -- alex-options" @=? findLineWith True "alex-options" defaultConfigFile
2146 " -- ar-options" @=? findLineWith True "ar-options" defaultConfigFile
2147 " -- c2hs-options" @=? findLineWith True "c2hs-options" defaultConfigFile
2148 " -- cpphs-options" @=? findLineWith True "cpphs-options" defaultConfigFile
2149 " -- doctest-options" @=? findLineWith True "doctest-options" defaultConfigFile
2150 " -- gcc-options" @=? findLineWith True "gcc-options" defaultConfigFile
2151 " -- ghc-options" @=? findLineWith True "ghc-options" defaultConfigFile
2152 " -- ghc-pkg-options" @=? findLineWith True "ghc-pkg-options" defaultConfigFile
2153 " -- ghcjs-options" @=? findLineWith True "ghcjs-options" defaultConfigFile
2154 " -- ghcjs-pkg-options" @=? findLineWith True "ghcjs-pkg-options" defaultConfigFile
2155 " -- greencard-options" @=? findLineWith True "greencard-options" defaultConfigFile
2156 " -- haddock-options" @=? findLineWith True "haddock-options" defaultConfigFile
2157 " -- happy-options" @=? findLineWith True "happy-options" defaultConfigFile
2158 " -- haskell-suite-options" @=? findLineWith True "haskell-suite-options" defaultConfigFile
2159 " -- haskell-suite-pkg-options" @=? findLineWith True "haskell-suite-pkg-options" defaultConfigFile
2160 " -- hmake-options" @=? findLineWith True "hmake-options" defaultConfigFile
2161 " -- hpc-options" @=? findLineWith True "hpc-options" defaultConfigFile
2162 " -- hsc2hs-options" @=? findLineWith True "hsc2hs-options" defaultConfigFile
2163 " -- hscolour-options" @=? findLineWith True "hscolour-options" defaultConfigFile
2164 " -- jhc-options" @=? findLineWith True "jhc-options" defaultConfigFile
2165 " -- ld-options" @=? findLineWith True "ld-options" defaultConfigFile
2166 " -- pkg-config-options" @=? findLineWith True "pkg-config-options" defaultConfigFile
2167 " -- runghc-options" @=? findLineWith True "runghc-options" defaultConfigFile
2168 " -- strip-options" @=? findLineWith True "strip-options" defaultConfigFile
2169 " -- tar-options" @=? findLineWith True "tar-options" defaultConfigFile
2170 " -- uhc-options" @=? findLineWith True "uhc-options" defaultConfigFile
2171 where
2172 -- | Find lines containing a target string.
2173 findLineWith :: Bool -> String -> String -> String
2174 findLineWith isComment target text
2175 | not . null $ findLinesWith isComment target text = removeCommentValue . L.head $ findLinesWith isComment target text
2176 | otherwise = ""
2177 findLinesWith :: Bool -> String -> String -> [String]
2178 findLinesWith isComment target
2179 | isComment = filter (isInfixOf (" " ++ target ++ ":")) . lines
2180 | otherwise = filter (isInfixOf (target ++ ":")) . lines
2181 removeCommentValue :: String -> String
2182 removeCommentValue = takeWhile (/= ':')
2184 testIgnoreProjectFlag :: Assertion
2185 testIgnoreProjectFlag = do
2186 -- Coverage flag should be false globally by default (~/.cabal folder)
2187 (_, _, prjConfigGlobal, _, _) <- configureProject testdir ignoreSetConfig
2188 let globalCoverageFlag = packageConfigCoverage . projectConfigLocalPackages $ prjConfigGlobal
2189 False @=? Flag.fromFlagOrDefault False globalCoverageFlag
2190 -- It is set to true in the cabal.project file
2191 (_, _, prjConfigLocal, _, _) <- configureProject testdir emptyConfig
2192 let localCoverageFlag = packageConfigCoverage . projectConfigLocalPackages $ prjConfigLocal
2193 True @=? Flag.fromFlagOrDefault False localCoverageFlag
2194 where
2195 testdir = "build/ignore-project"
2196 emptyConfig = mempty
2197 ignoreSetConfig :: ProjectConfig
2198 ignoreSetConfig = mempty { projectConfigShared = mempty { projectConfigIgnoreProject = Flag True } }