[commit: ghc] wip/nfs-locking: Build program executables directly in inplace/bin. (663ad01)

git at git.haskell.org git at git.haskell.org
Thu Oct 26 23:27:03 UTC 2017


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

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

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

commit 663ad019699389006a2c99e9f17c92bd53ea4e22
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Mon Dec 21 02:56:49 2015 +0000

    Build program executables directly in inplace/bin.


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

663ad019699389006a2c99e9f17c92bd53ea4e22
 cfg/system.config.in              | 20 ++++++++++----------
 src/Base.hs                       |  7 ++++++-
 src/Builder.hs                    |  1 +
 src/GHC.hs                        | 30 ++++++++++++------------------
 src/Rules.hs                      |  5 +++--
 src/Settings/Builders/GhcCabal.hs |  3 ++-
 6 files changed, 34 insertions(+), 32 deletions(-)

diff --git a/cfg/system.config.in b/cfg/system.config.in
index 9de3166..6c21f6e 100644
--- a/cfg/system.config.in
+++ b/cfg/system.config.in
@@ -5,29 +5,29 @@
 #===================
 
 system-ghc     = @WithGhc@
-ghc-stage1     = @hardtop@/inplace/bin/ghc-stage1
-ghc-stage2     = @hardtop@/inplace/bin/ghc-stage2
-ghc-stage3     = @hardtop@/inplace/bin/ghc-stage3
+ghc-stage1     = inplace/bin/ghc-stage1
+ghc-stage2     = inplace/bin/ghc-stage2
+ghc-stage3     = inplace/bin/ghc-stage3
 
 system-gcc     = @CC_STAGE0@
 gcc            = @WhatGccIsCalled@
 
 system-ghc-pkg = @GhcPkgCmd@
-ghc-pkg        = @hardtop@/inplace/bin/ghc-pkg
+ghc-pkg        = inplace/bin/ghc-pkg
 
-ghc-cabal      = @hardtop@/inplace/bin/ghc-cabal
+ghc-cabal      = inplace/bin/ghc-cabal
 
-haddock        = @hardtop@/inplace/bin/haddock
+haddock        = inplace/bin/haddock
 
-hsc2hs         = @hardtop@/inplace/bin/hsc2hs
+hsc2hs         = inplace/bin/hsc2hs
 
-genprimopcode  = @hardtop@/inplace/bin/genprimopcode
+genprimopcode  = inplace/bin/genprimopcode
 
 hs-cpp         = @HaskellCPPCmd@
 hs-cpp-args    = @HaskellCPPArgs@
 
-unlit          = @hardtop@/inplace/lib/unlit
-ghc-split      = @hardtop@/inplace/lib/ghc-split
+unlit          = inplace/lib/unlit
+ghc-split      = inplace/lib/ghc-split
 
 ld             = @LdCmd@
 ar             = @ArCmd@
diff --git a/src/Base.hs b/src/Base.hs
index 009e197..834f589 100644
--- a/src/Base.hs
+++ b/src/Base.hs
@@ -17,7 +17,8 @@ module Base (
     module Development.Shake.Util,
 
     -- * Paths
-    shakeFilesPath, configPath, bootPackageConstraints, packageDependencies,
+    shakeFilesPath, configPath, programInplacePath,
+    bootPackageConstraints, packageDependencies,
 
     -- * Output
     putColoured, putOracle, putBuild, putSuccess, putError, renderBox,
@@ -56,6 +57,10 @@ shakeFilesPath = shakePath -/- ".db"
 configPath :: FilePath
 configPath = shakePath -/- "cfg"
 
+-- TODO: shall we read this from system.config instead?
+programInplacePath :: FilePath
+programInplacePath = "inplace/bin"
+
 bootPackageConstraints :: FilePath
 bootPackageConstraints = shakeFilesPath -/- "boot-package-constraints"
 
diff --git a/src/Builder.hs b/src/Builder.hs
index f15054d..4d41d0a 100644
--- a/src/Builder.hs
+++ b/src/Builder.hs
@@ -66,6 +66,7 @@ builderKey builder = case builder of
     Ld               -> "ld"
     Unlit            -> "unlit"
 
+-- TODO: Paths to some builders should be determined using defaultProgramPath
 builderPath :: Builder -> Action FilePath
 builderPath builder = do
     path <- askConfigWithDefault (builderKey builder) $
diff --git a/src/GHC.hs b/src/GHC.hs
index 923fdf1..f47242a 100644
--- a/src/GHC.hs
+++ b/src/GHC.hs
@@ -105,25 +105,19 @@ defaultTargetDirectory stage pkg
     | stage == Stage0   = "dist-boot"
     | otherwise         = "dist-install"
 
+-- TODO: simplify
+-- | Returns a relative path to the program executable
 defaultProgramPath :: Stage -> Package -> Maybe FilePath
 defaultProgramPath stage pkg
-    | pkg == compareSizes    = program $ pkgName pkg
-    | pkg == deriveConstants = program $ pkgName pkg
-    | pkg == dllSplit        = program $ pkgName pkg
-    | pkg == genapply        = program $ pkgName pkg
-    | pkg == genprimopcode   = program $ pkgName pkg
-    | pkg == ghc             = program $ "ghc-stage" ++ show (fromEnum stage + 1)
-    | pkg == ghcCabal        = program $ pkgName pkg
-    | pkg == ghcPkg          = program $ pkgName pkg
-    | pkg == ghcPwd          = program $ pkgName pkg
-    | pkg == ghcTags         = program $ pkgName pkg
-    | pkg == haddock         = program $ pkgName pkg
-    | pkg == hsc2hs          = program $ pkgName pkg
-    | pkg == hp2ps           = program $ pkgName pkg
-    | pkg == hpcBin          = program $ pkgName pkg
-    | pkg == mkUserGuidePart = program $ pkgName pkg
-    | pkg == runghc          = program $ pkgName pkg
-    | otherwise              = Nothing
+    | pkg == ghc     = Just . inplaceProgram $ "ghc-stage" ++ show (fromEnum stage + 1)
+    | pkg == haddock = case stage of
+        Stage2 -> Just . inplaceProgram $ pkgName pkg
+        _      -> Nothing
+    | isProgram pkg  = case stage of
+        Stage0 -> Just . inplaceProgram $ pkgName pkg
+        _      -> Just . installProgram $ pkgName pkg
+    | otherwise = Nothing
   where
-    program name = Just $ pkgPath pkg -/- defaultTargetDirectory stage pkg
+    inplaceProgram name = programInplacePath -/- name <.> exe
+    installProgram name = pkgPath pkg -/- defaultTargetDirectory stage pkg
                                       -/- "build/tmp" -/- name <.> exe
diff --git a/src/Rules.hs b/src/Rules.hs
index 55ff066..7d88de8 100644
--- a/src/Rules.hs
+++ b/src/Rules.hs
@@ -5,7 +5,8 @@ import Rules.Package
 import Rules.Resources
 import Settings
 
--- generateTargets needs top-level build targets
+-- TODO: not all program targets should be needed explicitly
+-- | generateTargets needs top-level build targets
 generateTargets :: Rules ()
 generateTargets = action $ do
     targets <- fmap concat . forM [Stage0 ..] $ \stage -> do
@@ -17,7 +18,7 @@ generateTargets = action $ do
             return [ pkgHaddockFile pkg | needHaddock && stage == Stage1 ]
         let programTargets = [ prog | Just prog <- programPath stage <$> pkgs ]
         return $ libTargets ++ programTargets
-    need $ reverse targets
+    need targets
 
 -- TODO: use stage 2 compiler for building stage 2 packages (instead of stage 1)
 packageRules :: Rules ()
diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs
index 151cd5f..66f9239 100644
--- a/src/Settings/Builders/GhcCabal.hs
+++ b/src/Settings/Builders/GhcCabal.hs
@@ -184,9 +184,10 @@ withBuilderKey b = case b of
 -- Expression 'with Gcc' appends "--with-gcc=/path/to/gcc" and needs Gcc.
 with :: Builder -> Args
 with b = specified b ? do
+    top  <- getSetting GhcSourcePath
     path <- getBuilderPath b
     lift $ needBuilder laxDependencies b
-    append [withBuilderKey b ++ path]
+    append [withBuilderKey b ++ top -/- path]
 
 withStaged :: (Stage -> Builder) -> Args
 withStaged sb = (with . sb) =<< getStage



More information about the ghc-commits mailing list