[commit: ghc] wip/nfs-locking: Add validate target. (a9f9876)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:15:48 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/nfs-locking
Link       : http://ghc.haskell.org/trac/ghc/changeset/a9f98769fbd07b93342cd263f6dcf3c6e51e4afd/ghc

>---------------------------------------------------------------

commit a9f98769fbd07b93342cd263f6dcf3c6e51e4afd
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Fri Jan 29 01:18:51 2016 +0000

    Add validate target.
    
    See #187.


>---------------------------------------------------------------

a9f98769fbd07b93342cd263f6dcf3c6e51e4afd
 src/Rules/Actions.hs | 16 ++++++++++++----
 src/Test.hs          |  6 +++++-
 2 files changed, 17 insertions(+), 5 deletions(-)

diff --git a/src/Rules/Actions.hs b/src/Rules/Actions.hs
index 0e4961f..d85e0dc 100644
--- a/src/Rules/Actions.hs
+++ b/src/Rules/Actions.hs
@@ -1,8 +1,8 @@
 {-# LANGUAGE RecordWildCards #-}
 module Rules.Actions (
     build, buildWithResources, copyFile, createDirectory, removeDirectory,
-    moveDirectory, fixFile, runConfigure, runMake, applyPatch, renderLibrary,
-    renderProgram, runBuilder, makeExecutable
+    moveDirectory, fixFile, runConfigure, runMake, runMakeVerbose, applyPatch,
+    renderLibrary, renderProgram, runBuilder, makeExecutable
     ) where
 
 import qualified System.Directory as IO
@@ -111,7 +111,13 @@ runConfigure dir opts args = do
         opts' = opts ++ [AddEnv "CONFIG_SHELL" "/bin/bash"]
 
 runMake :: FilePath -> [String] -> Action ()
-runMake dir args = do
+runMake = runMakeWithVerbosity False
+
+runMakeVerbose :: FilePath -> [String] -> Action ()
+runMakeVerbose = runMakeWithVerbosity True
+
+runMakeWithVerbosity :: Bool -> FilePath -> [String] -> Action ()
+runMakeWithVerbosity verbose dir args = do
     need [dir -/- "Makefile"]
     path <- builderPath Make
 
@@ -125,7 +131,9 @@ runMake dir args = do
 
     let note = if null args then "" else " (" ++ intercalate ", " args ++ ")"
     putBuild $ "| Run " ++ fixPath ++ note ++ " in " ++ dir ++ "..."
-    quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args
+    if verbose
+    then           cmd Shell                    fixPath ["-C", dir] args
+    else quietly $ cmd Shell (EchoStdout False) fixPath ["-C", dir] args
 
 applyPatch :: FilePath -> FilePath -> Action ()
 applyPatch dir patch = do
diff --git a/src/Test.hs b/src/Test.hs
index 547e286..06c82eb 100644
--- a/src/Test.hs
+++ b/src/Test.hs
@@ -7,12 +7,16 @@ import GHC (rts, libffi)
 import Oracles.Config.Flag
 import Oracles.Config.Setting
 import Oracles.WindowsRoot -- TODO: rename to Oracles.TopDirectory
+import Rules.Actions
 import Settings.Packages
 import Settings.User
 
 -- TODO: clean up after testing
 testRules :: Rules ()
-testRules =
+testRules = do
+    "validate" ~> do
+        runMakeVerbose "testsuite/tests" ["fast"]
+
     "test" ~> do
         let quote s = "\"" ++ s ++ "\""
             yesNo x = quote $ if x then "YES" else "NO"



More information about the ghc-commits mailing list