[Git][ghc/ghc][wip/hadrian-ar-merge] Hadrian: merge archives even in stage 0

sheaf (@sheaf) gitlab at gitlab.haskell.org
Fri Sep 16 10:53:20 UTC 2022



sheaf pushed to branch wip/hadrian-ar-merge at Glasgow Haskell Compiler / GHC


Commits:
3c6c2809 by sheaf at 2022-09-16T12:51:58+02:00
Hadrian: merge archives even in stage 0

We now always merge .a archives when ar supports -L.
This change is necessary in order to bootstrap GHC using GHC 9.4
on Windows, as nested archives aren't supported.
Not doing so triggered bug #21990 when trying to use the Win32
package, with errors such as:

  Not a x86_64 PE+ file.
  Unknown COFF 4 type in getHeaderInfo.

  ld.lld: error: undefined symbol: Win32zm2zi12zi0zi0_SystemziWin32ziConsoleziCtrlHandler_withConsoleCtrlHandler1_info

We have to be careful about which ar is meant: in stage 0, the check
should be done on the system ar (system-ar in system.config).

- - - - -


3 changed files:

- hadrian/cfg/system.config.in
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Settings/Builders/Ar.hs


Changes:

=====================================
hadrian/cfg/system.config.in
=====================================
@@ -39,10 +39,11 @@ python         = @PythonCmd@
 # Information about builders:
 #============================
 
-ar-supports-at-file = @ArSupportsAtFile@
-ar-supports-dash-l  = @ArSupportsDashL@
-cc-llvm-backend     = @CcLlvmBackend@
-hs-cpp-args         = @HaskellCPPArgs@
+ar-supports-at-file       = @ArSupportsAtFile@
+ar-supports-dash-l        = @ArSupportsDashL@
+system-ar-supports-dash-l = @ArSupportsDashL_STAGE0@
+cc-llvm-backend           = @CcLlvmBackend@
+hs-cpp-args               = @HaskellCPPArgs@
 
 # Build options:
 #===============


=====================================
hadrian/src/Oracles/Flag.hs
=====================================
@@ -5,7 +5,8 @@ module Oracles.Flag (
     platformSupportsSharedLibs,
     platformSupportsGhciObjects,
     targetSupportsSMP,
-    useLibffiForAdjustors
+    useLibffiForAdjustors,
+    arSupportsDashL
     ) where
 
 import Hadrian.Oracles.TextFile
@@ -16,6 +17,7 @@ import Oracles.Setting
 
 data Flag = ArSupportsAtFile
           | ArSupportsDashL
+          | SystemArSupportsDashL
           | CrossCompiling
           | CcLlvmBackend
           | GhcUnregisterised
@@ -39,6 +41,7 @@ flag f = do
     let key = case f of
             ArSupportsAtFile     -> "ar-supports-at-file"
             ArSupportsDashL      -> "ar-supports-dash-l"
+            SystemArSupportsDashL-> "system-ar-supports-dash-l"
             CrossCompiling       -> "cross-compiling"
             CcLlvmBackend        -> "cc-llvm-backend"
             GhcUnregisterised    -> "ghc-unregisterised"
@@ -69,6 +72,10 @@ platformSupportsGhciObjects :: Action Bool
 platformSupportsGhciObjects =
     not . null <$> settingsFileSetting SettingsFileSetting_MergeObjectsCommand
 
+arSupportsDashL :: Stage -> Action Bool
+arSupportsDashL (Stage0 {}) = flag SystemArSupportsDashL
+arSupportsDashL _           = flag ArSupportsDashL
+
 platformSupportsSharedLibs :: Action Bool
 platformSupportsSharedLibs = do
     windows       <- isWinTarget


=====================================
hadrian/src/Settings/Builders/Ar.hs
=====================================
@@ -6,7 +6,9 @@ import Settings.Builders.Common
 -- want to place these in a response file. This is handled in
 -- 'Hadrian.Builder.Ar.runAr'.
 arBuilderArgs :: Args
-arBuilderArgs = mconcat
+arBuilderArgs = do
+  stage <- getStage
+  mconcat
     [ builder (Ar Pack) ? mconcat
       [ -- When building on platforms which don't support object merging
         -- we must use the -L flag supported by llvm-ar, which ensures that
@@ -14,7 +16,7 @@ arBuilderArgs = mconcat
         -- not added as a single file. This requires that we are using llvm-ar
         --
         -- See Note [Object merging] in GHC.Driver.Pipeline.Execute for details.
-        ifM ((&&) <$> notStage0 <*> expr (flag ArSupportsDashL)) (arg "qL") (arg "q")
+        ifM (expr $ arSupportsDashL stage) (arg "qL") (arg "q")
       , arg =<< getOutput
       ]
     , builder (Ar Unpack) ? mconcat



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3c6c28096a59fddf467fb37cccf1239220197435

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3c6c28096a59fddf467fb37cccf1239220197435
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/20220916/74507a1b/attachment-0001.html>


More information about the ghc-commits mailing list