[commit: ghc] wip/nfs-locking: Clean up. (7ad0b09)
git at git.haskell.org
git at git.haskell.org
Thu Oct 26 23:06:16 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/7ad0b09ddbfd98ec8e026ef146add00e12c35e2f/ghc
>---------------------------------------------------------------
commit 7ad0b09ddbfd98ec8e026ef146add00e12c35e2f
Author: Andrey Mokhov <andrey.mokhov at ncl.ac.uk>
Date: Tue Jan 13 15:22:31 2015 +0000
Clean up.
>---------------------------------------------------------------
7ad0b09ddbfd98ec8e026ef146add00e12c35e2f
src/Base.hs | 2 ++
src/Oracles/Builder.hs | 12 ++++++++----
src/Oracles/Option.hs | 4 ++++
src/Package.hs | 6 +++---
src/Package/Compile.hs | 7 ++++---
src/Package/Dependencies.hs | 2 +-
src/Package/Library.hs | 3 ++-
7 files changed, 24 insertions(+), 12 deletions(-)
diff --git a/src/Base.hs b/src/Base.hs
index 169f556..e3f2256 100644
--- a/src/Base.hs
+++ b/src/Base.hs
@@ -27,6 +27,8 @@ data Stage = Stage0 | Stage1 | Stage2 | Stage3 deriving (Eq, Enum)
instance Show Stage where
show = show . fromEnum
+-- The returned list of strings is a list of arguments
+-- to be passed to a Builder
type Args = Action [String]
type Condition = Action Bool
diff --git a/src/Oracles/Builder.hs b/src/Oracles/Builder.hs
index 8a2c5b2..5c9d64b 100644
--- a/src/Oracles/Builder.hs
+++ b/src/Oracles/Builder.hs
@@ -11,6 +11,9 @@ import Oracles.Base
import Oracles.Flag
import Oracles.Option
+-- A Builder is an external command invoked in separate process
+-- by calling Shake.cmd
+--
-- Ghc Stage0 is the bootstrapping compiler
-- Ghc StageN, N > 0, is the one built on stage (N - 1)
-- GhcPkg Stage0 is the bootstrapping GhcPkg
@@ -96,7 +99,8 @@ run :: Builder -> Args -> Action ()
run builder args = do
needBuilder builder
[exe] <- showArgs builder
- cmd [exe] =<< args
+ args' <- args
+ cmd [exe] args'
-- Run the builder with a given collection of arguments printing out a
-- terse commentary with only 'interesting' info for the builder.
@@ -106,9 +110,9 @@ terseRun builder args = do
needBuilder builder
[exe] <- showArgs builder
args' <- args
- putNormal $ "--------\nRunning " ++ show builder ++ " with arguments:"
- mapM_ (putNormal . (" " ++)) $ interestingInfo builder args'
- putNormal "--------"
+ putNormal $ "|--------\n| Running " ++ show builder ++ " with arguments:"
+ mapM_ (putNormal . ("| " ++)) $ interestingInfo builder args'
+ putNormal "|--------"
quietly $ cmd [exe] args'
interestingInfo :: Builder -> [String] -> [String]
diff --git a/src/Oracles/Option.hs b/src/Oracles/Option.hs
index 89192a7..ee8fb66 100644
--- a/src/Oracles/Option.hs
+++ b/src/Oracles/Option.hs
@@ -8,6 +8,10 @@ import Base
import Oracles.Flag
import Oracles.Base
+-- For each Option the files {default.config, user.config} contain
+-- a line of the form 'target-os = mingw32'.
+-- (showArgs TargetOS) is an action that consults the config files
+-- and returns ["mingw32"].
-- TODO: separate single string options from multiple string ones.
data Option = TargetOS
| TargetArch
diff --git a/src/Package.hs b/src/Package.hs
index 217c05a..e815c4b 100644
--- a/src/Package.hs
+++ b/src/Package.hs
@@ -11,9 +11,9 @@ import Package.Dependencies
-- These are the packages we build:
packages :: [Package]
packages = [libraryPackage "array" Stage1 defaultSettings,
- libraryPackage "deepseq" Stage1 defaultSettings,
libraryPackage "bin-package-db" Stage1 defaultSettings,
- libraryPackage "binary" Stage1 defaultSettings]
+ libraryPackage "binary" Stage1 defaultSettings,
+ libraryPackage "deepseq" Stage1 defaultSettings]
-- Rule buildPackageX is defined in module Package.X
buildPackage :: Package -> TodoItem -> Rules ()
@@ -24,7 +24,7 @@ buildPackage = buildPackageData
packageRules :: Rules ()
packageRules = do
- -- TODO: control targets from commang line arguments
+ -- TODO: control targets from command line arguments
forM_ packages $ \pkg @ (Package name path todo) -> do
forM_ todo $ \todoItem @ (stage, dist, settings) -> do
diff --git a/src/Package/Compile.hs b/src/Package/Compile.hs
index 56d168a..d701af6 100644
--- a/src/Package/Compile.hs
+++ b/src/Package/Compile.hs
@@ -32,7 +32,7 @@ suffixArgs way = arg ["-hisuf", hisuf way]
oRule :: Package -> TodoItem -> Rules ()
oRule (Package name path _) (stage, dist, settings) =
let buildDir = toStandard $ path </> dist </> "build"
- pkgData = toStandard $ path </> dist </> "package-data.mk"
+ pkgData = path </> dist </> "package-data.mk"
depFile = buildDir </> name <.> "m"
in
(buildDir <//> "*o") %> \out -> do
@@ -49,6 +49,7 @@ oRule (Package name path _) (stage, dist, settings) =
<> packageArgs stage pkgData
<> includeArgs path dist
<> concatArgs ["-optP"] (CppOpts pkgData)
+ -- TODO: use HC_OPTS from pkgData
-- TODO: now we have both -O and -O2
<> arg ["-Wall", "-XHaskell2010", "-O2"]
<> productArgs ["-odir", "-hidir", "-stubdir"] buildDir
@@ -59,10 +60,10 @@ oRule (Package name path _) (stage, dist, settings) =
-- TODO: This rule looks hacky... combine it with the above?
hiRule :: Package -> TodoItem -> Rules ()
hiRule (Package name path _) (stage, dist, settings) =
- let buildDir = toStandard $ path </> dist </> "build"
+ let buildDir = path </> dist </> "build"
in
(buildDir <//> "*hi") %> \out -> do
- let way = detectWay $ tail $ takeExtension out
+ let way = detectWay $ tail $ takeExtension out
oFile = out -<.> osuf way
need [oFile]
diff --git a/src/Package/Dependencies.hs b/src/Package/Dependencies.hs
index fc9f4af..e428371 100644
--- a/src/Package/Dependencies.hs
+++ b/src/Package/Dependencies.hs
@@ -6,7 +6,7 @@ import Package.Base
buildPackageDependencies :: Package -> TodoItem -> Rules ()
buildPackageDependencies (Package name path _) (stage, dist, settings) =
let buildDir = toStandard $ path </> dist </> "build"
- pkgData = toStandard $ path </> dist </> "package-data.mk"
+ pkgData = path </> dist </> "package-data.mk"
in
(buildDir </> name <.> "m") %> \out -> do
need ["shake/src/Package/Dependencies.hs"]
diff --git a/src/Package/Library.hs b/src/Package/Library.hs
index ec2b845..043977a 100644
--- a/src/Package/Library.hs
+++ b/src/Package/Library.hs
@@ -7,7 +7,6 @@ import Data.List.Split
arRule :: Package -> TodoItem -> Rules ()
arRule (Package _ path _) (stage, dist, _) =
let buildDir = path </> dist </> "build"
- pkgData = path </> dist </> "package-data.mk"
in
(buildDir <//> "*a") %> \out -> do
let way = detectWay $ tail $ takeExtension out
@@ -16,6 +15,8 @@ arRule (Package _ path _) (stage, dist, _) =
need depObjs
libObjs <- pkgLibObjects path dist stage way
liftIO $ removeFiles "." [out]
+ -- Splitting argument list into chunks as otherwise Ar chokes up
+ -- TODO: use simpler list notation for passing arguments
forM_ (chunksOf 100 libObjs) $ \os -> do
terseRun Ar $ "q" <+> toStandard out <+> os
More information about the ghc-commits
mailing list