[Git][ghc/ghc][wip/hadrian-cross-stage2] 3 commits: whitespace

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Thu Oct 5 16:03:39 UTC 2023



Matthew Pickering pushed to branch wip/hadrian-cross-stage2 at Glasgow Haskell Compiler / GHC


Commits:
b22d40f1 by Matthew Pickering at 2023-10-05T15:42:16+01:00
whitespace

- - - - -
93420843 by Matthew Pickering at 2023-10-05T16:46:50+01:00
hadrian: Move ghcBinDeps into ghcLibDeps

This completes a5227080b57cb51ac34d4c9de1accdf6360b818b, the
`ghc-usage.txt` and `ghci-usage.txt` file are also used by the `ghc`
library so need to make sure they are present in the libdir even if we
are not going to build `ghc-bin`.

This also fixes things for cross compilers because the stage2
cross-compiler requires the ghc-usage.txt file, but we are using
the stage2 lib folder but not building stage3:exe:ghc-bin so
ghc-usage.txt was not being generated.

- - - - -
38332414 by Matthew Pickering at 2023-10-05T17:02:23+01:00
Werror

- - - - -


5 changed files:

- hadrian/src/Base.hs
- hadrian/src/Builder.hs
- hadrian/src/Packages.hs
- hadrian/src/Rules/Program.hs
- hadrian/src/Settings/Program.hs


Changes:

=====================================
hadrian/src/Base.hs
=====================================
@@ -32,7 +32,7 @@ module Base (
     hadrianPath, configPath, configFile, sourcePath, shakeFilesDir,
     stageBinPath, stageLibPath, templateHscPath,
     buildTargetFile, hostTargetFile, targetTargetFile,
-    ghcBinDeps, ghcLibDeps, haddockDeps,
+    ghcLibDeps, haddockDeps,
     relativePackageDbPath, packageDbPath, packageDbStamp, mingwStamp,
     systemCxxStdLibConf, systemCxxStdLibConfPath
     , PackageDbLoc(..), Inplace(..)
@@ -151,17 +151,12 @@ ghcLibDeps stage iplace = do
         , "llvm-passes"
         , "ghc-interp.js"
         , "settings"
+        , "ghc-usage.txt"
+        , "ghci-usage.txt"
         ]
     cxxStdLib <- systemCxxStdLibConfPath (PackageDbLoc stage iplace)
     return (cxxStdLib : ps)
 
--- | Files the GHC binary depends on.
-ghcBinDeps :: Stage -> Action [FilePath]
-ghcBinDeps stage = mapM (\f -> stageLibPath stage <&> (-/- f))
-    [ "ghc-usage.txt"
-    , "ghci-usage.txt"
-    ]
-
 -- | Files the `haddock` binary depends on
 haddockDeps :: Stage -> Action [FilePath]
 haddockDeps stage = do


=====================================
hadrian/src/Builder.hs
=====================================
@@ -238,17 +238,12 @@ instance H.Builder Builder where
           -- changes (#18001).
           _bootGhcVersion <- setting GhcVersion
           pure []
-        Ghc _ stage -> do
+        Ghc {} -> do
             root <- buildRoot
             touchyPath <- programPath (vanillaContext (Stage0 InTreeLibs) touchy)
             unlitPath  <- builderPath Unlit
 
-            -- GHC from the previous stage is used to build artifacts in the
-            -- current stage. Need the previous stage's GHC deps.
-            ghcdeps <- ghcBinDeps (predStage stage)
-
             return $ [ unlitPath ]
-                  ++ ghcdeps
                   ++ [ touchyPath          | windowsHost ]
                   ++ [ root -/- mingwStamp | windowsHost ]
                      -- proxy for the entire mingw toolchain that


=====================================
hadrian/src/Packages.hs
=====================================
@@ -188,7 +188,7 @@ programName Context {..} = do
     return $ prefix ++ programBasename way package
 
 programBasename :: Way -> Package -> String
-programBasename way package 
+programBasename way package
       | package == ghc          = "ghc"
       | package == ghciWrapper  = "ghci" -- See Note [Hadrian's ghci-wrapper package]
       | package == hpcBin       = "hpc"


=====================================
hadrian/src/Rules/Program.hs
=====================================
@@ -85,8 +85,6 @@ buildProgram bin ctx@(Context{..}) rs = do
     need [template]
   -- Custom dependencies: this should be modeled better in the
   -- Cabal file somehow.
-  when (package == ghc) $ do
-    need =<< ghcBinDeps stage
   when (package == haddock) $ do
     -- Haddock has a resource folder
     need =<< haddockDeps stage


=====================================
hadrian/src/Settings/Program.hs
=====================================
@@ -5,7 +5,6 @@ module Settings.Program
 import Base
 import Context
 import Oracles.Flavour
-import Oracles.Setting
 import Packages
 
 -- TODO: there is duplication and inconsistency between this and
@@ -14,11 +13,11 @@ import Packages
 programContext :: Stage -> Package -> Action Context
 programContext stage pkg = do
     profiled <- askGhcProfiled stage
-    dynGhcProgs <- askDynGhcPrograms stage 
+    dynGhcProgs <- askDynGhcPrograms stage
     -- Have to build static if it's a cross stage as we won't distribute the libraries built for the host.
     return $ Context stage pkg (wayFor profiled dynGhcProgs) Final
 
-    where wayFor prof dyn 
+    where wayFor prof dyn
             | prof && dyn                           =
                 error "programContext: profiling+dynamic not supported"
             | pkg == ghc && prof && notStage0 stage = profiling



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f2b01a14405ad08ae3bfd9b1a9c74013685ff6a4...383324142ee5cef2c18d3c137fff314519a4b0f0

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f2b01a14405ad08ae3bfd9b1a9c74013685ff6a4...383324142ee5cef2c18d3c137fff314519a4b0f0
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/20231005/dd7de37c/attachment-0001.html>


More information about the ghc-commits mailing list