[Git][ghc/ghc][wip/toolchain-selection] 6 commits: Fixes

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Tue Jun 20 11:41:00 UTC 2023



Rodrigo Mesquita pushed to branch wip/toolchain-selection at Glasgow Haskell Compiler / GHC


Commits:
87c9832e by Rodrigo Mesquita at 2023-06-20T12:09:49+01:00
Fixes

- - - - -
aab272d5 by Rodrigo Mesquita at 2023-06-20T12:09:49+01:00
ghc-toolchain: Fix check for gold bug

- - - - -
7c2492b9 by Rodrigo Mesquita at 2023-06-20T12:09:49+01:00
ghc-toolchain: set CC LD plat. dependent flags

A lot to be said about this approach, we might want to re-do this all
eventually...
Perhaps I ought to add a TODO at the top level of these functions?

We might also not do it altogether, some of these might be outdated?

- - - - -
294f77f9 by Rodrigo Mesquita at 2023-06-20T12:09:49+01:00
Configure -Wl,--no-as-needed

- - - - -
5a25fede by Rodrigo Mesquita at 2023-06-20T12:09:49+01:00
ghc-toolchain: configure linker options correctly

- - - - -
d179661e by Rodrigo Mesquita at 2023-06-20T12:40:48+01:00
Revert LLVMTarget deletion in mkprojectmkin

- - - - -


8 changed files:

- distrib/configure.ac.in
- + m4/fp_link_supports_no_as_needed.m4
- m4/fptools_set_c_ld_flags.m4
- mk/project.mk.in
- utils/ghc-toolchain/src/GHC/Toolchain/Lens.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/MergeObjs.hs


Changes:

=====================================
distrib/configure.ac.in
=====================================
@@ -286,6 +286,7 @@ AC_SUBST(UseLibdw)
 FP_SETTINGS
 
 AC_CONFIG_FILES([config.mk])
+#ROMES:TODO AC_CONFIG_FILES([default.target])
 AC_OUTPUT
 
 # We get caught by


=====================================
m4/fp_link_supports_no_as_needed.m4
=====================================
@@ -0,0 +1,22 @@
+# FP_LINK_SUPPORTS_NO_AS_NEEDED
+# ----------------------------------
+# Set the Cc linker flag -Wl,--no-as-needed if it is supported
+# $1 is the name of the linker flags variable when linking with gcc
+# See also Note [ELF needed shared libs]
+AC_DEFUN([FP_LINK_SUPPORTS_NO_AS_NEEDED],
+[
+    AC_MSG_CHECKING([whether Cc linker supports -Wl,--no-as-needed])
+    echo 'int f(int a) {return 2*a;}' > conftest.a.c
+    echo 'int f(int a); int main(int argc, char **argv) {return f(0);}' > conftest.b.c
+    $CC -o conftest.a.o conftest.a.c
+    $CC -o conftest.b.o conftest.b.c
+    if $CC $$1 -Wl,--no-as-needed -o conftest conftest.a.o conftest.b.o > /dev/null 2>&1
+    then
+        $1="$$1 -Wl,--no-as-needed"
+        AC_MSG_RESULT([yes])
+    else
+        AC_MSG_RESULT([no])
+    fi
+    rm -f conftest*
+])
+


=====================================
m4/fptools_set_c_ld_flags.m4
=====================================
@@ -17,6 +17,12 @@ AC_DEFUN([FPTOOLS_SET_C_LD_FLAGS],
         ;;
     esac
 
+    case $$1 in
+    *-linux)
+        FP_LINK_SUPPORTS_NO_AS_NEEDED([$3])
+        ;;
+    esac
+
     case $$1 in
     i386-unknown-mingw32)
         $2="$$2 -march=i686"


=====================================
mk/project.mk.in
=====================================
@@ -94,6 +94,7 @@ TargetPlatform_CPP      = @TargetPlatform_CPP@
 TargetArch_CPP          = @TargetArch_CPP@
 TargetOS_CPP            = @TargetOS_CPP@
 TargetVendor_CPP        = @TargetVendor_CPP@
+LLVMTarget_CPP          = @LLVMTarget_CPP@
 
 BuildPlatform_CPP       = @BuildPlatform_CPP@
 BuildArch_CPP           = @BuildArch_CPP@


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Lens.hs
=====================================
@@ -3,9 +3,12 @@ module GHC.Toolchain.Lens
     ( Lens(..)
     , (%)
     , over
+    , (%++)
+    , (&)
     ) where
 
-import Prelude ((.), ($))
+import Prelude ((.), ($), (++))
+import Data.Function ((&))
 
 data Lens a b = Lens { view :: (a -> b), set :: (b -> a -> a) }
 
@@ -17,3 +20,11 @@ a % b = Lens { view = view b . view a
 over :: Lens a b -> (b -> b) -> a -> a
 over l f x = set l (f $ view l x) x
 
+-- | Append @b@ to @[b]@
+--
+-- Example usage:
+-- @@
+-- cc & _ccProgram % _prgFlags %++ "-U__i686"
+-- @@
+(%++) :: Lens a [b] -> b -> (a -> a)
+(%++) l el = over l (++[el])


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
=====================================
@@ -1,4 +1,5 @@
 {-# LANGUAGE NamedFieldPuns #-}
+{-# LANGUAGE ViewPatterns #-}
 
 module GHC.Toolchain.Tools.Cc
     ( Cc(..)
@@ -28,6 +29,9 @@ newtype Cc = Cc { ccProgram :: Program
 _ccProgram :: Lens Cc Program
 _ccProgram = Lens ccProgram (\x o -> o{ccProgram=x})
 
+_ccFlags :: Lens Cc [String]
+_ccFlags = _ccProgram % _prgFlags
+
 findCc :: String -- ^ The llvm target to use if Cc supports --target
        -> ProgOpt -> M Cc
 findCc llvmTarget progOpt = checking "for C compiler" $ do
@@ -57,10 +61,10 @@ checkCcWorks cc = withTempDir $ \dir -> do
 -- these. See #11684.
 ignoreUnusedArgs :: Cc -> M Cc
 ignoreUnusedArgs cc
-  | "-Qunused-arguments" `elem` (view (_ccProgram % _prgFlags) cc) = return cc
+  | "-Qunused-arguments" `elem` (view _ccFlags cc) = return cc
   | otherwise
   = checking "for -Qunused-arguments support" $ do
-      let cc' = over (_ccProgram % _prgFlags) (++["-Qunused-arguments"]) cc
+      let cc' = cc & _ccFlags %++ "-Qunused-arguments"
       (cc' <$ checkCcWorks cc') <|> return cc
 
 -- Does Cc support the --target=<triple> option? If so, we should pass it
@@ -124,8 +128,51 @@ compileAsm = compile "S" ["-c"] _ccProgram
 -- | Add various platform-dependent compiler flags needed by GHC. We can't do
 -- this in `findCc` since we need a 'Cc` to determine the 'ArchOS'.
 addPlatformDepCcFlags :: ArchOS -> Cc -> M Cc
-addPlatformDepCcFlags archOs cc
-  | OSMinGW32 <- archOS_OS archOs = do
+addPlatformDepCcFlags archOs cc0 = do
+  let cc1 = addWorkaroundFor7799 archOs cc0
+  cc2 <- addOSMinGW32CcFlags archOs cc1
+  -- As per FPTOOLS_SET_C_LD_FLAGS
+  case archOs of
+    ArchOS ArchX86 OSMinGW32 ->
+      return $ cc2 & _ccFlags %++ "-march=i686"
+    ArchOS ArchX86 OSFreeBSD ->
+      return $ cc2 & _ccFlags %++ "-march=i686"
+    ArchOS ArchX86_64 OSSolaris2 ->
+      -- Solaris is a multi-lib platform, providing both 32- and 64-bit
+      -- user-land. It appears to default to 32-bit builds but we of course want to
+      -- compile for 64-bits on x86-64.
+      return $ cc2 & _ccFlags %++ "-m64"
+    ArchOS ArchAlpha _ ->
+      -- For now, to suppress the gcc warning "call-clobbered
+      -- register used for global register variable", we simply
+      -- disable all warnings altogether using the -w flag. Oh well.
+      return $ cc2 & over _ccFlags (++["-w","-mieee","-D_REENTRANT"])
+    -- ArchOS ArchHPPA? _ ->
+    ArchOS ArchARM{} OSFreeBSD ->
+      -- On arm/freebsd, tell gcc to generate Arm
+      -- instructions (ie not Thumb).
+      return $ cc2 & _ccFlags %++ "-marm"
+    ArchOS ArchARM{} OSLinux ->
+      -- On arm/linux and arm/android, tell gcc to generate Arm
+      -- instructions (ie not Thumb).
+      return $ cc2 & _ccFlags %++ "-marm"
+    ArchOS ArchPPC OSAIX ->
+      -- We need `-D_THREAD_SAFE` to unlock the thread-local `errno`.
+      return $ cc2 & _ccFlags %++ "-D_THREAD_SAFE"
+    _ ->
+      return cc2
+
+
+-- | Workaround for #7799
+addWorkaroundFor7799 :: ArchOS -> Cc -> Cc
+addWorkaroundFor7799 archOs cc
+  | ArchX86 <- archOS_arch archOs = cc & _ccFlags %++ "-U__i686"
+  | otherwise = cc
+
+-- | Adds flags specific to mingw32
+addOSMinGW32CcFlags :: ArchOS -> Cc -> M Cc
+addOSMinGW32CcFlags archOs cc
+  | ArchOS _ OSMinGW32 <- archOs = do
       checkFStackCheck cc <|> throwE "Windows requires -fstack-check support yet the C compiler appears not to support it"
   | otherwise = return cc
 
@@ -133,7 +180,7 @@ addPlatformDepCcFlags archOs cc
 -- See Note [Windows stack allocations].
 checkFStackCheck :: Cc -> M Cc
 checkFStackCheck cc = withTempDir $ \dir -> checking "that -fstack-check works" $ do
-      let cc' = over (_ccProgram % _prgFlags) (++["-Wl,-fstack-checkzz"]) cc
+      let cc' = cc & _ccFlags %++ "-Wl,-fstack-checkzz"
       compileC cc' (dir </> "test.o") "int main(int argc, char **argv) { return 0; }"
       return cc'
 


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
=====================================
@@ -128,16 +128,13 @@ checkSupportsNoPie ccLink = checking "whether the cc linker supports -no-pie" $
 
 checkSupportsCompactUnwind :: Cc -> Program -> M Bool
 checkSupportsCompactUnwind cc ccLink = checking "whether the cc linker understands -no_compact_unwind" $
-  -- ROMES:TODO: This returns False here but True in configure because in
-  -- configure we check for ld supports compact unwind, whereas here we check
-  -- for cclink supports compact unwind... what do we need it for?
   withTempDir $ \dir -> do
     let test_o  = dir </> "test.o"
         test2_o = dir </> "test2.o"
 
     compileC cc test_o "int foo() { return 0; }"
 
-    exitCode <- runProgram ccLink ["-r", "-no_compact_unwind", "-o", test2_o, test_o]
+    exitCode <- runProgram ccLink ["-r", "-Wl,-no_compact_unwind", "-o", test2_o, test_o]
     return $ isSuccess exitCode
 
 checkSupportsFilelist :: Cc -> Program -> M Bool
@@ -154,14 +151,12 @@ checkSupportsFilelist cc ccLink = checking "whether the cc linker understands -f
     --  write the filenames test1_o and test2_o to the test_ofiles file
     writeFile  test_ofiles (unlines [test1_o,test2_o])
 
-    exitCode <- runProgram ccLink ["-r", "-filelist", test_ofiles, "-o", test_o]
+    exitCode <- runProgram ccLink ["-r", "-Wl,-filelist", test_ofiles, "-o", test_o]
 
     return (isSuccess exitCode)
 
 checkSupportsResponseFiles :: Cc -> Program -> M Bool
 checkSupportsResponseFiles cc ccLink = checking "whether the cc linker supports response files" $
-  -- ROMES:TODO: This returns True here while False in configure because in
-  -- configure we call -shared and -dylib on LD, whereas here we do it on CcLink
   withTempDir $ \dir -> do
     let test_o = dir </> "test.o"
     compileC cc test_o "int main(void) {return 0;}"
@@ -170,6 +165,9 @@ checkSupportsResponseFiles cc ccLink = checking "whether the cc linker supports
         out      = dir </> "test"
     writeFile args_txt (unlines ["-o", out, test_o])
 
+    -- ROMES:TODO: Should we run this with -Wl?
+    -- In clang, -shared seems to exist as an argument to cc but not to -Wl,
+    -- while -dylib works for both
     -- TODO: It'd be good to shortcircuit this logical `or`
     exitCode1 <- runProgram ccLink ["-shared", "@"++args_txt]
     exitCode2 <- runProgram ccLink ["-dylib", "@"++args_txt]
@@ -189,7 +187,7 @@ checkLinkWorks cc ccLink = withTempDir $ \dir -> do
 
 checkLinkIsGnu :: Program -> M Bool
 checkLinkIsGnu ccLink = do
-  out <- readProgramStdout ccLink ["--version"]
+  out <- readProgramStdout ccLink ["-Wl,--version"]
   return ("GNU" `isInfixOf` out)
 
 -- | Check for binutils bug #16177 present in some versions of the bfd ld
@@ -260,13 +258,52 @@ The flag is only needed on ELF systems. On Windows (PE) and Mac OS X
 
 -- | Add various platform-dependent flags needed for reliable linking.
 addPlatformDepLinkFlags :: ArchOS -> Cc -> Program -> M Program
-addPlatformDepLinkFlags archOs cc ccLink
+addPlatformDepLinkFlags archOs cc ccLink0 = do
+  ccLink1 <- addNoAsNeeded archOs cc ccLink0
+  -- As per FPTOOLS_SET_C_LD_FLAGS
+  case archOs of
+    -- ROMES:TODO: Consider dropping this alongside other configuration for solaris that was dropped
+    ArchOS ArchX86_64 OSSolaris2 ->
+      -- Solaris is a multi-lib platform, providing both 32- and 64-bit
+      -- user-land. It appears to default to 32-bit builds but we of course want to
+      -- compile for 64-bits on x86-64.
+      --
+      -- On OpenSolaris uses gnu ld whereas SmartOS appears to use the Solaris
+      -- implementation, which rather uses the -64 flag.
+      return $ ccLink1 & _prgFlags %++ "-m64"
+    ArchOS ArchAlpha _ ->
+      -- For now, to suppress the gcc warning "call-clobbered
+      -- register used for global register variable", we simply
+      -- disable all warnings altogether using the -w flag. Oh well.
+      return $ ccLink1 & over _prgFlags (++["-w","-mieee","-D_REENTRANT"])
+    -- ArchOS ArchHPPA? _ ->
+    ArchOS ArchARM{} OSFreeBSD ->
+      -- On arm/freebsd, tell gcc to generate Arm
+      -- instructions (ie not Thumb).
+      return $ ccLink1 & _prgFlags %++ "-Wl,-z,noexecstack"
+    ArchOS ArchARM{} OSLinux ->
+      -- On arm/linux and arm/android, tell gcc to generate Arm
+      -- instructions (ie not Thumb).
+      return $ ccLink1 & _prgFlags %++ "-Wl,-z,noexecstack"
+    ArchOS ArchAArch64 OSFreeBSD ->
+      return $ ccLink1 & _prgFlags %++ "-Wl,-z,noexecstack"
+    ArchOS ArchAArch64 OSLinux ->
+      return $ ccLink1 & _prgFlags %++ "-Wl,-z,noexecstack"
+    ArchOS ArchAArch64 OSNetBSD ->
+      return $ ccLink1 & _prgFlags %++ "-Wl,-z,noexecstack"
+    ArchOS ArchPPC OSAIX ->
+      -- We need `-D_THREAD_SAFE` to unlock the thread-local `errno`.
+      return $ ccLink1 & over _prgFlags (++["-D_THREAD_SAFE","-Wl,-bnotextro"])
+    _ ->
+      return ccLink1
+
+-- | See Note [ELF needed shared libs]
+addNoAsNeeded :: ArchOS -> Cc -> Program -> M Program
+addNoAsNeeded archOs cc ccLink
   | OSLinux <- archOS_OS archOs = checking "that --no-as-needed works" $ do
-      -- | See Note [ELF needed shared libs]
       let ccLink' = over _prgFlags (++["-Wl,--no-as-needed"]) ccLink
       checkLinkWorks cc ccLink'
       return ccLink'
-
   | otherwise = return ccLink
 
 -- See if whether we are using a version of ld64 on darwin platforms which


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/MergeObjs.hs
=====================================
@@ -4,10 +4,8 @@
 module GHC.Toolchain.Tools.MergeObjs ( MergeObjs(..), findMergeObjs ) where
 
 import Control.Monad
-import Control.Monad.IO.Class
 import Data.List
 import System.FilePath
-import System.Process
 
 import GHC.Toolchain.Prelude
 import GHC.Toolchain.Utils
@@ -23,7 +21,7 @@ newtype MergeObjs = MergeObjs { mergeObjsProgram :: Program
 
 findMergeObjs :: ProgOpt -> Cc -> CcLink -> Nm -> M MergeObjs
 findMergeObjs progOpt cc ccLink nm = checking "for linker for merging objects" $ do
-    prog <- findProgram "linker for merging objects" progOpt ["ld"]
+    prog <- findProgram "linker for merging objects" progOpt ["ld.gold", "ld"]
     let mo = MergeObjs $ over _prgFlags (++["-r"]) prog
     checkMergingWorks cc nm mo
     checkForGoldT22266 cc ccLink mo
@@ -63,11 +61,11 @@ checkForGoldT22266 cc ccLink mergeObjs = do
             compileC cc a_o progA
             writeFile link_script ldScript
             callProgram (mergeObjsProgram mergeObjs)
-                ["-T", link_script, "-o", merged_o]
+                ["-T", link_script, a_o, "-o", merged_o]
             compileC cc main_o progMain
             callProgram (ccLinkProgram ccLink)
                 ["-o", exe, merged_o, main_o]
-            liftIO $ callProcess exe []
+            callProgram (Program exe []) []
 
     progA = unlines
         [ "__attribute__((section(\".data.a\")))"



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/eb5f75b94d6ef12e096f8be75a74dc6da7ad27b1...d179661ef6c07326c7c811376371065bbb9351b4

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/eb5f75b94d6ef12e096f8be75a74dc6da7ad27b1...d179661ef6c07326c7c811376371065bbb9351b4
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/20230620/5064eacc/attachment-0001.html>


More information about the ghc-commits mailing list