[Git][ghc/ghc][wip/toolchain-selection] ghc-toolchain: set CC LD plat. dependent flags

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Mon Jun 19 14:39:40 UTC 2023



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


Commits:
eb5f75b9 by Rodrigo Mesquita at 2023-06-19T15:39:29+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?

- - - - -


4 changed files:

- 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:

=====================================
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,50 @@ 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
+  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 +179,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
=====================================
@@ -260,13 +260,51 @@ 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
+  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
+
+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



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eb5f75b94d6ef12e096f8be75a74dc6da7ad27b1
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/20230619/6ba5ab25/attachment-0001.html>


More information about the ghc-commits mailing list