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

Commit

Permalink
Add validate target.
Browse files Browse the repository at this point in the history
See #187.
  • Loading branch information
snowleopard committed Jan 29, 2016
1 parent 0c06eac commit a9f9876
Show file tree
Hide file tree
Showing 2 changed files with 17 additions and 5 deletions.
16 changes: 12 additions & 4 deletions src/Rules/Actions.hs
Original file line number Diff line number Diff line change
@@ -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
Expand Down Expand Up @@ -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

Expand All @@ -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
Expand Down
6 changes: 5 additions & 1 deletion src/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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"
Expand Down

0 comments on commit a9f9876

Please sign in to comment.