[Git][ghc/ghc][wip/hadrian-windows-bindist-cross] 11 commits: Add same LD hack to ghc-toolchain

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Fri Aug 25 14:53:49 UTC 2023



Matthew Pickering pushed to branch wip/hadrian-windows-bindist-cross at Glasgow Haskell Compiler / GHC


Commits:
6cf18f0e by Matthew Pickering at 2023-08-25T15:53:26+01:00
Add same LD hack to ghc-toolchain

In the ./configure script, if you pass the `LD` variable then this has
the effect of stopping use searching for a linker and hence passing
`-fuse-ld=...`.

We want to emulate this logic in ghc-toolchain, if a use explicilty
specifies `LD` variable then don't add `-fuse-ld=..` with the goal of
making ./configure and ghc-toolchain agree on which flags to use when
using the C compiler as a linker.

This is quite unsavoury as we don't bake the choice of LD into the
configuration anywhere but what's important for now is making
ghc-toolchain and ./configure agree as much as possible.

See #23857 for more discussion

- - - - -
81191495 by Ben Gamari at 2023-08-25T15:53:26+01:00
ghc-toolchain: Check for C99 support with -std=c99

Previously we failed to try enabling C99 support with `-std=c99`, as
`autoconf` attempts. This broke on older compilers (e.g. CentOS 7) which
don't enable C99 by default.

Fixes #23879.

- - - - -
bfe0b030 by Matthew Pickering at 2023-08-25T15:53:26+01:00
ghc-toolchain: Add endianess check using __BYTE_ORDER__ macro

In very old toolchains the BYTE_ORDER macro is not set but thankfully
the __BYTE_ORDER__ macro can be used instead.

- - - - -
0009da3d by Matthew Pickering at 2023-08-25T15:53:26+01:00
configure: AC_PATH_TARGET_TOOL for LD

We want to make sure that LD is set to an absolute path in order to be
consistent with the `LD=$(command -v ld)` call. The AC_PATH_TARGET_TOOL
macro uses the absolute path rather than AC_CHECK_TARGET_TOOL which
might use a relative path.

- - - - -
00679395 by Matthew Pickering at 2023-08-25T15:53:26+01:00
ghc-toolchain: Check whether we need -std=gnu99 for CPP as well

In ./configure the C99 flag is passed to the C compiler when used as a C
preprocessor. So we also check the same thing in ghc-toolchain.

- - - - -
9a8d433d by Matthew Pickering at 2023-08-25T15:53:26+01:00
Check for --target linker flag separately to C compiler

There are situations where the C compiler doesn't accept `--target` but
when used as a linker it does (but doesn't do anything most likely)

In particular with old gcc toolchains, the C compiler doesn't support
--target but when used as a linker it does.

- - - - -
fe07dfe9 by Matthew Pickering at 2023-08-25T15:53:26+01:00
Use Cc to compile test file in nopie check

We were attempting to use the C compiler, as a linker, to compile a file
in the nopie check, but that won't work in general as the flags we pass
to the linker might not be compatible with the ones we pass when using
the C compiler.

- - - - -
e8b78dbe by Matthew Pickering at 2023-08-25T15:53:26+01:00
configure: Error when ghc-toolchain fails to compile

This is a small QOL change as if you are working on ghc-toolchain and it
fails to compile then configure will continue and can give you outdated
results.

- - - - -
7f28aa0f by Matthew Pickering at 2023-08-25T15:53:26+01:00
configure: Check whether -no-pie works when the C compiler is used as a linker

`-no-pie` is a flag we pass when using the C compiler as a linker (see
pieCCLDOpts in GHC.Driver.Session) so we should test whether the C
compiler used as a linker supports the flag, rather than just the C
compiler.

- - - - -
289ba78a by Matthew Pickering at 2023-08-25T15:53:26+01:00
ghc-toolchain: Remove javascript special case for --target detection

emcc when used as a linker seems to ignore the --target flag, and for
consistency with configure which now tests for --target, we remove this
special case.

- - - - -
892e1aeb by Matthew Pickering at 2023-08-25T15:53:26+01:00
hadrian: Don't pass LDFLAGS as a --configure-arg to cabal configure

We don't have anything sensible to set LDFLAGS to because the "linker"
flags we have are actually flags we pass to the C compiler when it's
used as a linker.

Likewise stop passing -gcc-options which mixed together linker flags and
non-linker flags. There's no guarantee the C compiler will accept both
of these in each mode.

- - - - -


12 changed files:

- configure.ac
- hadrian/src/Settings/Builders/Cabal.hs
- m4/find_merge_objects.m4
- m4/fp_cc_supports_target.m4
- m4/fp_gcc_supports_no_pie.m4
- + m4/fp_prog_cc_linker_target.m4
- m4/ghc_toolchain.m4
- utils/ghc-toolchain/exe/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/PlatformDetails.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs


Changes:

=====================================
configure.ac
=====================================
@@ -55,6 +55,8 @@ USER_CONF_CC_OPTS_STAGE2="$CONF_CC_OPTS_STAGE2"
 USER_CONF_CXX_OPTS_STAGE2="$CONF_CXX_OPTS_STAGE2"
 USER_CONF_GCC_LINKER_OPTS_STAGE2="$CONF_GCC_LINKER_OPTS_STAGE2"
 
+USER_LD="$LD"
+
 dnl ----------------------------------------------------------
 dnl ** Find unixy sort and find commands,
 dnl ** which are needed by FP_SETUP_PROJECT_VERSION
@@ -491,6 +493,7 @@ FP_PROG_LD_IS_GNU
 FP_PROG_LD_NO_COMPACT_UNWIND
 FP_PROG_LD_FILELIST
 
+
 dnl ** Which nm to use?
 dnl --------------------------------------------------------------
 FP_FIND_NM
@@ -615,8 +618,6 @@ dnl     If gcc, make sure it's at least 4.7
 dnl
 FP_GCC_VERSION
 
-dnl ** See whether cc supports -no-pie
-FP_GCC_SUPPORTS_NO_PIE
 
 dnl ** Check support for the extra flags passed by GHC when compiling via C
 FP_GCC_SUPPORTS_VIA_C_FLAGS
@@ -656,9 +657,15 @@ AC_SUBST(LlvmTarget)
 
 dnl ** See whether cc supports --target=<triple> and set
 dnl CONF_CC_OPTS_STAGE[012] accordingly.
-FP_CC_SUPPORTS_TARGET([$CC_STAGE0], [CONF_CC_OPTS_STAGE0], [CONF_CXX_OPTS_STAGE0], [CONF_GCC_LINKER_OPTS_STAGE0])
-FP_CC_SUPPORTS_TARGET([$CC], [CONF_CC_OPTS_STAGE1], [CONF_CXX_OPTS_STAGE1], [CONF_GCC_LINKER_OPTS_STAGE1])
-FP_CC_SUPPORTS_TARGET([$CC], [CONF_CC_OPTS_STAGE2], [CONF_CXX_OPTS_STAGE2], [CONF_GCC_LINKER_OPTS_STAGE2])
+FP_CC_SUPPORTS_TARGET([$CC_STAGE0], [CONF_CC_OPTS_STAGE0], [CONF_CXX_OPTS_STAGE0])
+FP_CC_SUPPORTS_TARGET([$CC], [CONF_CC_OPTS_STAGE1], [CONF_CXX_OPTS_STAGE1])
+FP_CC_SUPPORTS_TARGET([$CC], [CONF_CC_OPTS_STAGE2], [CONF_CXX_OPTS_STAGE2])
+
+FP_PROG_CC_LINKER_TARGET([CONF_CC_OPTS_STAGE1], [CONF_GCC_LINKER_OPTS_STAGE1])
+FP_PROG_CC_LINKER_TARGET([CONF_CC_OPTS_STAGE2], [CONF_GCC_LINKER_OPTS_STAGE2])
+
+dnl ** See whether cc used as a linker supports -no-pie
+FP_GCC_SUPPORTS_NO_PIE
 
 dnl Pass -Qunused-arguments or otherwise GHC will have very noisy invocations of Clang
 dnl TODO: Do we need -Qunused-arguments in CXX and GCC linker too?


=====================================
hadrian/src/Settings/Builders/Cabal.hs
=====================================
@@ -191,11 +191,8 @@ configureArgs cFlags' ldFlags' = do
                            , cFlags'
                            ]
         ldFlags  = ldArgs <> ldFlags'
-    cldFlags <- unwords <$> (cFlags <> ldFlags)
     mconcat
         [ conf "CFLAGS"   cFlags
-        , conf "LDFLAGS"  ldFlags
-        , not (null cldFlags) ? arg ("--gcc-options=" ++ cldFlags)
         , conf "--with-iconv-includes"    $ arg =<< getSetting IconvIncludeDir
         , conf "--with-iconv-libraries"   $ arg =<< getSetting IconvLibDir
         , conf "--with-gmp-includes"      $ arg =<< getSetting GmpIncludeDir


=====================================
m4/find_merge_objects.m4
=====================================
@@ -45,7 +45,7 @@ AC_DEFUN([FIND_MERGE_OBJECTS],[
       if test "$result" = "1"; then
           AC_MSG_NOTICE([$MergeObjsCmd is broken due to binutils 22266, looking for another linker...])
           MergeObjsCmd=""
-          AC_CHECK_TARGET_TOOL([MergeObjsCmd], [ld])
+          AC_PATH_TARGET_TOOL([MergeObjsCmd], [ld])
           CHECK_FOR_GOLD_T22266($MergeObjsCmd)
           if test "$result" = "1"; then
               AC_MSG_ERROR([Linker is affected by binutils 22266 but couldn't find another unaffected linker. Please set the MergeObjsCmd variable to a functional linker.])


=====================================
m4/fp_cc_supports_target.m4
=====================================
@@ -10,7 +10,6 @@
 # $1 = CC
 # $2 = CC_OPTS variable
 # $3 = CXX_OPTS variable
-# $4 = GCC_LINK_OPTS variable
 AC_DEFUN([FP_CC_SUPPORTS_TARGET],
 [
    AC_REQUIRE([GHC_LLVM_TARGET_SET_VAR])
@@ -28,7 +27,6 @@ AC_DEFUN([FP_CC_SUPPORTS_TARGET],
    if test $CONF_CC_SUPPORTS_TARGET = YES ; then
        $2="--target=$LlvmTarget $$2"
        $3="--target=$LlvmTarget $$3"
-       $4="--target=$LlvmTarget $$4"
    fi
 ])
 


=====================================
m4/fp_gcc_supports_no_pie.m4
=====================================
@@ -7,8 +7,9 @@ AC_DEFUN([FP_GCC_SUPPORTS_NO_PIE],
    AC_REQUIRE([AC_PROG_CC])
    AC_MSG_CHECKING([whether CC supports -no-pie])
    echo 'int main() { return 0; }' > conftest.c
+   "$CC" $CONF_GCC_CC_OPTS_STAGE2 -c conftest.c
    # Some GCC versions only warn when passed an unrecognized flag.
-   if $CC -no-pie -Werror -x c conftest.c -o conftest > conftest.txt 2>&1 && ! grep -i unrecognized conftest.txt > /dev/null 2>&1; then
+   if "$CC" $CONF_GCC_LINKER_OPTS_STAGE2 -no-pie -Werror conftest.o -o conftest > conftest.txt 2>&1 && ! grep -i unrecognized conftest.txt > /dev/null 2>&1; then
        CONF_GCC_SUPPORTS_NO_PIE=YES
        AC_MSG_RESULT([yes])
    else


=====================================
m4/fp_prog_cc_linker_target.m4
=====================================
@@ -0,0 +1,23 @@
+# FP_PROG_CC_LINKER_TARGET
+# -------------------
+# Check to see if the C compiler used as a linker supports `--target`
+#
+# $1 - Variable which contains the options passed to the C compiler when compiling a C file
+# $2 - Variable which contains the options passed to the C compiler when used as
+#      a linker
+AC_DEFUN([FP_PROG_CC_LINKER_TARGET],
+[
+    AC_MSG_CHECKING([whether $CC used as a linker understands --target])
+    echo 'int foo() { return 0; }' > conftest1.c
+    echo 'int main() { return 0; }' > conftest2.c
+    "${CC}" $$1 -c conftest1.c || AC_MSG_ERROR([Failed to compile conftest1.c])
+    "${CC}" $$1 -c conftest2.c || AC_MSG_ERROR([Failed to compile conftest2.c])
+    if "$CC" $$2 --target=$LlvmTarget -o conftest conftest1.o conftest2.o;
+    then
+        $2="--target=$LlvmTarget $$2"
+        AC_MSG_RESULT([yes])
+    else
+        AC_MSG_RESULT([no])
+    fi
+    rm -rf conftest*
+])# FP_PROG_CC_LINKER_TARGET


=====================================
m4/ghc_toolchain.m4
=====================================
@@ -106,6 +106,10 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN],
     echo "--readelf=$READELF" >> acargs
     echo "--windres=$WindresCmd" >> acargs
 
+    if test -n "$USER_LD"; then
+      echo "--ld=$USER_LD" >> acargs
+    fi
+
     ENABLE_GHC_TOOLCHAIN_NOT_ARG([locally-executable], [$CrossCompiling])
     ENABLE_GHC_TOOLCHAIN_ARG([unregisterised], [$Unregisterised])
     ENABLE_GHC_TOOLCHAIN_ARG([tables-next-to-code], [$TablesNextToCode])
@@ -144,7 +148,7 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN_BIN],[
                 -ilibraries/ghc-platform/src -iutils/ghc-toolchain/src \
                 -XNoImplicitPrelude \
                 -odir actmp-ghc-toolchain -hidir actmp-ghc-toolchain \
-                utils/ghc-toolchain/exe/Main.hs -o acghc-toolchain
+                utils/ghc-toolchain/exe/Main.hs -o acghc-toolchain || AC_MSG_ERROR([Could not compile ghc-toolchain])
             GHC_TOOLCHAIN_BIN="./acghc-toolchain"
             ;;
         *)


=====================================
utils/ghc-toolchain/exe/Main.hs
=====================================
@@ -50,6 +50,9 @@ data Opts = Opts
     , optReadelf   :: ProgOpt
     , optMergeObjs :: ProgOpt
     , optWindres   :: ProgOpt
+    -- Note we don't actually configure LD into anything but
+    -- see #23857 and #22550 for the very unfortunate story.
+    , optLd        :: ProgOpt
     , optUnregisterised :: Maybe Bool
     , optTablesNextToCode :: Maybe Bool
     , optUseLibFFIForAdjustors :: Maybe Bool
@@ -92,6 +95,7 @@ emptyOpts = Opts
     , optReadelf   = po0
     , optMergeObjs = po0
     , optWindres   = po0
+    , optLd        = po0
     , optUnregisterised = Nothing
     , optTablesNextToCode = Nothing
     , optUseLibFFIForAdjustors = Nothing
@@ -103,7 +107,7 @@ emptyOpts = Opts
     po0 = emptyProgOpt
 
 _optCc, _optCxx, _optCpp, _optHsCpp, _optCcLink, _optAr, _optRanlib, _optNm,
-    _optReadelf, _optMergeObjs, _optWindres
+    _optReadelf, _optMergeObjs, _optWindres, _optLd
     :: Lens Opts ProgOpt
 _optCc      = Lens optCc      (\x o -> o {optCc=x})
 _optCxx     = Lens optCxx     (\x o -> o {optCxx=x})
@@ -116,6 +120,7 @@ _optNm      = Lens optNm      (\x o -> o {optNm=x})
 _optReadelf = Lens optReadelf (\x o -> o {optReadelf=x})
 _optMergeObjs = Lens optMergeObjs (\x o -> o {optMergeObjs=x})
 _optWindres = Lens optWindres (\x o -> o {optWindres=x})
+_optLd = Lens optLd (\x o -> o {optLd= x})
 
 _optTriple :: Lens Opts String
 _optTriple = Lens optTriple (\x o -> o {optTriple=x})
@@ -170,6 +175,7 @@ options =
     , progOpts "readelf" "readelf utility" _optReadelf
     , progOpts "merge-objs" "linker for merging objects" _optMergeObjs
     , progOpts "windres" "windres utility" _optWindres
+    , progOpts "ld" "linker" _optLd
     ]
   where
     progOpts :: String -> String -> Lens Opts ProgOpt -> [OptDescr (Opts -> Opts)]
@@ -381,7 +387,7 @@ mkTarget opts = do
     (archOs, tgtVendor) <- parseTriple cc0 normalised_triple
     cc <- addPlatformDepCcFlags archOs cc0
     readelf <- optional $ findReadelf (optReadelf opts)
-    ccLink <- findCcLink tgtLlvmTarget (optCcLink opts) (ldOverrideWhitelist archOs && fromMaybe True (optLdOverride opts)) archOs cc readelf
+    ccLink <- findCcLink tgtLlvmTarget (optLd opts) (optCcLink opts) (ldOverrideWhitelist archOs && fromMaybe True (optLdOverride opts)) archOs cc readelf
 
     ar <- findAr tgtVendor (optAr opts)
     -- TODO: We could have


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/PlatformDetails.hs
=====================================
@@ -46,7 +46,7 @@ checkWordSize cc = checking "word size" $ do
 
 checkEndianness :: Cc -> M Endianness
 checkEndianness cc = do
-    checkEndiannessParamH cc <|> checkEndiannessLimitsH cc
+    checkEndiannessParamH cc <|> checkEndiannessLimitsH cc <|> checkEndianness__BYTE_ORDER__ cc
 
 checkEndiannessParamH :: Cc -> M Endianness
 checkEndiannessParamH cc = checking "endianness (param.h)" $ do
@@ -92,6 +92,28 @@ checkEndiannessLimitsH cc = checking "endianness (limits.h)" $ do
         , "#endif"
         ]
 
+checkEndianness__BYTE_ORDER__ :: Cc -> M Endianness
+checkEndianness__BYTE_ORDER__ cc = checking "endianness (__BYTE_ORDER__)" $ do
+    out <- preprocess cc prog
+    case reverse $ lines out of
+      "big":_ -> return BigEndian
+      "little":_ -> return LittleEndian
+      "unknown":_ -> throwE "unknown endianness"
+      _ -> throwE "unrecognized output"
+  where
+    prog = unlines
+        [ "#include <sys/param.h>"
+        , "#if __BYTE_ORDER__ == __ORDER_LITTLE_ENDIAN__"
+        , "little"
+        , "#elif __BYTE_ORDER__ == __ORDER_BIG_ENDIAN__"
+        , "big"
+        , "#else"
+        , "unknown"
+        , "#endif"
+        ]
+
+
+
 checkLeadingUnderscore :: Cc -> Nm -> M Bool
 checkLeadingUnderscore cc nm = checking ctxt $ withTempDir $ \dir -> do
     let test_o = dir </> "test.o"


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
=====================================
@@ -10,6 +10,7 @@ module GHC.Toolchain.Tools.Cc
     , compileC
     , compileAsm
     , addPlatformDepCcFlags
+    , checkC99Support
     ) where
 
 import Control.Monad
@@ -39,12 +40,15 @@ findCc llvmTarget progOpt = checking "for C compiler" $ do
     -- there's a more optimal one
     ccProgram <- findProgram "C compiler" progOpt ["gcc", "clang", "cc"]
 
-    cc' <- ignoreUnusedArgs $ Cc {ccProgram}
-    cc  <- ccSupportsTarget llvmTarget cc'
-    checking "whether Cc works" $ checkCcWorks cc
-    checkC99Support cc
-    checkCcSupportsExtraViaCFlags cc
-    return cc
+    cc0 <- ignoreUnusedArgs $ Cc {ccProgram}
+    cc1 <- ccSupportsTarget llvmTarget cc0
+    checking "whether Cc works" $ checkCcWorks cc1
+    cc2 <- oneOf "cc doesn't support C99" $ map checkC99Support
+        [ cc1
+        , cc1 & _ccFlags %++ "-std=gnu99"
+        ]
+    checkCcSupportsExtraViaCFlags cc2
+    return cc2
 
 checkCcWorks :: Cc -> M ()
 checkCcWorks cc = withTempDir $ \dir -> do
@@ -75,7 +79,7 @@ ccSupportsTarget :: String -> Cc -> M Cc
 ccSupportsTarget target cc = checking "whether Cc supports --target" $
                              supportsTarget _ccProgram checkCcWorks target cc
 
-checkC99Support :: Cc -> M ()
+checkC99Support :: Cc -> M Cc
 checkC99Support cc = checking "for C99 support" $ withTempDir $ \dir -> do
     let test_o = dir </> "test.o"
     compileC cc test_o $ unlines
@@ -84,6 +88,7 @@ checkC99Support cc = checking "for C99 support" $ withTempDir $ \dir -> do
         , "# error \"Compiler does not advertise C99 conformance\""
         , "#endif"
         ]
+    return cc
 
 checkCcSupportsExtraViaCFlags :: Cc -> M ()
 checkCcSupportsExtraViaCFlags cc = checking "whether cc supports extra via-c flags" $ withTempDir $ \dir -> do


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs
=====================================
@@ -10,7 +10,7 @@ import GHC.Toolchain.Prelude
 import GHC.Toolchain.Program
 
 import GHC.Toolchain.Tools.Cc
-import GHC.Toolchain.Utils (withTempDir)
+import GHC.Toolchain.Utils (withTempDir, oneOf)
 
 newtype Cpp = Cpp { cppProgram :: Program
                     }
@@ -83,7 +83,12 @@ findCpp :: ProgOpt -> Cc -> M Cpp
 findCpp progOpt cc = checking "for C preprocessor" $ do
   -- Use the specified CPP or try to use the c compiler
   foundCppProg <- findProgram "C preprocessor" progOpt [] <|> pure (programFromOpt progOpt (prgPath $ ccProgram cc) [])
+  -- Check whether the C preprocessor needs -std=gnu99 (only very old toolchains need this)
+  Cc cpp2 <- oneOf "cc doesn't support C99" $ map checkC99Support
+        [ Cc foundCppProg
+        , Cc (foundCppProg & _prgFlags %++ "-std=gnu99")
+        ]
   -- Always add the -E flag to the CPP, regardless of the user options
-  let cppProgram = addFlagIfNew "-E" foundCppProg
+  let cppProgram = addFlagIfNew "-E" cpp2
   return Cpp{cppProgram}
 


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
=====================================
@@ -42,21 +42,28 @@ _ccLinkProgram :: Lens CcLink Program
 _ccLinkProgram = Lens ccLinkProgram (\x o -> o{ccLinkProgram=x})
 
 findCcLink :: String -- ^ The llvm target to use if CcLink supports --target
+           -> ProgOpt
            -> ProgOpt
            -> Bool   -- ^ Whether we should search for a more efficient linker
            -> ArchOS -> Cc -> Maybe Readelf -> M CcLink
-findCcLink target progOpt ldOverride archOs cc readelf = checking "for C compiler for linking command" $ do
+findCcLink target ld progOpt ldOverride archOs cc readelf = checking "for C compiler for linking command" $ do
   -- Use the specified linker or try using the C compiler
   rawCcLink <- findProgram "C compiler for linking" progOpt [] <|> pure (programFromOpt progOpt (prgPath $ ccProgram cc) [])
-  ccLinkProgram <- case poFlags progOpt of
-                     Just _ ->
+  -- See #23857 for why we check to see if LD is set here
+  -- TLDR: If the user explicitly sets LD then in ./configure
+  -- we don't perform a linker search (and set -fuse-ld), so
+  -- we do the same here for consistency.
+  ccLinkProgram <- case (poPath ld, poFlags progOpt) of
+                     (_, Just _) ->
                          -- If the user specified linker flags don't second-guess them
                          pure rawCcLink
-                     Nothing -> do
+                     (Just {}, _) ->
+                         pure rawCcLink
+                     _ -> do
                          -- If not then try to find decent linker flags
                          findLinkFlags ldOverride cc rawCcLink <|> pure rawCcLink
-  ccLinkProgram <- linkSupportsTarget archOs cc target ccLinkProgram
-  ccLinkSupportsNoPie         <- checkSupportsNoPie  ccLinkProgram
+  ccLinkProgram <- linkSupportsTarget cc target ccLinkProgram
+  ccLinkSupportsNoPie         <- checkSupportsNoPie  cc ccLinkProgram
   ccLinkSupportsCompactUnwind <- checkSupportsCompactUnwind archOs cc ccLinkProgram
   ccLinkSupportsFilelist      <- checkSupportsFilelist cc ccLinkProgram
   ccLinkIsGnu                 <- checkLinkIsGnu archOs ccLinkProgram
@@ -87,13 +94,10 @@ findLinkFlags enableOverride cc ccLink
   | otherwise =
     return ccLink
 
-linkSupportsTarget :: ArchOS -> Cc -> String -> Program -> M Program
+linkSupportsTarget :: Cc -> String -> Program -> M Program
 -- Javascript toolchain provided by emsdk just ignores --target flag so
 -- we have this special case to match with ./configure (#23744)
-linkSupportsTarget archOS _ _ c
-  | ArchJavaScript <- archOS_arch archOS
-  = return c
-linkSupportsTarget _ cc target link
+linkSupportsTarget cc target link
   = checking "whether cc linker supports --target" $
     supportsTarget (Lens id const) (checkLinkWorks cc) target link
 
@@ -112,16 +116,15 @@ doLinkerSearch = False
 #endif
 
 -- | See Note [No PIE when linking] in GHC.Driver.Session
-checkSupportsNoPie :: Program -> M Bool
-checkSupportsNoPie ccLink = checking "whether the cc linker supports -no-pie" $
+checkSupportsNoPie :: Cc -> Program -> M Bool
+checkSupportsNoPie cc ccLink = checking "whether the cc linker supports -no-pie" $
   withTempDir $ \dir -> do
-    let test_c = dir </> "test.c"
-    writeFile test_c "int main() { return 0; }"
-
+    let test_o  = dir </> "test.o"
     let test = dir </> "test"
+    compileC cc test_o "int main() { return 0; }"
     -- Check output as some GCC versions only warn and don't respect -Werror
     -- when passed an unrecognized flag.
-    (code, out, err) <- readProgram ccLink ["-no-pie", "-Werror", "-x", "c", test_c, "-o", test]
+    (code, out, err) <- readProgram ccLink ["-no-pie", "-Werror", test_o, "-o", test]
     return (isSuccess code && not ("unrecognized" `isInfixOf` out) && not ("unrecognized" `isInfixOf` err))
 
 -- ROMES:TODO: This check is wrong here and in configure because with ld.gold parses "-n" "o_compact_unwind"



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/eda0a2bea4ab630f6df1d76fd9779dea2ad589e9...892e1aeb3543cc95259976a95f07a7ad86e36100

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/eda0a2bea4ab630f6df1d76fd9779dea2ad589e9...892e1aeb3543cc95259976a95f07a7ad86e36100
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/20230825/b8059090/attachment-0001.html>


More information about the ghc-commits mailing list