[commit: ghc] wip/andrey/cached-hadrian: Make sure autogen files have been generated before scanning sources. (5498f16)

git at git.haskell.org git at git.haskell.org
Sat Feb 9 18:22:48 UTC 2019


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

On branch  : wip/andrey/cached-hadrian
Link       : http://ghc.haskell.org/trac/ghc/changeset/5498f16ec5e7cae4c3000a73c7eddf7a85f7c77f/ghc

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

commit 5498f16ec5e7cae4c3000a73c7eddf7a85f7c77f
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Sat Feb 9 02:19:46 2019 +0000

    Make sure autogen files have been generated before scanning sources.
    
    Part of https://gitlab.haskell.org/ghc/ghc/merge_requests/317.


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

5498f16ec5e7cae4c3000a73c7eddf7a85f7c77f
 hadrian/src/Hadrian/Haskell/Cabal/Parse.hs |  9 ++++-----
 hadrian/src/Oracles/ModuleFiles.hs         |  1 +
 hadrian/src/Packages.hs                    | 12 +++++++++++-
 hadrian/src/Rules/Gmp.hs                   |  7 +------
 hadrian/src/Rules/Register.hs              |  5 +----
 5 files changed, 18 insertions(+), 16 deletions(-)

diff --git a/hadrian/src/Hadrian/Haskell/Cabal/Parse.hs b/hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
index fd1cd9c..7e78aa2 100644
--- a/hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
+++ b/hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
@@ -107,8 +107,7 @@ biModules pd = go [ comp | comp@(bi,_,_) <-
 -- the package the 'Context' points to.
 configurePackage :: Context -> Action ()
 configurePackage context at Context {..} = do
-    putLoud $ "| Configure package " ++ quote (pkgName package)
-
+    putProgressInfo $ "| Configure package " ++ quote (pkgName package)
     gpd     <- pkgGenericDescription package
     depPkgs <- packageDependencies <$> readPackageData package
 
@@ -155,7 +154,7 @@ configurePackage context at Context {..} = do
 -- corresponding to the 'Stage' of the 'Context'.
 copyPackage :: Context -> Action ()
 copyPackage context at Context {..} = do
-    putLoud $ "| Copy package " ++ quote (pkgName package)
+    putProgressInfo $ "| Copy package " ++ quote (pkgName package)
     gpd <- pkgGenericDescription package
     ctxPath   <- Context.contextPath context
     pkgDbPath <- packageDbPath stage
@@ -167,7 +166,7 @@ copyPackage context at Context {..} = do
 -- | Register the 'Package' of a given 'Context' into the package database.
 registerPackage :: Context -> Action ()
 registerPackage context at Context {..} = do
-    putLoud $ "| Register package " ++ quote (pkgName package)
+    putProgressInfo $ "| Register package " ++ quote (pkgName package)
     ctxPath <- Context.contextPath context
     gpd <- pkgGenericDescription package
     verbosity <- getVerbosity
@@ -289,7 +288,7 @@ buildAutogenFiles :: Context -> Action ()
 buildAutogenFiles context = do
     cPath <- Context.contextPath context
     setupConfig <- pkgSetupConfigFile context
-    need [setupConfig]
+    need [setupConfig] -- This triggers 'configurePackage'
     pd <- packageDescription <$> readContextData context
     -- Note: the @cPath@ is ignored. The path that's used is the 'buildDir' path
     -- from the local build info @lbi at .
diff --git a/hadrian/src/Oracles/ModuleFiles.hs b/hadrian/src/Oracles/ModuleFiles.hs
index 0ec1573..d2f0299 100644
--- a/hadrian/src/Oracles/ModuleFiles.hs
+++ b/hadrian/src/Oracles/ModuleFiles.hs
@@ -131,6 +131,7 @@ moduleFilesOracle :: Rules ()
 moduleFilesOracle = void $ do
     void . addOracleCache $ \(ModuleFiles (stage, package)) -> do
         let context = vanillaContext stage package
+        ensureConfigured context
         srcDirs <- interpretInContext context (getContextData PD.srcDirs)
         mainIs  <- interpretInContext context (getContextData PD.mainIs)
         let removeMain = case mainIs of
diff --git a/hadrian/src/Packages.hs b/hadrian/src/Packages.hs
index 9a70420..6104148 100644
--- a/hadrian/src/Packages.hs
+++ b/hadrian/src/Packages.hs
@@ -13,7 +13,7 @@ module Packages (
     -- * Package information
     programName, nonHsMainPackage, autogenPath, programPath, timeoutPath,
     rtsContext, rtsBuildPath, libffiContext, libffiBuildPath, libffiLibraryName,
-    generatedGhcDependencies
+    generatedGhcDependencies, ensureConfigured
     ) where
 
 import Hadrian.Package
@@ -184,6 +184,16 @@ autogenPath context at Context {..}
   where
     autogen dir = contextPath context <&> (-/- dir -/- "autogen")
 
+-- | Make sure a given context has already been fully configured. The
+-- implementation simply calls 'need' on the context's @autogen/cabal_macros.h@
+-- file, which triggers 'configurePackage' and 'buildAutogenFiles'. Why this
+-- indirection? Going via @autogen/cabal_macros.h@ allows us to cache the
+-- configuration steps, i.e. not to repeat them if they have already been done.
+ensureConfigured :: Context -> Action ()
+ensureConfigured context = do
+    autogen <- autogenPath context
+    need [autogen -/- "cabal_macros.h"]
+
 -- | RTS is considered a Stage1 package. This determines RTS build directory.
 rtsContext :: Stage -> Context
 rtsContext stage = vanillaContext stage rts
diff --git a/hadrian/src/Rules/Gmp.hs b/hadrian/src/Rules/Gmp.hs
index 9b56a3e..a78170c 100644
--- a/hadrian/src/Rules/Gmp.hs
+++ b/hadrian/src/Rules/Gmp.hs
@@ -92,12 +92,7 @@ gmpRules = do
         copyFile (gmpPath -/- gmpLibraryH)
 
     -- This file is created when 'integerGmp' is configured.
-    gmpPath -/- "config.mk" %> \_ -> do
-        -- Calling 'need' on @setup-config@ triggers 'configurePackage'. Why
-        -- this indirection? Going via @setup-config@ allows us to cache the
-        -- configuration step, i.e. not to repeat it if it's already been done.
-        setupConfig <- pkgSetupConfigFile gmpContext
-        need [setupConfig]
+    gmpPath -/- "config.mk" %> \_ -> ensureConfigured gmpContext
 
     -- Run GMP's configure script
     gmpPath -/- "Makefile" %> \mk -> do
diff --git a/hadrian/src/Rules/Register.hs b/hadrian/src/Rules/Register.hs
index 625fca8..d215938 100644
--- a/hadrian/src/Rules/Register.hs
+++ b/hadrian/src/Rules/Register.hs
@@ -92,10 +92,7 @@ registerPackageRules rs stage = do
 buildConf :: [(Resource, Int)] -> Context -> FilePath -> Action ()
 buildConf _ context at Context {..} conf = do
     depPkgIds <- cabalDependencies context
-
-    -- Calling 'need' on @setupConfig@, triggers the package configuration.
-    setupConfig <- pkgSetupConfigFile context
-    need [setupConfig]
+    ensureConfigured context
     need =<< mapM (\pkgId -> packageDbPath stage <&> (-/- pkgId <.> "conf")) depPkgIds
 
     ways <- interpretInContext context (getLibraryWays <> if package == rts then getRtsWays else mempty)



More information about the ghc-commits mailing list