Skip to content
Snippets Groups Projects
Commit 32523713 authored by Matthew Pickering's avatar Matthew Pickering Committed by Marge Bot
Browse files

hadrian: Move ghcBinDeps into ghcLibDeps

This completes a5227080, 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.
parent fea9ecdb
No related branches found
No related tags found
No related merge requests found
...@@ -32,7 +32,7 @@ module Base ( ...@@ -32,7 +32,7 @@ module Base (
hadrianPath, configPath, configFile, sourcePath, shakeFilesDir, hadrianPath, configPath, configFile, sourcePath, shakeFilesDir,
stageBinPath, stageLibPath, templateHscPath, stageBinPath, stageLibPath, templateHscPath,
buildTargetFile, hostTargetFile, targetTargetFile, buildTargetFile, hostTargetFile, targetTargetFile,
ghcBinDeps, ghcLibDeps, haddockDeps, ghcLibDeps, haddockDeps,
relativePackageDbPath, packageDbPath, packageDbStamp, mingwStamp, relativePackageDbPath, packageDbPath, packageDbStamp, mingwStamp,
systemCxxStdLibConf, systemCxxStdLibConfPath systemCxxStdLibConf, systemCxxStdLibConfPath
, PackageDbLoc(..), Inplace(..) , PackageDbLoc(..), Inplace(..)
...@@ -151,17 +151,12 @@ ghcLibDeps stage iplace = do ...@@ -151,17 +151,12 @@ ghcLibDeps stage iplace = do
, "llvm-passes" , "llvm-passes"
, "ghc-interp.js" , "ghc-interp.js"
, "settings" , "settings"
, "ghc-usage.txt"
, "ghci-usage.txt"
] ]
cxxStdLib <- systemCxxStdLibConfPath (PackageDbLoc stage iplace) cxxStdLib <- systemCxxStdLibConfPath (PackageDbLoc stage iplace)
return (cxxStdLib : ps) 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 -- | Files the `haddock` binary depends on
haddockDeps :: Stage -> Action [FilePath] haddockDeps :: Stage -> Action [FilePath]
haddockDeps stage = do haddockDeps stage = do
......
...@@ -238,17 +238,12 @@ instance H.Builder Builder where ...@@ -238,17 +238,12 @@ instance H.Builder Builder where
-- changes (#18001). -- changes (#18001).
_bootGhcVersion <- setting GhcVersion _bootGhcVersion <- setting GhcVersion
pure [] pure []
Ghc _ stage -> do Ghc {} -> do
root <- buildRoot root <- buildRoot
touchyPath <- programPath (vanillaContext (Stage0 InTreeLibs) touchy) touchyPath <- programPath (vanillaContext (Stage0 InTreeLibs) touchy)
unlitPath <- builderPath Unlit 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 ] return $ [ unlitPath ]
++ ghcdeps
++ [ touchyPath | windowsHost ] ++ [ touchyPath | windowsHost ]
++ [ root -/- mingwStamp | windowsHost ] ++ [ root -/- mingwStamp | windowsHost ]
-- proxy for the entire mingw toolchain that -- proxy for the entire mingw toolchain that
......
...@@ -85,8 +85,6 @@ buildProgram bin ctx@(Context{..}) rs = do ...@@ -85,8 +85,6 @@ buildProgram bin ctx@(Context{..}) rs = do
need [template] need [template]
-- Custom dependencies: this should be modeled better in the -- Custom dependencies: this should be modeled better in the
-- Cabal file somehow. -- Cabal file somehow.
when (package == ghc) $ do
need =<< ghcBinDeps stage
when (package == haddock) $ do when (package == haddock) $ do
-- Haddock has a resource folder -- Haddock has a resource folder
need =<< haddockDeps stage need =<< haddockDeps stage
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment