[commit: ghc] wip/nfs-locking: Include PR Comments (423c5dd)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 00:04:14 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/423c5dd10b51f3251d59fec64c68b7bc07019dbf/ghc
>---------------------------------------------------------------
commit 423c5dd10b51f3251d59fec64c68b7bc07019dbf
Author: Moritz Angermann <moritz.angermann at gmail.com>
Date: Sat Jan 9 21:44:23 2016 +0800
Include PR Comments
>---------------------------------------------------------------
423c5dd10b51f3251d59fec64c68b7bc07019dbf
shaking-up-ghc.cabal | 1 +
src/GHC.hs | 5 +----
src/Main.hs | 3 ++-
src/Rules/Generate.hs | 33 ++++-----------------------------
src/Rules/Generators/GhcSplit.hs | 2 +-
src/Rules/Perl.hs | 25 +++++++++++++++++++++++++
6 files changed, 34 insertions(+), 35 deletions(-)
diff --git a/shaking-up-ghc.cabal b/shaking-up-ghc.cabal
index bd6e31f..a5b4c57 100644
--- a/shaking-up-ghc.cabal
+++ b/shaking-up-ghc.cabal
@@ -55,6 +55,7 @@ executable ghc-shake
, Rules.Library
, Rules.Oracles
, Rules.Package
+ , Rules.Perl
, Rules.Program
, Rules.Resources
, Rules.Wrappers.Ghc
diff --git a/src/GHC.hs b/src/GHC.hs
index c26f552..3b58bbe 100644
--- a/src/GHC.hs
+++ b/src/GHC.hs
@@ -113,12 +113,9 @@ defaultProgramPath stage pkg
| pkg == haddock || pkg == ghcTags = case stage of
Stage2 -> Just . inplaceProgram $ pkgNameString pkg
_ -> Nothing
- | pkg == touchy = case stage of
+ | pkg `elem` [touchy, unlit] = case stage of
Stage0 -> Just $ "inplace/lib/bin" -/- pkgNameString pkg <.> exe
_ -> Nothing
- | pkg == unlit = case stage of
- Stage0 -> Just $ "inplace/lib" -/- pkgNameString pkg <.> exe
- _ -> Nothing
| isProgram pkg = case stage of
Stage0 -> Just . inplaceProgram $ pkgNameString pkg
_ -> Just . installProgram $ pkgNameString pkg
diff --git a/src/Main.hs b/src/Main.hs
index a56f9ed..9f223a8 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -10,6 +10,7 @@ import qualified Rules.Generate
import qualified Rules.IntegerGmp
import qualified Rules.Libffi
import qualified Rules.Oracles
+import qualified Rules.Perl
main :: IO ()
main = shakeArgs options rules
@@ -19,7 +20,7 @@ main = shakeArgs options rules
, Rules.Config.configRules
, Rules.Generate.copyRules
, Rules.Generate.generateRules
- , Rules.Generate.generateScripts
+ , Rules.Perl.perlScriptRules
, Rules.generateTargets
, Rules.IntegerGmp.integerGmpRules
, Rules.Libffi.libffiRules
diff --git a/src/Rules/Generate.hs b/src/Rules/Generate.hs
index 3b6dfdc..2b2962b 100644
--- a/src/Rules/Generate.hs
+++ b/src/Rules/Generate.hs
@@ -1,6 +1,6 @@
module Rules.Generate (
- generatePackageCode, generateRules, generateScripts,
- derivedConstantsPath, generatedDependencies,
+ generate, generateExec, generatePackageCode, generateRules,
+ derivedConstantsPath, emptyTarget, generatedDependencies,
installTargets, copyRules
) where
@@ -11,7 +11,6 @@ import Rules.Generators.ConfigHs
import Rules.Generators.GhcAutoconfH
import Rules.Generators.GhcBootPlatformH
import Rules.Generators.GhcPlatformH
-import Rules.Generators.GhcSplit
import Rules.Generators.GhcVersionH
import Rules.Generators.VersionHs
import Oracles.ModuleFiles
@@ -78,10 +77,11 @@ compilerDependencies stage =
, "primop-vector-tys-exports.hs-incl"
, "primop-vector-tycons.hs-incl"
, "primop-vector-tys.hs-incl" ]
+ ++ ["inplace/lib/bin/ghc-split"]
generatedDependencies :: Stage -> Package -> [FilePath]
generatedDependencies stage pkg
- | pkg == compiler = compilerDependencies stage ++ ["inplace/lib/bin/ghc-split"]
+ | pkg == compiler = compilerDependencies stage
| pkg == ghcPrim = ghcPrimDependencies stage
| pkg == rts = includesDependencies ++ derivedConstantsDependencies
| stage == Stage0 = defaultDependencies
@@ -185,31 +185,6 @@ generateRules = do
where
file <~ gen = file %> \out -> generate out emptyTarget gen
--- | Generate scripts the build system requires. For now we generate the
--- @ghc-split@ script from it's literate perl source.
-generateScripts :: Rules ()
-generateScripts = do
- -- how to translate literate perl to perl.
- -- this is a hack :-/
- "//*.prl" %> \out -> do
- let src = out -<.> "lprl"
- path <- builderPath Unlit
- need [path]
- unit $ cmd [path] [src] [out]
-
- -- ghc-split is only a perl script.
- let ghcSplit = "inplace/lib/ghc-split" -- See system.config
- let ghcSplitBin = "inplace/lib/bin/ghc-split" -- See ConfigHs.hs
-
- ghcSplit <~ generateGhcSplit
-
- ghcSplitBin %> \out -> do
- need [ghcSplit]
- copyFileChanged ghcSplit out
-
- where
- file <~ gen = file %> \out -> generateExec out emptyTarget gen
-
-- TODO: Use the Types, Luke! (drop partial function)
-- We sometimes need to evaluate expressions that do not require knowing all
-- information about the target. In this case, we don't want to know anything.
diff --git a/src/Rules/Generators/GhcSplit.hs b/src/Rules/Generators/GhcSplit.hs
index 77cd49f..a2bd8b2 100644
--- a/src/Rules/Generators/GhcSplit.hs
+++ b/src/Rules/Generators/GhcSplit.hs
@@ -9,7 +9,7 @@ generateGhcSplit :: Expr String
generateGhcSplit = do
let yesNo = lift . fmap (\x -> if x then "YES" else "NO")
perl <- getBuilderPath Perl
- let script = "driver" -/- "split" -/- "ghc-split.prl"
+ let script = "driver/split/ghc-split.prl"
when trackBuildSystem . lift $
need [sourcePath -/- "Rules" -/- "Generators" -/- "GhcSplit.hs"]
lift $ need [script]
diff --git a/src/Rules/Perl.hs b/src/Rules/Perl.hs
new file mode 100644
index 0000000..c1e5ba8
--- /dev/null
+++ b/src/Rules/Perl.hs
@@ -0,0 +1,25 @@
+module Rules.Perl (perlScriptRules) where
+
+import Base
+import Expression
+import Rules.Actions (runBuilder)
+import Rules.Generate (generateExec, emptyTarget)
+import Rules.Generators.GhcSplit (generateGhcSplit)
+
+-- | Generate scripts the build system requires. For now we generate the
+-- @ghc-split@ script from it's literate perl source.
+perlScriptRules :: Rules ()
+perlScriptRules = do
+ -- how to translate literate perl to perl.
+ -- this is a hack :-/
+ "//*.prl" %> \out -> do
+ let src = out -<.> "lprl"
+ runBuilder Unlit [src, out]
+
+ -- ghc-split is only a perl script.
+ let ghcSplit = "inplace/lib/bin/ghc-split"
+
+ ghcSplit <~ generateGhcSplit
+
+ where
+ file <~ gen = file %> \out -> generateExec out emptyTarget gen
More information about the ghc-commits
mailing list