[Git][ghc/ghc][master] Hadrian: Generate GHC wrapper scripts
Marge Bot
gitlab at gitlab.haskell.org
Tue Apr 16 19:52:47 UTC 2019
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
894ec447 by Andrey Mokhov at 2019-04-16T19:46:44Z
Hadrian: Generate GHC wrapper scripts
This is a temporary workaround for #16534. We generate wrapper scripts
<build-root>/ghc-stage1 and <build-root>/ghc-stage2 that can be used to
run Stage1 and Stage2 GHCs with the right arguments.
See https://gitlab.haskell.org/ghc/ghc/issues/16534.
- - - - -
2 changed files:
- hadrian/src/Rules.hs
- hadrian/src/Rules/Generate.hs
Changes:
=====================================
hadrian/src/Rules.hs
=====================================
@@ -83,7 +83,12 @@ topLevelTargets = action $ do
targets <- concatForM buildStages $ \stage -> do
packages <- stagePackages stage
mapM (path stage) packages
- need targets
+
+ -- Why we need wrappers: https://gitlab.haskell.org/ghc/ghc/issues/16534.
+ root <- buildRoot
+ let wrappers = [ root -/- ("ghc-" ++ stageString s) | s <- [Stage1 ..]
+ , s < finalStage ]
+ need (targets ++ wrappers)
where
-- either the package database config file for libraries or
-- the programPath for programs. However this still does
=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -170,6 +170,10 @@ copyRules = do
generateRules :: Rules ()
generateRules = do
root <- buildRootRules
+
+ (root -/- "ghc-stage1") <~ ghcWrapper Stage1
+ (root -/- "ghc-stage2") <~ ghcWrapper Stage2
+
priority 2.0 $ (root -/- generatedDir -/- "ghcautoconf.h") <~ generateGhcAutoconfH
priority 2.0 $ (root -/- generatedDir -/- "ghcplatform.h") <~ generateGhcPlatformH
priority 2.0 $ (root -/- generatedDir -/- "ghcversion.h") <~ generateGhcVersionH
@@ -190,6 +194,17 @@ emptyTarget = vanillaContext (error "Rules.Generate.emptyTarget: unknown stage")
-- Generators
+-- | GHC wrapper scripts used for passing the path to the right package database
+-- when invoking in-tree GHC executables.
+ghcWrapper :: Stage -> Expr String
+ghcWrapper Stage0 = error "Stage0 GHC does not require a wrapper script to run."
+ghcWrapper stage = do
+ dbPath <- expr $ packageDbPath stage
+ ghcPath <- expr $ programPath (vanillaContext (pred stage) ghc)
+ return $ unwords $ map show $ [ ghcPath ]
+ ++ [ "-package-db " ++ dbPath | stage == Stage1 ]
+ ++ [ "$@" ]
+
-- | Given a 'String' replace charaters '.' and '-' by underscores ('_') so that
-- the resulting 'String' is a valid C preprocessor identifier.
cppify :: String -> String
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/894ec447955a5066faee1b87af9cc7785ae14cd8
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/894ec447955a5066faee1b87af9cc7785ae14cd8
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/20190416/067b2c75/attachment-0001.html>
More information about the ghc-commits
mailing list