[commit: ghc] wip/nfs-locking: Add basic validation support (GHC tests). (e9abc61)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:45:08 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/e9abc617b6bd4ebf5c79ccd8fb8974d1f7c01101/ghc
>---------------------------------------------------------------
commit e9abc617b6bd4ebf5c79ccd8fb8974d1f7c01101
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Thu Jan 28 02:51:12 2016 +0000
Add basic validation support (GHC tests).
See #187.
>---------------------------------------------------------------
e9abc617b6bd4ebf5c79ccd8fb8974d1f7c01101
shaking-up-ghc.cabal | 1 +
src/Main.hs | 4 +++-
src/Test.hs | 63 ++++++++++++++++++++++++++++++++++++++++++++++++++++
3 files changed, 67 insertions(+), 1 deletion(-)
diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal
index 60f3c34..f00c7c6 100644
--- a/shaking-up-ghc.cabal
+++ b/shaking-up-ghc.cabal
@@ -105,6 +105,7 @@ executable ghc-shake
, Settings.Ways
, Stage
, Target
+ , Test
, Way
default-language: Haskell2010
diff --git a/src/Main.hs b/src/Main.hs
index befb6e7..2c944d4 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -15,6 +15,7 @@ import qualified Rules.Libffi
import qualified Rules.Oracles
import qualified Rules.Perl
import qualified Selftest
+import qualified Test
main :: IO ()
main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do
@@ -37,7 +38,8 @@ main = shakeArgsWith options CmdLineFlag.cmdFlags $ \cmdLineFlags targets -> do
, Rules.Perl.perlScriptRules
, Rules.generateTargets
, Rules.packageRules
- , Selftest.selftestRules ]
+ , Selftest.selftestRules
+ , Test.testRules ]
options = shakeOptions
{ shakeChange = ChangeModtimeAndDigest
, shakeFiles = Base.shakeFilesPath
diff --git a/src/Test.hs b/src/Test.hs
new file mode 100644
index 0000000..547e286
--- /dev/null
+++ b/src/Test.hs
@@ -0,0 +1,63 @@
+module Test (testRules) where
+
+import Base
+import Builder
+import Expression
+import GHC (rts, libffi)
+import Oracles.Config.Flag
+import Oracles.Config.Setting
+import Oracles.WindowsRoot -- TODO: rename to Oracles.TopDirectory
+import Settings.Packages
+import Settings.User
+
+-- TODO: clean up after testing
+testRules :: Rules ()
+testRules =
+ "test" ~> do
+ let quote s = "\"" ++ s ++ "\""
+ yesNo x = quote $ if x then "YES" else "NO"
+ pkgs <- interpretWithStage Stage1 getPackages
+ tests <- filterM doesDirectoryExist $ concat
+ [ [ pkgPath pkg -/- "tests", pkgPath pkg -/- "tests-ghc" ]
+ | pkg <- pkgs, isLibrary pkg, pkg /= rts, pkg /= libffi ]
+ windows <- windowsHost
+ top <- topDirectory
+ compiler <- builderPath $ Ghc Stage2
+ ghcPkg <- builderPath $ GhcPkg Stage1
+ haddock <- builderPath Haddock
+ threads <- shakeThreads <$> getShakeOptions
+ ghcWithNativeCodeGenInt <- fromEnum <$> ghcWithNativeCodeGen
+ ghcWithInterpreterInt <- fromEnum <$> ghcWithInterpreter
+ ghcUnregisterisedInt <- fromEnum <$> flag GhcUnregisterised
+ quietly . cmd "python2" $
+ [ "testsuite/driver/runtests.py" ]
+ ++ map ("--rootdir="++) tests ++
+ [ "-e", "windows=" ++ show windows
+ , "-e", "config.speed=2"
+ , "-e", "ghc_compiler_always_flags=" ++ quote "-fforce-recomp -dcore-lint -dcmm-lint -dno-debug-output -no-user-package-db -rtsopts"
+ , "-e", "ghc_with_native_codegen=" ++ show ghcWithNativeCodeGenInt
+ , "-e", "ghc_debugged=" ++ yesNo ghcDebugged
+ , "-e", "ghc_with_vanilla=1" -- TODO: do we always build vanilla?
+ , "-e", "ghc_with_dynamic=0" -- TODO: support dynamic
+ , "-e", "ghc_with_profiling=0" -- TODO: support profiling
+ , "-e", "ghc_with_interpreter=" ++ show ghcWithInterpreterInt
+ , "-e", "ghc_unregisterised=" ++ show ghcUnregisterisedInt
+ , "-e", "ghc_with_threaded_rts=0" -- TODO: support threaded
+ , "-e", "ghc_with_dynamic_rts=0" -- TODO: support dynamic
+ , "-e", "ghc_dynamic_by_default=False" -- TODO: support dynamic
+ , "-e", "ghc_dynamic=0" -- TODO: support dynamic
+ , "-e", "ghc_with_llvm=0" -- TODO: support LLVM
+ , "-e", "in_tree_compiler=True" -- TODO: when is it equal to False?
+ , "-e", "clean_only=False" -- TODO: do we need to support True?
+ , "--configfile=testsuite/config/ghc"
+ , "--config", "compiler=" ++ quote (top -/- compiler)
+ , "--config", "ghc_pkg=" ++ quote (top -/- ghcPkg)
+ , "--config", "haddock=" ++ quote (top -/- haddock)
+ , "--summary-file", "testsuite_summary.txt"
+ , "--threads=" ++ show threads
+ ]
+
+ -- , "--config", "hp2ps=" ++ quote ("hp2ps")
+ -- , "--config", "hpc=" ++ quote ("hpc")
+ -- , "--config", "gs=$(call quote_path,$(GS))"
+ -- , "--config", "timeout_prog=$(call quote_path,$(TIMEOUT_PROGRAM))"
More information about the ghc-commits
mailing list