[Git][ghc/ghc][wip/romes/24161] 3 commits: darwin: Fix single_module is obsolete warning

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Tue Nov 14 12:32:02 UTC 2023



Rodrigo Mesquita pushed to branch wip/romes/24161 at Glasgow Haskell Compiler / GHC


Commits:
df988e4a by Rodrigo Mesquita at 2023-11-14T12:31:44+00:00
darwin: Fix single_module is obsolete warning

In XCode 15's linker, -single_module is the default and otherwise
passing it as a flag results in a warning being raised:

    ld: warning: -single_module is obsolete

This patch fixes this warning by, at configure time, determining whether
the linker supports -single_module (which is likely false for all
non-darwin linkers, and true for darwin linkers in previous versions of
macOS), and using that information at runtime to decide to pass or not
the flag in the invocation.

Fixes #24168

- - - - -
f03c1fef by Rodrigo Mesquita at 2023-11-14T12:31:44+00:00
testsuite: Skip MultiLayerModulesTH_Make on darwin

The recent toolchain upgrade on darwin machines resulted in the
MultiLayerModulesTH_Make test metrics varying too much from the
baseline, ultimately blocking the CI pipelines.

This commit skips the test on darwin to temporarily avoid failures due
to the environment change in the runners. However, the metrics
divergence is being investigated still (tracked in #24177)

- - - - -
b4a6d8c8 by Rodrigo Mesquita at 2023-11-14T12:31:44+00:00
configure: check target (not build) understands -no_compact_unwind

Previously, we were branching on whether the build system was darwin to
shortcut this check, but we really want to branch on whether the target
system (which is what we are configuring ld_prog for) is darwin.

- - - - -


15 changed files:

- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- configure.ac
- distrib/configure.ac.in
- hadrian/bindist/Makefile
- hadrian/bindist/config.mk.in
- hadrian/cfg/default.host.target.in
- hadrian/cfg/default.target.in
- hadrian/src/Rules/Generate.hs
- m4/fp_prog_ld_no_compact_unwind.m4
- + m4/fp_prog_ld_single_module.m4
- m4/prep_target_file.m4
- testsuite/tests/perf/compiler/all.T
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs


Changes:

=====================================
compiler/GHC/Linker/Dynamic.hs
=====================================
@@ -11,6 +11,7 @@ where
 import GHC.Prelude
 import GHC.Platform
 import GHC.Platform.Ways
+import GHC.Settings (ToolSettings(toolSettings_ldSupportsSingleModule))
 
 import GHC.Driver.Config.Linker
 import GHC.Driver.Session
@@ -152,6 +153,9 @@ linkDynLib logger tmpfs dflags0 unit_env o_files dep_packages
             --   dynamic binding nonsense when referring to symbols from
             --   within the library. The NCG assumes that this option is
             --   specified (on i386, at least).
+            --   In XCode 15, -single_module is the default and passing the
+            --   flag is now obsolete and raises a warning (#24168). We encode
+            --   this information into the toolchain field ...SupportsSingleModule.
             -- -install_name
             --   Mac OS/X stores the path where a dynamic library is (to
             --   be) installed in the library itself.  It's called the
@@ -177,8 +181,11 @@ linkDynLib logger tmpfs dflags0 unit_env o_files dep_packages
                     ]
                  ++ map Option o_files
                  ++ [ Option "-undefined",
-                      Option "dynamic_lookup",
-                      Option "-single_module" ]
+                      Option "dynamic_lookup"
+                    ]
+                 ++ (if toolSettings_ldSupportsSingleModule (toolSettings dflags)
+                        then [ Option "-single_module" ]
+                        else [ ])
                  ++ (if platformArch platform `elem` [ ArchX86_64, ArchAArch64 ]
                      then [ ]
                      else [ Option "-Wl,-read_only_relocs,suppress" ])


=====================================
compiler/GHC/Settings.hs
=====================================
@@ -86,6 +86,7 @@ data Settings = Settings
 data ToolSettings = ToolSettings
   { toolSettings_ldSupportsCompactUnwind :: Bool
   , toolSettings_ldSupportsFilelist      :: Bool
+  , toolSettings_ldSupportsSingleModule  :: Bool
   , toolSettings_mergeObjsSupportsResponseFiles :: Bool
   , toolSettings_ldIsGnuLd               :: Bool
   , toolSettings_ccSupportsNoPie         :: Bool


=====================================
compiler/GHC/Settings/IO.hs
=====================================
@@ -107,6 +107,7 @@ initSettings top_dir = do
 
   ldSupportsCompactUnwind <- getBooleanSetting "ld supports compact unwind"
   ldSupportsFilelist      <- getBooleanSetting "ld supports filelist"
+  ldSupportsSingleModule  <- getBooleanSetting "ld supports single module"
   mergeObjsSupportsResponseFiles <- getBooleanSetting "Merge objects supports response files"
   ldIsGnuLd               <- getBooleanSetting "ld is GNU ld"
   arSupportsDashL         <- getBooleanSetting "ar supports -L"
@@ -171,6 +172,7 @@ initSettings top_dir = do
     , sToolSettings = ToolSettings
       { toolSettings_ldSupportsCompactUnwind = ldSupportsCompactUnwind
       , toolSettings_ldSupportsFilelist      = ldSupportsFilelist
+      , toolSettings_ldSupportsSingleModule  = ldSupportsSingleModule
       , toolSettings_mergeObjsSupportsResponseFiles = mergeObjsSupportsResponseFiles
       , toolSettings_ldIsGnuLd               = ldIsGnuLd
       , toolSettings_ccSupportsNoPie         = gccSupportsNoPie


=====================================
configure.ac
=====================================
@@ -452,6 +452,7 @@ CFLAGS="$CFLAGS $GccUseLdOpt"
 FP_PROG_LD_IS_GNU
 FP_PROG_LD_NO_COMPACT_UNWIND
 FP_PROG_LD_FILELIST
+FP_PROG_LD_SINGLE_MODULE
 
 
 dnl ** Which nm to use?


=====================================
distrib/configure.ac.in
=====================================
@@ -136,6 +136,7 @@ CFLAGS="$CFLAGS $GccUseLdOpt"
 FP_PROG_LD_IS_GNU
 FP_PROG_LD_NO_COMPACT_UNWIND
 FP_PROG_LD_FILELIST
+FP_PROG_LD_SINGLE_MODULE
 
 dnl ** which strip to use?
 dnl --------------------------------------------------------------


=====================================
hadrian/bindist/Makefile
=====================================
@@ -104,6 +104,7 @@ lib/settings : config.mk
 	@echo ',("Haskell CPP flags", "$(SettingsHaskellCPPFlags)")' >> $@
 	@echo ',("ld supports compact unwind", "$(LdHasNoCompactUnwind)")' >> $@
 	@echo ',("ld supports filelist", "$(LdHasFilelist)")' >> $@
+	@echo ',("ld supports single module", "$(LdHasSingleModule)")' >> $@
 	@echo ',("ld is GNU ld", "$(LdIsGNULd)")' >> $@
 	@echo ',("Merge objects command", "$(SettingsMergeObjectsCommand)")' >> $@
 	@echo ',("Merge objects flags", "$(SettingsMergeObjectsFlags)")' >> $@


=====================================
hadrian/bindist/config.mk.in
=====================================
@@ -191,6 +191,7 @@ LdHasBuildId = @LdHasBuildId@
 LdHasFilelist = @LdHasFilelist@
 LdIsGNULd = @LdIsGNULd@
 LdHasNoCompactUnwind = @LdHasNoCompactUnwind@
+LdHasSingleModule = @LdHasSingleModule@
 ArArgs = @ArArgs@
 ArSupportsAtFile = @ArSupportsAtFile@
 ArSupportsDashL  = @ArSupportsDashL@


=====================================
hadrian/cfg/default.host.target.in
=====================================
@@ -21,6 +21,7 @@ Target
 , ccLinkSupportsNoPie = False
 , ccLinkSupportsCompactUnwind = False
 , ccLinkSupportsFilelist = False
+, ccLinkSupportsSingleModule = True
 , ccLinkIsGnu = False
 }
 


=====================================
hadrian/cfg/default.target.in
=====================================
@@ -21,6 +21,7 @@ Target
 , ccLinkSupportsNoPie = @CONF_GCC_SUPPORTS_NO_PIEBool@
 , ccLinkSupportsCompactUnwind = @LdHasNoCompactUnwindBool@
 , ccLinkSupportsFilelist = @LdHasFilelistBool@
+, ccLinkSupportsSingleModule = @LdHasSingleModuleBool@
 , ccLinkIsGnu = @LdIsGNULdBool@
 }
 


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -373,6 +373,7 @@ generateSettings = do
         , ("Haskell CPP flags",   queryTarget hsCppFlags)
         , ("ld supports compact unwind", queryTarget linkSupportsCompactUnwind)
         , ("ld supports filelist",       queryTarget linkSupportsFilelist)
+        , ("ld supports single module",       queryTarget linkSupportsSingleModule)
         , ("ld is GNU ld",               queryTarget linkIsGnu)
         , ("Merge objects command", queryTarget mergeObjsPath)
         , ("Merge objects flags", queryTarget mergeObjsFlags)
@@ -431,6 +432,7 @@ generateSettings = do
     hsCppFlags = unwords . prgFlags . hsCppProgram . tgtHsCPreprocessor
     mergeObjsPath  = maybe "" (prgPath . mergeObjsProgram) . tgtMergeObjs
     mergeObjsFlags = maybe "" (unwords . prgFlags . mergeObjsProgram) . tgtMergeObjs
+    linkSupportsSingleModule    = yesNo . ccLinkSupportsSingleModule . tgtCCompilerLink
     linkSupportsFilelist        = yesNo . ccLinkSupportsFilelist . tgtCCompilerLink
     linkSupportsCompactUnwind   = yesNo . ccLinkSupportsCompactUnwind . tgtCCompilerLink
     linkIsGnu                   = yesNo . ccLinkIsGnu . tgtCCompilerLink


=====================================
m4/fp_prog_ld_no_compact_unwind.m4
=====================================
@@ -6,7 +6,7 @@ AC_DEFUN([FP_PROG_LD_NO_COMPACT_UNWIND],
 [
 AC_CACHE_CHECK([whether ld understands -no_compact_unwind], [fp_cv_ld_no_compact_unwind],
 [
-case $build in
+case $target in
   *-darwin)
     echo 'int foo() { return 0; }' > conftest.c
     "${CC-cc}" -c conftest.c


=====================================
m4/fp_prog_ld_single_module.m4
=====================================
@@ -0,0 +1,30 @@
+# FP_PROG_LD_SINGLE_MODULE
+# ----------------------------
+# Sets the output variable LdHasSingleModule to YES if the darwin ld supports
+# -single_module, or NO otherwise.
+#
+# In XCode 15, -single_module is a default and passing it as a flag raises a
+# warning.
+AC_DEFUN([FP_PROG_LD_SINGLE_MODULE],
+[
+AC_CACHE_CHECK([whether ld supports -single_module], [fp_cv_ld_single_module],
+[
+case $target in
+  *-darwin)
+    echo 'int foo(int x) { return x*x; }' > conftest.c
+    echo 'extern int foo(int); int main() { return foo(5); }' > conftestmain.c
+    "$CC" -c -o conftestmain.o conftestmain.c
+    "$CC" -shared -o conftest.dylib conftest.c
+    if "$CC" -Wl,-single_module -o conftest conftestmain.o conftest.dylib 2>&1 | grep obsolete > /dev/null; then
+      fp_cv_ld_single_module=no
+    else
+      fp_cv_ld_single_module=yes
+    fi
+    rm -rf conftest* ;;
+  *)
+    fp_cv_ld_single_module=no ;;
+esac
+])
+FP_CAPITALIZE_YES_NO(["$fp_cv_ld_single_module"], [LdHasSingleModule])
+AC_SUBST([LdHasSingleModule])
+])# FP_PROG_LD_SINGLE_MODULE


=====================================
m4/prep_target_file.m4
=====================================
@@ -131,6 +131,7 @@ AC_DEFUN([PREP_TARGET_FILE],[
     PREP_BOOLEAN([TargetHasIdentDirective])
     PREP_BOOLEAN([CONF_GCC_SUPPORTS_NO_PIE])
     PREP_BOOLEAN([LdHasFilelist])
+    PREP_BOOLEAN([LdHasSingleModule])
     PREP_BOOLEAN([LdIsGNULd])
     PREP_BOOLEAN([LdHasNoCompactUnwind])
     PREP_BOOLEAN([TargetHasSubsectionsViaSymbols])


=====================================
testsuite/tests/perf/compiler/all.T
=====================================
@@ -361,7 +361,10 @@ test('MultiLayerModulesTH_Make',
        pre_cmd('$MAKE -s --no-print-directory MultiLayerModulesTH_Make_Prep'),
        extra_files(['genMultiLayerModulesTH']),
        unless(have_dynamic(),skip),
-       compile_timeout_multiplier(5)
+       compile_timeout_multiplier(5),
+       # We skip the test on darwin due to recent regression due to toolchain
+       # upgrade (tracked in #24177)
+       when(opsys('darwin'), skip)
      ],
      multimod_compile_fail,
      # see Note [Increased initial stack size for MultiLayerModules]


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
=====================================
@@ -22,6 +22,7 @@ data CcLink = CcLink { ccLinkProgram :: Program
                      , ccLinkSupportsNoPie :: Bool -- See Note [No PIE when linking] in GHC.Driver.Session
                      , ccLinkSupportsCompactUnwind :: Bool
                      , ccLinkSupportsFilelist :: Bool
+                     , ccLinkSupportsSingleModule :: Bool
                      , ccLinkIsGnu :: Bool
                      }
     deriving (Read, Eq, Ord)
@@ -34,6 +35,7 @@ instance Show CcLink where
     , ", ccLinkSupportsNoPie = " ++ show ccLinkSupportsNoPie
     , ", ccLinkSupportsCompactUnwind = " ++ show ccLinkSupportsCompactUnwind
     , ", ccLinkSupportsFilelist = " ++ show ccLinkSupportsFilelist
+    , ", ccLinkSupportsSingleModule = " ++ show ccLinkSupportsSingleModule
     , ", ccLinkIsGnu = " ++ show ccLinkIsGnu
     , "}"
     ]
@@ -66,12 +68,13 @@ findCcLink target ld progOpt ldOverride archOs cc readelf = checking "for C comp
   ccLinkSupportsNoPie         <- checkSupportsNoPie  cc ccLinkProgram
   ccLinkSupportsCompactUnwind <- checkSupportsCompactUnwind archOs cc ccLinkProgram
   ccLinkSupportsFilelist      <- checkSupportsFilelist cc ccLinkProgram
+  ccLinkSupportsSingleModule  <- checkSupportsSingleModule archOs cc ccLinkProgram
   ccLinkIsGnu                 <- checkLinkIsGnu archOs ccLinkProgram
   checkBfdCopyBug archOs cc readelf ccLinkProgram
   ccLinkProgram <- addPlatformDepLinkFlags archOs cc ccLinkProgram
   let ccLink = CcLink {ccLinkProgram, ccLinkSupportsNoPie,
                        ccLinkSupportsCompactUnwind, ccLinkSupportsFilelist,
-                       ccLinkIsGnu}
+                       ccLinkSupportsSingleModule, ccLinkIsGnu}
   ccLink <- linkRequiresNoFixupChains archOs cc ccLink
   ccLink <- linkRequiresNoWarnDuplicateLibraries archOs cc ccLink
   return ccLink
@@ -164,6 +167,35 @@ checkSupportsFilelist cc ccLink = checking "whether the cc linker understands -f
 
     return (isSuccess exitCode)
 
+-- | Check that the (darwin) linker supports @-single_module at .
+--
+-- In XCode 15, the linker warns when @-single_module@ is passed as the flag
+-- became the default and is now obsolete to pass.
+--
+-- We assume non-darwin linkers don't support this flag.
+checkSupportsSingleModule :: ArchOS -> Cc -> Program -> M Bool
+checkSupportsSingleModule archOs cc link
+  | ArchOS _ OSDarwin <- archOs
+  = checking "whether the darwin linker supports -single_module" $ do
+      withTempDir $ \dir -> do
+        let test_dylib = dir </> "test.dylib"
+            test_c     = dir </> "test.c"
+            testmain_o = dir </> "testmain.o"
+            testmain   = dir </> "testmain"
+
+        -- Main
+        compileC cc testmain_o "extern int foo(int); int main() { return foo(5); }"
+
+        -- Dynamic library
+        writeFile test_c "int foo(int x) { return x*x; }"
+        _ <- runProgram (ccProgram cc) ["-shared", "-o", test_dylib, test_c]
+
+        (_, out, err) <- readProgram link ["-Wl,-single_module", "-o", testmain, test_dylib, testmain_o]
+
+        return $ not $ "obsolete" `isInfixOf` err || "obsolete" `isInfixOf` out
+  | otherwise
+  = return False
+
 -- | Check whether linking works.
 checkLinkWorks :: Cc -> Program -> M ()
 checkLinkWorks cc ccLink = withTempDir $ \dir -> do



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/743bf658caf56283779aa7d4fb3a72680205ae12...b4a6d8c8be2834b9727af5412457892fb41d5040

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/743bf658caf56283779aa7d4fb3a72680205ae12...b4a6d8c8be2834b9727af5412457892fb41d5040
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/20231114/09c544fe/attachment-0001.html>


More information about the ghc-commits mailing list