Skip to content

Commit

Permalink
Preliminary nofib rule (snowleopard#599)
Browse files Browse the repository at this point in the history
* first draft of a nofib rule

* address some of Andrey's feedback

* refactor nofib into a proper Builder, now runs but one of the programs fails

* more subtle error handling, docs

* get rid of RunNofib builder, invoke commands directly
  • Loading branch information
alpmestan authored and chitrak7 committed May 18, 2018
1 parent 48e72f1 commit 9303ace
Show file tree
Hide file tree
Showing 4 changed files with 71 additions and 1 deletion.
1 change: 1 addition & 0 deletions hadrian.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,7 @@ executable hadrian
, Rules.Gmp
, Rules.Libffi
, Rules.Library
, Rules.Nofib
, Rules.Program
, Rules.Register
, Rules.Selftest
Expand Down
2 changes: 2 additions & 0 deletions src/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ import qualified Environment
import qualified Rules
import qualified Rules.Clean
import qualified Rules.Documentation
import qualified Rules.Nofib
import qualified Rules.SourceDist
import qualified Rules.Selftest
import qualified Rules.Test
Expand Down Expand Up @@ -43,6 +44,7 @@ main = do
Rules.buildRules
Rules.Documentation.documentationRules
Rules.Clean.cleanRules
Rules.Nofib.nofibRules
Rules.oracleRules
Rules.Selftest.selftestRules
Rules.SourceDist.sourceDistRules
Expand Down
58 changes: 58 additions & 0 deletions src/Rules/Nofib.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,58 @@
module Rules.Nofib where

import Base
import Expression
import GHC
import Oracles.Setting
import Target

import System.Environment
import System.Exit

nofibRules :: Rules ()
nofibRules = do
root <- buildRootRules

-- a phony "nofib" rule that just triggers
-- the rule below.
"nofib" ~> need [root -/- nofibLogFile]

-- a rule to produce <build root>/nofig-log
-- by running the nofib suite and capturing
-- the relevant output.
root -/- nofibLogFile %> \fp -> do
needNofibDeps

makePath <- builderPath (Make "nofib")
top <- topDirectory
ghcPath <- builderPath (Ghc CompileHs Stage2)
perlPath <- builderPath Perl

-- some makefiles in nofib rely on a $MAKE
-- env var being defined
liftIO (setEnv "MAKE" makePath)

-- this runs make commands in the nofib
-- subdirectory, passing the path to
-- the GHC to benchmark and perl to
-- nofib's makefiles.
let nofibArgs = ["WithNofibHc=" ++ (top -/- ghcPath), "PERL=" ++ perlPath]
unit $ cmd (Cwd "nofib") [makePath] ["clean"]
unit $ cmd (Cwd "nofib") [makePath] (nofibArgs ++ ["boot"])
(Exit e, Stdouterr log) <- cmd (Cwd "nofib") [makePath] nofibArgs
writeFile' fp log
if e == ExitSuccess
then putLoud $ "nofib log available at " ++ fp
else error $ "nofib failed, full log available at " ++ fp

nofibLogFile :: FilePath
nofibLogFile = "nofib-log"


-- the dependencies that nofib seems to require.
needNofibDeps :: Action ()
needNofibDeps = do
unlitPath <- programPath (Context Stage1 unlit vanilla)
mtlPath <- pkgConfFile (Context Stage1 mtl vanilla)
need [ unlitPath, mtlPath ]
needBuilder (Ghc CompileHs Stage2)
11 changes: 10 additions & 1 deletion src/Settings/Builders/Make.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ module Settings.Builders.Make (makeBuilderArgs) where

import GHC
import Oracles.Setting
import Builder
import Rules.Gmp
import Rules.Libffi
import Settings.Builders.Common
Expand All @@ -12,12 +13,20 @@ makeBuilderArgs = do
threads <- shakeThreads <$> expr getShakeOptions
gmpPath <- expr gmpBuildPath
libffiPath <- expr libffiBuildPath
ghcPath <- expr $
(-/-) <$> topDirectory <*> builderPath (Ghc CompileHs Stage2)
perlPath <- expr $ builderPath Perl
let t = show $ max 4 (threads - 2) -- Don't use all Shake's threads
testsuiteFlags <- expr makeTestsuiteFlags
mconcat
[ builder (Make gmpPath ) ? pure ["MAKEFLAGS=-j" ++ t]
, builder (Make libffiPath ) ? pure ["MAKEFLAGS=-j" ++ t, "install"]
, builder (Make "testsuite/tests") ? pure (["THREADS=" ++ t, "fast"] ++ testsuiteFlags) ]
, builder (Make "testsuite/tests") ? pure (["THREADS=" ++ t, "fast"] ++ testsuiteFlags)
, builder (Make "nofib" ) ? pure
[ "WithNofibHc=" ++ ghcPath
, "PERL=" ++ perlPath
]
]

makeTestsuiteFlags :: Action [String]
makeTestsuiteFlags = do
Expand Down

0 comments on commit 9303ace

Please sign in to comment.