[Git][ghc/ghc][master] 3 commits: Hadrian: fix cross-compiler build (#16051)
Marge Bot
gitlab at gitlab.haskell.org
Sun May 24 19:22:26 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
7a07aa71 by Sylvain Henry at 2020-05-24T15:22:17-04:00
Hadrian: fix cross-compiler build (#16051)
- - - - -
15ccca16 by Sylvain Henry at 2020-05-24T15:22:17-04:00
Hadrian: fix distDir per stage
- - - - -
b420fb24 by Sylvain Henry at 2020-05-24T15:22:17-04:00
Hadrian: fix hp2ps error during cross-compilation
Fixed by @alp (see https://gitlab.haskell.org/ghc/ghc/issues/16051#note_274265)
- - - - -
3 changed files:
- hadrian/src/Context.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Packages.hs
Changes:
=====================================
hadrian/src/Context.hs
=====================================
@@ -55,9 +55,12 @@ libPath Context {..} = buildRoot <&> (-/- (stageString stage -/- "lib"))
-- conventions (see 'cabalOsString' and 'cabalArchString').
distDir :: Stage -> Action FilePath
distDir st = do
+ let (os,arch) = case st of
+ Stage0 -> (HostOs , HostArch)
+ _ -> (TargetOs, TargetArch)
version <- ghcVersionStage st
- hostOs <- cabalOsString <$> setting BuildOs
- hostArch <- cabalArchString <$> setting BuildArch
+ hostOs <- cabalOsString <$> setting os
+ hostArch <- cabalArchString <$> setting arch
return $ hostArch ++ "-" ++ hostOs ++ "-ghc-" ++ version
pkgFileName :: Package -> String -> String -> Action FilePath
=====================================
hadrian/src/Settings/Default.hs
=====================================
@@ -81,6 +81,7 @@ stage0Packages = do
++ [ terminfo | not windowsHost, not cross ]
++ [ timeout | windowsHost ]
++ [ touchy | windowsHost ]
+ ++ [ hp2ps | cross ]
-- | Packages built in 'Stage1' by default. You can change this in "UserSettings".
stage1Packages :: Action [Package]
=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -20,6 +20,10 @@ packageArgs = do
-- See: https://gitlab.haskell.org/ghc/ghc/issues/16809.
cross = flag CrossCompiling
+ -- Check if the bootstrap compiler has the same version as the one we
+ -- are building. This is used to build cross-compilers
+ bootCross = (==) <$> ghcVersionStage Stage0 <*> ghcVersionStage Stage1
+
mconcat
--------------------------------- base ---------------------------------
[ package base ? mconcat
@@ -105,22 +109,37 @@ packageArgs = do
input "**/cbits/atomic.c" ? arg "-Wno-sync-nand" ]
--------------------------------- ghci ---------------------------------
- -- TODO: This should not be @not <$> flag CrossCompiling at . Instead we
- -- should ensure that the bootstrap compiler has the same version as the
- -- one we are building.
-
- -- TODO: In that case we also do not need to build most of the Stage1
- -- libraries, as we already know that the compiler comes with the most
- -- recent versions.
-
- -- TODO: The use case here is that we want to build @ghc-proxy@ for the
- -- cross compiler. That one needs to be compiled by the bootstrap
- -- compiler as it needs to run on the host. Hence @libiserv@ needs
- -- @GHCi.TH@, @GHCi.Message@ and @GHCi.Run@ from @ghci at . And those are
- -- behind the @-fghci@ flag.
, package ghci ? mconcat
[ notStage0 ? builder (Cabal Flags) ? arg "ghci"
- , cross ? stage0 ? builder (Cabal Flags) ? arg "ghci" ]
+
+ -- The use case here is that we want to build @ghc-proxy@ for the
+ -- cross compiler. That one needs to be compiled by the bootstrap
+ -- compiler as it needs to run on the host. Hence @libiserv@ needs
+ -- @GHCi.TH@, @GHCi.Message@ and @GHCi.Run@ from @ghci at . And those are
+ -- behind the @-fghci@ flag.
+ --
+ -- But it may not build if we have made some changes to ghci's
+ -- dependencies (see #16051).
+ --
+ -- To fix this properly Hadrian would need to:
+ -- * first build a compiler for the build platform (stage1 is enough)
+ -- * use it as a bootstrap compiler to build the stage1 cross-compiler
+ --
+ -- The issue is that "configure" would have to be executed twice (for
+ -- the build platform and for the cross-platform) and Hadrian would
+ -- need to be fixed to support two different stage1 compilers.
+ --
+ -- The workaround we use is to check if the bootstrap compiler has
+ -- the same version as the one we are building. In this case we can
+ -- avoid the first step above and directly build with `-fghci`.
+ --
+ -- TODO: Note that in that case we also do not need to build most of
+ -- the Stage1 libraries, as we already know that the bootstrap
+ -- compiler comes with the same versions as the one we are building.
+ --
+ , cross ? stage0 ? bootCross ? builder (Cabal Flags) ? arg "ghci"
+
+ ]
--------------------------------- iserv --------------------------------
-- Add -Wl,--export-dynamic enables GHCi to load dynamic objects that
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/01c43634d443bd3cc0b95b43a7180e12230b845d...b420fb2474650e6dfbd66afd199f28492f900f75
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/01c43634d443bd3cc0b95b43a7180e12230b845d...b420fb2474650e6dfbd66afd199f28492f900f75
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/20200524/5f52e455/attachment-0001.html>
More information about the ghc-commits
mailing list