[Git][ghc/ghc][wip/inplace-final] comments

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Mon Aug 22 15:51:01 UTC 2022



Matthew Pickering pushed to branch wip/inplace-final at Glasgow Haskell Compiler / GHC


Commits:
064c07eb by Matthew Pickering at 2022-08-22T16:50:52+01:00
comments

- - - - -


9 changed files:

- hadrian/src/Base.hs
- hadrian/src/Builder.hs
- hadrian/src/Context.hs
- hadrian/src/Context/Type.hs
- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
- hadrian/src/Rules/Library.hs
- hadrian/src/Rules/Register.hs
- hadrian/src/Settings/Builders/Ghc.hs
- hadrian/src/Stage.hs


Changes:

=====================================
hadrian/src/Base.hs
=====================================
@@ -88,7 +88,7 @@ relativePackageDbPath :: PackageDbLoc -> FilePath
 relativePackageDbPath (PackageDbLoc stage Final) = stageString stage-/- "lib/package.conf.d"
 relativePackageDbPath (PackageDbLoc stage Inplace) = stageString stage -/- "inplace/package.conf.d"
 
-
+-- See Note [Inplace vs Final package databases]
 data PackageDbLoc = PackageDbLoc { db_stage :: Stage, db_inplace :: Inplace }
 
 -- | Path to the package database used in a given 'Stage', including


=====================================
hadrian/src/Builder.hs
=====================================
@@ -66,7 +66,6 @@ data GhcMode = CompileHs
              | CompileCppWithGhc
              | FindHsDependencies
              | LinkHs
-             | AbiHash
              | ToolArgs
     deriving (Eq, Generic, Show)
 
@@ -296,11 +295,6 @@ instance H.Builder Builder where
           withResources buildResources $ do
               Stdout stdout <- cmd' [path] buildArgs
               pure stdout
-        Ghc AbiHash _ -> do
-          path <- builderPath builder
-          withResources buildResources $ do
-              Stdout stdout <- cmd' [path] buildArgs
-              pure stdout
         _ -> error $ "Builder " ++ show builder ++ " can not be asked!"
 
     runBuilderWith :: Builder -> BuildInfo -> Action ()


=====================================
hadrian/src/Context.hs
=====================================
@@ -141,6 +141,8 @@ pkgConfFile Context {..} = do
     dbPath <- packageDbPath (PackageDbLoc stage iplace)
     return $ dbPath -/- pid <.> "conf"
 
+-- | Path to the stamp file for a given 'Context'. The stamp file records if
+-- we have built all the objects necessary for a certain way or not.
 pkgStampFile :: Context -> Action FilePath
 pkgStampFile c at Context{..} = do
     let extension = waySuffix way


=====================================
hadrian/src/Context/Type.hs
=====================================
@@ -13,7 +13,7 @@ data Context = Context
     { stage   :: Stage   -- ^ Currently build Stage
     , package :: Package -- ^ Currently build Package
     , way     :: Way     -- ^ Currently build Way (usually 'vanilla')
-    , iplace  :: Inplace
+    , iplace  :: Inplace -- ^ Whether to use the inplace or final package database
     } deriving (Eq, Generic, Show)
 
 instance Binary   Context


=====================================
hadrian/src/Hadrian/Haskell/Cabal/Parse.hs
=====================================
@@ -12,7 +12,7 @@
 -----------------------------------------------------------------------------
 module Hadrian.Haskell.Cabal.Parse (
     parsePackageData, resolveContextData, parseCabalPkgId, configurePackage,
-    buildAutogenFiles, copyPackage, writeFakePkgConf, registerPackage
+    buildAutogenFiles, copyPackage, writeInplacePkgConf, registerPackage
     ) where
 
 import Data.Bifunctor
@@ -67,6 +67,7 @@ import qualified Distribution.Simple.Register as C
 import System.Directory (getCurrentDirectory)
 import qualified Distribution.InstalledPackageInfo as CP
 import Distribution.Simple.Utils (writeUTF8File)
+import Utilities
 
 
 -- | Parse the Cabal file of a given 'Package'. This operation is cached by the
@@ -296,9 +297,10 @@ resolveContextData context at Context {..} = do
 
       in return cdata
 
-
-write_fake_conf :: FilePath -> FilePath -> C.PackageDescription -> LocalBuildInfo -> IO ()
-write_fake_conf pkg_path res_path pd lbi = do
+-- Writes a .conf file which points directly into the build directory of a package
+-- so the artefacts can be used as they are produced.
+write_inplace_conf :: FilePath -> FilePath -> C.PackageDescription -> LocalBuildInfo -> IO ()
+write_inplace_conf pkg_path res_path pd lbi = do
        withLibLBI pd lbi $ \lib clbi ->
            do cwd <- getCurrentDirectory
               let fixupIncludeDir dir | cwd `isPrefixOf` dir = [prefix ++ drop (length cwd) dir]
@@ -327,9 +329,9 @@ write_fake_conf pkg_path res_path pd lbi = do
                               (C.toUTF8LBS content)
 
 -- This uses the API directly because no way to register into a different package db which is
--- configured.
-registerPackage :: Context -> Action ()
-registerPackage context = do
+-- configured. See the use of C.SpecificPackageDB
+registerPackage :: [(Resource, Int)] -> Context -> Action ()
+registerPackage rs context = do
     cPath <- Context.contextPath context
     setupConfig <- pkgSetupConfigFile context
     need [setupConfig] -- This triggers 'configurePackage'
@@ -341,8 +343,12 @@ registerPackage context = do
     -- from the local build info @lbi at .
     lbi <- liftIO $ C.getPersistBuildConfig cPath
     liftIO $ register db_path pid dist_dir pd lbi
+    -- Then after the register, which just writes the .conf file, do the recache step.
+    buildWithResources rs $
+      target context (GhcPkg Recache (stage context)) [] []
 
-
+-- This is copied and simplified from Cabal, because we want to install the package
+-- into a different package database to the one it was configured against.
 register :: FilePath
          -> FilePath
          -> FilePath
@@ -354,23 +360,16 @@ register pkg_db conf_file build_dir pd lbi
 
     absPackageDBs    <- C.absolutePackageDBPaths packageDbs
     installedPkgInfo <- C.generateRegistrationInfo
-                           C.verbose pd lib lbi clbi False reloc build_dir
+                           C.silent pd lib lbi clbi False reloc build_dir
                            (C.registrationPackageDB absPackageDBs)
 
-
-     -- Three different modes:
     writeRegistrationFile installedPkgInfo
 
   where
     regFile             = conf_file
-
     reloc     = relocatable lbi
-    -- FIXME: there's really no guarantee this will work.
-    -- registering into a totally different db stack can
-    -- fail if dependencies cannot be satisfied.
+    -- Using a specific package db here is why we have to copy the function from Cabal.
     packageDbs = [C.SpecificPackageDB pkg_db]
---    distPref  = fromFlag (regDistPref regFlags)
---    verbosity = fromFlag (regVerbosity regFlags)
 
     writeRegistrationFile installedPkgInfo = do
       writeUTF8File (pkg_db </> regFile <.> "conf") (CP.showInstalledPackageInfo installedPkgInfo)
@@ -389,9 +388,10 @@ buildAutogenFiles context = do
         lbi <- C.getPersistBuildConfig cPath
         C.initialBuildSteps cPath pd (lbi { C.localPkgDescr = pd }) C.silent
 
--- | Build autogenerated files @autogen/cabal_macros.h@ and @autogen/Paths_*.hs at .
-writeFakePkgConf :: Context -> Action ()
-writeFakePkgConf context = do
+-- | Write a .conf file for the inplace package database which points into the
+-- build directories rather than the final install locations.
+writeInplacePkgConf :: Context -> Action ()
+writeInplacePkgConf context = do
     cPath <- Context.contextPath context
     setupConfig <- pkgSetupConfigFile context
     need [setupConfig] -- This triggers 'configurePackage'
@@ -400,7 +400,7 @@ writeFakePkgConf context = do
     -- Note: the @cPath@ is ignored. The path that's used is the 'buildDir' path
     -- from the local build info @lbi at .
     lbi <- liftIO $ C.getPersistBuildConfig cPath
-    liftIO $ write_fake_conf (pkgPath (package context)) conf pd (lbi { C.localPkgDescr = pd })
+    liftIO $ write_inplace_conf (pkgPath (package context)) conf pd (lbi { C.localPkgDescr = pd })
 
 
 -- | Look for a @.buildinfo@ in all of the specified directories, stopping on


=====================================
hadrian/src/Rules/Library.hs
=====================================
@@ -119,6 +119,8 @@ buildPackage root fp = do
 
   need (srcs ++ gens ++ lib_targets)
 
+  -- Write the current time into the file so the file always changes if
+  -- we restamp it because a dependency changes.
   time <- liftIO $ getCurrentTime
   liftIO $ writeFile fp (show time)
   ways <- interpretInContext ctx getLibraryWays


=====================================
hadrian/src/Rules/Register.hs
=====================================
@@ -114,6 +114,7 @@ registerPackageRules rs stage iplace = do
         case stage of
             Stage0 _ | isBoot -> copyConf  rs ctx conf
             _               ->
+              -- See Note [Inplace vs Final package databases]
               case iplace of
                 Inplace -> buildConfInplace rs ctx conf
                 Final   -> buildConfFinal rs ctx conf
@@ -151,8 +152,6 @@ buildConfFinal rs context at Context {..} _conf = do
     -- Copy and register the package.
     Cabal.copyPackage context
     Cabal.registerPackage context
-    buildWithResources rs $
-      target context (GhcPkg Recache stage) [] []
 
     -- We declare that this rule also produces files matching:
     --   - <root>/stage<N>/lib/<arch>-<os>-ghc-<version>/*libHS<pkgid>*
@@ -196,7 +195,7 @@ buildConfInplace rs context at Context {..} _conf = do
 
     -- Write an "inplace" package conf which points into the build directories
     -- for finding the build products
-    Cabal.writeFakePkgConf context
+    Cabal.writeInplacePkgConf context
     conf <- pkgInplaceConfig context
     buildWithResources rs $
       target context (GhcPkg Update stage) [conf] []


=====================================
hadrian/src/Settings/Builders/Ghc.hs
=====================================
@@ -28,8 +28,7 @@ ghcBuilderArgs = mconcat
       let nextStageRtsBuildIncludeDir = nextStageRtsBuildDir </> "include"
       builder Ghc ? arg ("-I" ++ nextStageRtsBuildIncludeDir)
   , compileAndLinkHs, compileC, compileCxx, findHsDependencies
-  , toolArgs
-  , abiHashArgs]
+  , toolArgs ]
 
 toolArgs :: Args
 toolArgs = do
@@ -41,10 +40,6 @@ toolArgs = do
               , map ("-optP" ++) <$> getContextData cppOpts
               ]
 
-abiHashArgs :: Args
-abiHashArgs = builder (Ghc AbiHash) ? do
-  mconcat [ arg "--abi-hash", commonGhcArgs, getInputs ]
-
 compileAndLinkHs :: Args
 compileAndLinkHs = (builder (Ghc CompileHs) ||^ builder (Ghc LinkHs)) ? do
     ways <- getLibraryWays


=====================================
hadrian/src/Stage.hs
=====================================
@@ -29,18 +29,29 @@ data Stage = Stage0 WhichLibs | Stage1 | Stage2 | Stage3
     deriving (Show, Eq, Ord, Generic)
 
 {-
+Note [Inplace vs Final package databases]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
 There are two package databases we maintain an "inplace" one and a "final" one.
 The inplace one is created by pre-configuring all the packages before doing any
 building. All GHC invocations to build .hs files will use an inplace package database
 for two reasons.
 
-1. To increase parrelism
+1. To increase parallelism
 2. ./hadrian/ghci-multi can use the inplace package db to avoid having to build everything
    before starting.
 
-Once we need to create the final library, we instead need the .conf in the "final"
-database which has the effect of needing the "final".conf for all dependent packages
-and so on as well as building the libraries.
+The "inplace" database has .conf files which point directly to the build folders.
+The "final" database has a .conf file which points like normall to the install folder.
+
+Therefore when we are building modules, we can start compiling a module as soon as
+all it's dependencies are available in the build folder, rather than waiting for the
+whole package to finish, be copied and installed like before.
+
+Once we need to do a final link then we need to wait for the "final" versions to
+be enabled because then we want to make sure to create objects with the right rpaths and
+so on. The "final" .conf has dependencies on all the objects in the package (unlike the "inplace" .conf
+which has no such dependencies).
 
 -}
 data Inplace = Inplace | Final deriving (Show, Eq, Generic)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/064c07ebf4967bf1e1ba381d4e78454dea9ea7f7

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/064c07ebf4967bf1e1ba381d4e78454dea9ea7f7
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20220822/9bae44b1/attachment-0001.html>


More information about the ghc-commits mailing list