Skip to content
Snippets Groups Projects
Commit 769279e6 authored by Matthew Pickering's avatar Matthew Pickering Committed by Marge Bot
Browse files

testsuite: Fix calculation about whether to pass -dynamic to compiler

parent f9728fdb
No related branches found
No related tags found
No related merge requests found
......@@ -146,16 +146,12 @@ testRules = do
top <- topDirectory
depsPkgs <- mod_pkgs . packageDependencies <$> readPackageData progPkg
bindir <- getBinaryDirectory testGhc
debugged <- ghcDebugged <$> flavour <*> pure (stageOf testGhc)
dynPrograms <- dynamicGhcPrograms =<< flavour
test_args <- outOfTreeCompilerArgs
let dynPrograms = hasDynamic test_args
cmd [bindir </> "ghc" <.> exe] $
concatMap (\p -> ["-package", pkgName p]) depsPkgs ++
["-o", top -/- path, top -/- sourcePath] ++
mextra ++
-- If GHC is build with debug options, then build check-ppr
-- also with debug options. This allows, e.g., to print debug
-- messages of various RTS subsystems while using check-ppr.
(if debugged then ["-debug"] else []) ++
-- If GHC is build dynamic, then build check-ppr also dynamic.
(if dynPrograms then ["-dynamic"] else [])
......
{-# LANGUAGE TypeApplications #-}
module Settings.Builders.RunTest (runTestBuilderArgs, runTestGhcFlags, assertSameCompilerArgs) where
module Settings.Builders.RunTest (runTestBuilderArgs
, runTestGhcFlags
, assertSameCompilerArgs
, outOfTreeCompilerArgs
, TestCompilerArgs(..) ) where
import Hadrian.Utilities
import qualified System.FilePath
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment