Skip to content
This repository has been archived by the owner on Aug 2, 2020. It is now read-only.

Added support for testsuite #602

Merged
merged 12 commits into from
Jun 13, 2018
91 changes: 68 additions & 23 deletions src/CommandLine.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,8 @@
module CommandLine (
optDescrs, cmdLineArgsMap, cmdFlavour, lookupFreeze1, cmdIntegerSimple,
cmdProgressColour, cmdProgressInfo, cmdConfigure, cmdSplitObjects,
cmdInstallDestDir, lookupBuildRoot, TestArgs(..), defaultTestArgs
cmdInstallDestDir, lookupBuildRoot, TestArgs(..), TestSpeed(..),
defaultTestArgs
) where

import Data.Either
Expand All @@ -12,6 +13,8 @@ import Hadrian.Utilities hiding (buildRoot)
import System.Console.GetOpt
import System.Environment

data TestSpeed = Slow | Average | Fast deriving (Show, Eq)

-- | All arguments that can be passed to Hadrian via the command line.
data CommandLineArgs = CommandLineArgs
{ configure :: Bool
Expand Down Expand Up @@ -42,21 +45,29 @@ defaultCommandLineArgs = CommandLineArgs

-- | These arguments are used by the `test` target.
data TestArgs = TestArgs
{ testOnly :: Maybe String
{ testConfigs :: [String]
, testJUnit :: Maybe FilePath
, testOnly :: Maybe String
, testOnlyPerf :: Bool
, testSkipPerf :: Bool
, testSpeed :: TestSpeed
, testSummary :: Maybe FilePath
, testJUnit :: Maybe FilePath
, testConfigs :: [String] }
, testVerbosity:: Maybe String
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Hadrian (or Shake) already has -jN option, which is enough to control the speed of running testsuite. We don't need the testThreads here.

Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

@sighingnow Indeed! Well spotted.

Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Shake already provides a --verbose option, let's reuse it.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

The verbose option of Shake is boolean, whereas test suite supports 5 levels of verbosity. This is why I chose to pass a separate verbose argument.

Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I think that it may be convenient to control these two verbosity settings separately: you might want verbose testing, but not Shake diagnostic info. And vice versa. So, let's keep this flag.

, testWays :: [String] }
deriving (Eq, Show)

-- | Default value for `TestArgs`.
defaultTestArgs :: TestArgs
defaultTestArgs = TestArgs
{ testOnly = Nothing
{ testConfigs = []
, testJUnit = Nothing
, testOnly = Nothing
, testOnlyPerf = False
, testSkipPerf = False
, testSpeed = Average
, testSummary = Nothing
, testJUnit = Nothing
, testConfigs = [] }
, testVerbosity= Nothing
, testWays = [] }

readConfigure :: Either String (CommandLineArgs -> CommandLineArgs)
readConfigure = Right $ \flags -> flags { configure = True }
Expand Down Expand Up @@ -110,26 +121,52 @@ readProgressInfo ms =
readSplitObjects :: Either String (CommandLineArgs -> CommandLineArgs)
readSplitObjects = Right $ \flags -> flags { splitObjects = True }

readTestConfig :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs)
readTestConfig config =
case config of
Nothing -> Right id
Just conf -> Right $ \flags ->
let configs = conf : testConfigs (testArgs flags)
in flags { testArgs = (testArgs flags) { testConfigs = configs } }

readTestJUnit :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs)
readTestJUnit filepath = Right $ \flags -> flags { testArgs = (testArgs flags) { testJUnit = filepath } }

readTestOnly :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs)
readTestOnly tests = Right $ \flags -> flags { testArgs = (testArgs flags) { testOnly = tests } }

readTestOnlyPerf :: Either String (CommandLineArgs -> CommandLineArgs)
readTestOnlyPerf = Right $ \flags -> flags { testArgs = (testArgs flags) { testOnlyPerf = True } }

readTestSkipPerf :: Either String (CommandLineArgs -> CommandLineArgs)
readTestSkipPerf = Right $ \flags -> flags { testArgs = (testArgs flags) { testSkipPerf = True } }

readTestSpeed :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs)
readTestSpeed ms =
maybe (Left "Cannot parse test-speed") (Right . set) (go =<< lower <$> ms)
where
go :: String -> Maybe TestSpeed
go "fast" = Just Fast
go "slow" = Just Slow
go "average" = Just Average
go _ = Nothing
set :: TestSpeed -> CommandLineArgs -> CommandLineArgs
set flag flags = flags { testArgs = (testArgs flags) {testSpeed = flag} }

readTestSummary :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs)
readTestSummary filepath = Right $ \flags -> flags { testArgs = (testArgs flags) { testJUnit = filepath } }

readTestJUnit :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs)
readTestJUnit filepath = Right $ \flags -> flags { testArgs = (testArgs flags) { testJUnit = filepath } }

readTestConfig :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs)
readTestConfig config =
case config of
Nothing -> Right id
Just conf -> Right $ \flags ->
let configs = conf : testConfigs (testArgs flags)
in flags { testArgs = (testArgs flags) { testConfigs = configs } }

readTestVerbose :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs)
readTestVerbose verbose = Right $ \flags -> flags { testArgs = (testArgs flags) { testVerbosity = verbose } }

readTestWay :: Maybe String -> Either String (CommandLineArgs -> CommandLineArgs)
readTestWay ways =
case ways of
Nothing -> Right id
Just way -> Right $ \flags ->
let newWays = way : testWays (testArgs flags)
in flags { testArgs = (testArgs flags) {testWays = newWays} }
-- | Standard 'OptDescr' descriptions of Hadrian's command line arguments.
optDescrs :: [OptDescr (Either String (CommandLineArgs -> CommandLineArgs))]
optDescrs =
Expand All @@ -151,17 +188,25 @@ optDescrs =
"Progress info style (None, Brief, Normal or Unicorn)."
, Option [] ["split-objects"] (NoArg readSplitObjects)
"Generate split objects (requires a full clean rebuild)."
, Option [] ["config"] (OptArg readTestConfig "EXTRA_TEST_CONFIG")
"Configurations to run test, in key=value format."
, Option [] ["summary-junit"] (OptArg readTestJUnit "TEST_SUMMARY_JUNIT")
"Output testsuite summary in JUnit format."
, Option [] ["only"] (OptArg readTestOnly "TESTS")
"Test cases to run."
, Option [] ["only-perf"] (NoArg readTestOnlyPerf)
"Only run performance tests."
, Option [] ["skip-perf"] (NoArg readTestSkipPerf)
"Skip performance tests."
, Option [] ["test-speed"] (OptArg readTestSpeed "SPEED")
"fast, slow or normal. Normal by default"
, Option [] ["summary"] (OptArg readTestSummary "TEST_SUMMARY")
"Where to output the test summary file."
, Option [] ["summary-junit"] (OptArg readTestJUnit "TEST_SUMMARY_JUNIT")
"Output testsuite summary in JUnit format."
, Option [] ["config"] (OptArg readTestConfig "EXTRA_TEST_CONFIG")
"Configurations to run test, in key=value format." ]

, Option [] ["test-verbose"] (OptArg readTestVerbose "TEST_VERBOSE")
"A verbosity value between 0 and 5. 0 is silent, 4 and higher activates extra output."
, Option [] ["test-way"] (OptArg readTestWay "TEST_WAY")
"only run these ways" ]
Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

We need to document all these flags. You don't need to do this right in this PR, but at least please create an issue so that we don't forget about this.

-- | A type-indexed map containing Hadrian command line arguments to be passed
-- to Shake via 'shakeExtra'.
cmdLineArgsMap :: IO (Map.HashMap TypeRep Dynamic)
Expand Down
21 changes: 12 additions & 9 deletions src/GHC.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,15 @@
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
module GHC (
-- * GHC packages
array, base, binary, bytestring, cabal, checkPpr, compareSizes, compiler,
containers, deepseq, deriveConstants, directory, filepath, genapply,
genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal, ghcCompact, ghcHeap, ghci,
ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock, haskeline, hsc2hs, hp2ps, hpc,
hpcBin, integerGmp, integerSimple, iserv, libffi, libiserv, mtl, parsec,
parallel, pretty, process, rts, runGhc, stm, templateHaskell, terminfo,
text, time, touchy, transformers, unlit, unix, win32, xhtml, ghcPackages,
isGhcPackage, defaultPackages, testsuitePackages,
array, base, binary, bytestring, cabal, checkApiAnnotations, checkPpr,
compareSizes, compiler, containers, deepseq, deriveConstants, directory,
filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCabal,
ghcCompact, ghcHeap, ghci, ghcPkg, ghcPrim, ghcTags, ghcSplit, haddock,
haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv,
libffi, libiserv, mtl, parsec, parallel, pretty, primitive, process, rts,
runGhc, stm, templateHaskell, terminfo, text, time, touchy, transformers,
unlit, unix, win32, xhtml, ghcPackages, isGhcPackage, defaultPackages,
testsuitePackages,

-- * Package information
programName, nonCabalContext, nonHsMainPackage, autogenPath, installStage,
Expand Down Expand Up @@ -103,7 +104,9 @@ stage2Packages = return [haddock]

-- | Packages that are built only for the testsuite.
testsuitePackages :: Action [Package]
testsuitePackages = return [checkPpr]
testsuitePackages = return [ checkApiAnnotations
, checkPpr
, hp2ps ]

-- | Given a 'Context', compute the name of the program that is built in it
-- assuming that the corresponding package's type is 'Program'. For example, GHC
Expand Down
15 changes: 8 additions & 7 deletions src/GHC/Packages.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,13 +11,13 @@ import Hadrian.Utilities
-- modify build default build conditions in "UserSettings".
ghcPackages :: [Package]
ghcPackages =
[ array, base, binary, bytestring, cabal, checkPpr, compareSizes, compiler
, containers, deepseq, deriveConstants, directory, filepath, genapply
, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCompact, ghcHeap, ghci, ghcPkg
, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hp2ps, hpc, hpcBin, integerGmp
, integerSimple, iserv, libffi, libiserv, mtl, parsec, parallel, pretty
, process, rts, runGhc, stm, templateHaskell, terminfo, text, time, touchy
, transformers, unlit, unix, win32, xhtml ]
[ array, base, binary, bytestring, cabal, checkPpr, checkApiAnnotations
, compareSizes, compiler, containers, deepseq, deriveConstants, directory
, filepath, genapply, genprimopcode, ghc, ghcBoot, ghcBootTh, ghcCompact
, ghcHeap, ghci, ghcPkg, ghcPrim, ghcTags, haddock, haskeline, hsc2hs, hp2ps
, hpc, hpcBin, integerGmp, integerSimple, iserv, libffi, libiserv, mtl
, parsec, parallel, pretty, process, rts, runGhc, stm, templateHaskell
, terminfo, text, time, touchy, transformers, unlit, unix, win32, xhtml ]

-- TODO: Optimise by switching to sets of packages.
isGhcPackage :: Package -> Bool
Expand All @@ -29,6 +29,7 @@ base = hsLib "base"
binary = hsLib "binary"
bytestring = hsLib "bytestring"
cabal = hsLib "Cabal" `setPath` "libraries/Cabal/Cabal"
checkApiAnnotations = hsUtil "check-api-annotations"
checkPpr = hsUtil "check-ppr"
compareSizes = hsUtil "compareSizes" `setPath` "utils/compare_sizes"
compiler = hsTop "ghc" `setPath` "compiler"
Expand Down
2 changes: 1 addition & 1 deletion src/Hadrian/Utilities.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ module Hadrian.Utilities (
(<&>), (%%>), cmdLineLengthLimit,

-- * Useful re-exports
Dynamic, fromDynamic, toDyn, TypeRep, typeOf
Dynamic, fromDynamic, toDyn, TypeRep, typeOf,
Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Drop the comma

) where

import Control.Monad.Extra
Expand Down
13 changes: 12 additions & 1 deletion src/Rules/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ import Expression
import GHC
import Oracles.Flag
import Oracles.Setting
import Settings
import Target
import Utilities

Expand Down Expand Up @@ -63,13 +64,23 @@ testRules = do
-- Execute the test target.
buildWithCmdOptions env $ target (vanillaContext Stage2 compiler) RunTest [] []

-- | Build extra programs required by testsuite
Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

The code below suggests that there are not only testsuite programs, but also testsuite libraries.

Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

@chitrak7 So, do you really need to handle libraries here?

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I have to handle rts library. I just cannot yet figure out how.

Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Why do you need to handle rts here? How is it related to the testsuite?

Copy link
Owner

@snowleopard snowleopard Jun 12, 2018

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I still don't understand why needTestsuiteBuilders needs libraries. Can testsuitePackages contain library packages? Right now there are only contain programs. If testsuitePackages can contain libraries, then you need to rename this function to something like needTestsuitePackages (instead of Builders).

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Some files are missing in rts library causing multiple failures. At the moment, I cannot figure out which files are missing. Or they may be missing includes. I have to look into this matter further.

Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I don't understand how rts relates to this question. You don't have rts in testsuitePackages.

The comment for this function says "Build extra programs required by testsuite", but the implementation can also build libraries. This is an inconsistency that should be fixed.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Okay! I think I should create an issue regarding this and temporarily install required programs only.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Resolved

needTestsuiteBuilders :: Action ()
needTestsuiteBuilders = do
targets <- mapM (needfile Stage1) =<< testsuitePackages
need targets
where
needfile :: Stage -> Package -> Action FilePath
needfile stage pkg = programPath =<< programContext stage pkg


needTestBuilders :: Action ()
needTestBuilders = do
needBuilder $ Ghc CompileHs Stage2
needBuilder $ GhcPkg Update Stage1
needBuilder Hp2Ps
needBuilder Hpc
needBuilder (Hsc2Hs Stage1)
needTestsuiteBuilders

-- | Extra flags to send to the Haskell compiler to run tests.
runTestGhcFlags :: Action String
Expand Down
23 changes: 21 additions & 2 deletions src/Settings/Builders/Make.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
module Settings.Builders.Make (makeBuilderArgs) where
module Settings.Builders.Make (makeBuilderArgs, validateBuilderArgs) where

import GHC
import Oracles.Setting
import Rules.Gmp
import Rules.Libffi
import Settings.Builders.Common
Expand All @@ -13,5 +15,22 @@ makeBuilderArgs = do
mconcat
[ builder (Make gmpPath ) ? pure ["MAKEFLAGS=-j" ++ t]
, builder (Make libffiPath ) ? pure ["MAKEFLAGS=-j" ++ t, "install"]
, builder (Make "testsuite/tests") ? pure ["THREADS=" ++ t, "fast"]
]

validateBuilderArgs :: Args
validateBuilderArgs = builder (Make "testsuite/tests") ? do
threads <- shakeThreads <$> expr getShakeOptions
top <- expr topDirectory
compiler <- expr $ fullpath ghc
checkPpr <- expr $ fullpath checkPpr
checkApiAnnotations <- expr $ fullpath checkApiAnnotations
return [ "fast"
Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Is the "fast" above related to TestSpeed.Fast?

Copy link
Contributor Author

@chitrak7 chitrak7 Jun 12, 2018

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

No, this is the default validate argument. Speed can be specified by running ./build.sh test and not validate.

Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Worst case, we can later arrange to support --slow and --fast flags, like the actual validate script, can't we?

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Yeah. I can do that right now.

Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

OK, I guess we can leave this for later.

, "THREADS=" ++ show threads
, "TEST_HC=" ++ (top -/- compiler)
, "CHECK_PPR=" ++ (top -/- checkPpr)
, "CHECK_API_ANNOTATIONS=" ++ (top -/- checkApiAnnotations)
]
where
Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Let's rename f to something more informative, perhaps, fullPath.

Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Also, a type signature might help.

fullpath :: Package -> Action FilePath
fullpath pkg = programPath =<< programContext Stage1 pkg

37 changes: 32 additions & 5 deletions src/Settings/Builders/RunTest.hs
Original file line number Diff line number Diff line change
@@ -1,10 +1,11 @@
module Settings.Builders.RunTest (runTestBuilderArgs) where

import CommandLine (TestArgs(..), defaultTestArgs)
import CommandLine (TestArgs(..), defaultTestArgs, TestSpeed(..))
import Flavour
import GHC.Packages
import Hadrian.Builder (getBuilderPath)
import Hadrian.Utilities
import Oracles.Setting (setting)
import Rules.Test
import Settings.Builders.Common

Expand All @@ -28,7 +29,9 @@ runTestBuilderArgs = builder RunTest ? do

threads <- shakeThreads <$> expr getShakeOptions
verbose <- shakeVerbosity <$> expr getShakeOptions

os <- expr $ setting TargetOs
arch <- expr $ setting TargetArch
platform <- expr $ setting TargetPlatform
top <- expr topDirectory
compiler <- getBuilderPath $ Ghc CompileHs Stage2
ghcPkg <- getBuilderPath $ GhcPkg Update Stage1
Expand Down Expand Up @@ -71,7 +74,12 @@ runTestBuilderArgs = builder RunTest ? do
, arg "-e", arg $ "config.ghc_dynamic=False" -- TODO: support dynamic

, arg "-e", arg $ "config.in_tree_compiler=True" -- Use default value, see https://github.com/ghc/ghc/blob/master/testsuite/mk/boilerplate.mk

, arg "-e", arg $ "config.top=" ++ show (top -/- "testsuite")
, arg "-e", arg $ "config.wordsize=\"64\""
, arg "-e", arg $ "config.os=" ++ show os
, arg "-e", arg $ "config.arch=" ++ show arch
, arg "-e", arg $ "config.platform=" ++ show platform

, arg "--config-file=testsuite/config/ghc"
, arg "--config", arg $ "compiler=" ++ show (top -/- compiler)
, arg "--config", arg $ "ghc_pkg=" ++ show (top -/- ghcPkg)
Expand All @@ -92,15 +100,34 @@ getTestArgs = do
let testOnlyArg = case testOnly args of
Just cases -> map ("--only=" ++) (words cases)
Nothing -> []
onlyPerfArg = if testOnlyPerf args
then Just "--only-perf-tests"
else Nothing
skipPerfArg = if testSkipPerf args
then Just "--skip-perf-tests"
else Nothing
speedArg = ["-e", "config.speed=" ++ setTestSpeed (testSpeed args)]
summaryArg = case testSummary args of
Just filepath -> Just $ "--summary-file" ++ quote filepath
Nothing -> Just $ "--summary-file=testsuite_summary.txt"
junitArg = case testJUnit args of
Just filepath -> Just $ "--junit " ++ quote filepath
Nothing -> Nothing
configArgs = map ("-e " ++) (testConfigs args)
configArgs = concat [["-e", configArg] | configArg <- testConfigs args]
verbosityArg = case testVerbosity args of
Nothing -> Nothing
Just verbosity -> Just $ "--verbose=" ++ verbosity
wayArgs = map ("--way=" ++) (testWays args)
pure $ testOnlyArg
++ speedArg
++ catMaybes [ onlyPerfArg, skipPerfArg, summaryArg
, junitArg, verbosityArg ]
++ configArgs
++ wayArgs

-- | Set speed for test
setTestSpeed :: TestSpeed -> String
setTestSpeed Fast = "2"
setTestSpeed Average = "1"
setTestSpeed Slow = "0"

pure $ testOnlyArg ++ catMaybes [skipPerfArg, summaryArg, junitArg] ++ configArgs
1 change: 1 addition & 0 deletions src/Settings/Default.hs
Original file line number Diff line number Diff line change
Expand Up @@ -139,6 +139,7 @@ defaultBuilderArgs = mconcat
, ldBuilderArgs
, makeBuilderArgs
, runTestBuilderArgs
, validateBuilderArgs
, xelatexBuilderArgs
-- Generic builders from the Hadrian library:
, builder (Ar Pack ) ? Hadrian.Builder.Ar.args Pack
Expand Down