[commit: ghc] wip/nfs-locking: Add Stage1Only rule (#340) (b245f0e)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:33:42 UTC 2017


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

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

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

commit b245f0e8ce176399dd87de283c7ad77125033bf5
Author: Zhen Zhang <izgzhen at gmail.com>
Date:   Thu Jul 6 14:11:00 2017 +0800

    Add Stage1Only rule (#340)


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

b245f0e8ce176399dd87de283c7ad77125033bf5
 src/Oracles/Dependencies.hs |  2 +-
 src/Rules.hs                | 36 ++++++++++++++++++++++++++++--------
 src/Rules/Install.hs        |  2 +-
 src/Settings.hs             | 12 +++++++++++-
 src/UserSettings.hs         | 21 ++++++++++++++++++---
 5 files changed, 59 insertions(+), 14 deletions(-)

diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs
index 167047d..2775b3e 100644
--- a/src/Oracles/Dependencies.hs
+++ b/src/Oracles/Dependencies.hs
@@ -63,7 +63,7 @@ needContext cs = do
         lib0     <- buildDll0          context
         ghciLib  <- pkgGhciLibraryFile context
         ghciFlag <- interpretInContext context $ getPkgData BuildGhciLib
-        let ghci = ghciFlag == "YES" && stage context == Stage1
+        let ghci = ghciFlag == "YES" && (stage context == Stage1 || stage1Only)
         return $ [ libFile ] ++ [ lib0File | lib0 ] ++ [ ghciLib | ghci ]
     confs <- mapM pkgConfFile cs
     need $ libs ++ confs
diff --git a/src/Rules.hs b/src/Rules.hs
index e5835c0..3ba6ba7 100644
--- a/src/Rules.hs
+++ b/src/Rules.hs
@@ -1,4 +1,4 @@
-module Rules (topLevelTargets, buildLib, buildRules) where
+module Rules (topLevelTargets, buildPackage, buildRules) where
 
 import Base
 import Context
@@ -18,22 +18,35 @@ import qualified Rules.Library
 import qualified Rules.Perl
 import qualified Rules.Program
 import qualified Rules.Register
+import Oracles.Dependencies (needContext)
+import Util (needBuilder)
 import Settings
 import Settings.Path
 
 allStages :: [Stage]
 allStages = [minBound ..]
 
--- | This rule 'need' all top-level build targets.
+-- | This rule 'need' all top-level build targets
+-- or Stage1Only targets
 topLevelTargets :: Rules ()
-topLevelTargets = do
-    want $ Rules.Generate.inplaceLibCopyTargets
+topLevelTargets = action $ do
+    need $ Rules.Generate.inplaceLibCopyTargets
 
-    forM_ allStages $ \stage ->
-        forM_ (knownPackages \\ [rts, libffi]) $ \pkg -> action (buildLib stage pkg)
+    if stage1Only
+        then do
+             forAllPkgs $ \stg pkg ->
+                 when (isLibrary pkg) $
+                     buildPackage stg pkg
+             forM_ programsStage1Only $ buildPackage Stage0
+        else
+             forAllPkgs buildPackage
+  where
+    forAllPkgs f =
+      forM_ allStages $ \stage ->
+          forM_ (knownPackages \\ [rts, libffi]) $ \pkg -> f stage pkg
 
-buildLib :: Stage -> Package -> Action ()
-buildLib stage pkg = do
+buildPackage :: Stage -> Package -> Action ()
+buildPackage stage pkg = do
     let context = vanillaContext stage pkg
     activePackages <- interpretInContext context getPackages
     when (pkg `elem` activePackages) $
@@ -44,6 +57,7 @@ buildLib stage pkg = do
             ways <- interpretInContext context getLibraryWays
             libs <- mapM (pkgLibraryFile . Context stage pkg) ways
             docs <- interpretInContext context $ buildHaddock flavour
+            needContext [context]
             need $ libs ++ [ pkgHaddockFile context | docs && stage == Stage1 ]
         else -- otherwise build a program
             need =<< maybeToList <$> programPath (programContext stage pkg)
@@ -90,3 +104,9 @@ buildRules = do
     Rules.Libffi.libffiRules
     packageRules
     Rules.Perl.perlScriptRules
+
+programsStage1Only :: [Package]
+programsStage1Only =
+  [ deriveConstants, genprimopcode, hp2ps, runGhc
+  , ghcCabal, hpc, dllSplit, ghcPkg, hsc2hs
+  , genapply, ghc ]
diff --git a/src/Rules/Install.hs b/src/Rules/Install.hs
index e7c6d41..0492a62 100644
--- a/src/Rules/Install.hs
+++ b/src/Rules/Install.hs
@@ -191,7 +191,7 @@ installPackages = do
                 let context = vanillaContext stg pkg
                 top <- interpretInContext context getTopDirectory
                 let installDistDir = top -/- buildPath context
-                buildLib stg pkg
+                buildPackage stg pkg
                 docDir <- installDocDir
                 ghclibDir <- installGhcLibDir
                 version <- interpretInContext context (getPkgData Version)
diff --git a/src/Settings.hs b/src/Settings.hs
index d09fa31..8152a6e 100644
--- a/src/Settings.hs
+++ b/src/Settings.hs
@@ -3,7 +3,7 @@ module Settings (
     findKnownPackage, getPkgData, getPkgDataList, isLibrary, getPackagePath,
     getContextDirectory, getBuildPath, stagePackages, builderPath,
     getBuilderPath, isSpecified, latestBuildStage, programPath, programContext,
-    integerLibraryName, destDir, pkgConfInstallPath
+    integerLibraryName, destDir, pkgConfInstallPath, stage1Only
     ) where
 
 import Base
@@ -117,3 +117,13 @@ programPath context at Context {..} = do
 
 pkgConfInstallPath :: FilePath
 pkgConfInstallPath = buildPath (vanillaContext Stage0 rts) -/- "package.conf.install"
+
+-- | Stage1Only flag
+-- TODO: Set this by cmdline flags
+stage1Only :: Bool
+stage1Only = defaultStage1Only
+
+-- | Install's DESTDIR flag
+-- TODO: Set this by cmdline flags
+destDir :: FilePath
+destDir = defaultDestDir
diff --git a/src/UserSettings.hs b/src/UserSettings.hs
index 96e6f4b..4398700 100644
--- a/src/UserSettings.hs
+++ b/src/UserSettings.hs
@@ -4,7 +4,7 @@
 -- accidentally commit them.
 module UserSettings (
     buildRootPath, userFlavours, userKnownPackages, verboseCommands,
-    putBuild, putSuccess, destDir
+    putBuild, putSuccess, defaultDestDir, defaultStage1Only
     ) where
 
 import System.Console.ANSI
@@ -47,5 +47,20 @@ putSuccess = putColoured Dull Green
 -- It is by default empty, representing the root of file system,
 -- or it might be a directory.
 -- It is usually used with @prefix@, like @/usr/local@
-destDir :: FilePath
-destDir = ""
+defaultDestDir :: FilePath
+defaultDestDir = ""
+
+{-
+  Stage1Only=YES means:
+   - don't build ghc-stage2 (the executable)
+   - don't build utils that rely on ghc-stage2
+     See Note [No stage2 packages when CrossCompiling or Stage1Only] in
+     ./ghc.mk.
+   - install ghc-stage1 instead of ghc-stage2
+   - install the ghc-pkg that was built with the stage0 compiler
+   - (*do* still build compiler/stage2 (i.e. the ghc library))
+   - (*do* still build all other libraries)
+-}
+-- | Stage1Only flag, default off
+defaultStage1Only :: Bool
+defaultStage1Only = False



More information about the ghc-commits mailing list