[Git][ghc/ghc][wip/hadrian-windows-bindist-cross] toolchain: Don't pass --target to emscripten toolchain

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Mon Oct 2 20:37:20 UTC 2023



Ben Gamari pushed to branch wip/hadrian-windows-bindist-cross at Glasgow Haskell Compiler / GHC


Commits:
40b264e8 by Ben Gamari at 2023-10-02T16:37:10-04:00
toolchain: Don't pass --target to emscripten toolchain

As noted in `Note [Don't pass --target to emscripten toolchain]`,
emscripten's `emcc` is rather inconsistent with respect to its treatment
of the `--target` flag. Avoid this by special-casing this toolchain
in the `configure` script and `ghc-toolchain`.

Fixes on aspect of #23744.

- - - - -


7 changed files:

- m4/fp_cc_supports_target.m4
- m4/fp_prog_cc_linker_target.m4
- utils/ghc-toolchain/exe/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Program.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cxx.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs


Changes:

=====================================
m4/fp_cc_supports_target.m4
=====================================
@@ -14,8 +14,13 @@ AC_DEFUN([FP_CC_SUPPORTS_TARGET],
 [
    AC_REQUIRE([GHC_LLVM_TARGET_SET_VAR])
    AC_MSG_CHECKING([whether $1 supports --target])
+
    echo 'int main() { return 0; }' > conftest.c
-   if $1 --target=$LlvmTarget -Werror conftest.c > /dev/null 2>&1 ; then
+   if test "$target_cpu" = "javascript" ; then
+       # See Note [Don't pass --target to emscripten toolchain] in GHC.Toolchain.Program
+       CONF_CC_SUPPORTS_TARGET=NO
+       AC_MSG_RESULT([no])
+   elif $1 --target=$LlvmTarget -Werror conftest.c > /dev/null 2>&1 ; then
        CONF_CC_SUPPORTS_TARGET=YES
        AC_MSG_RESULT([yes])
    else


=====================================
m4/fp_prog_cc_linker_target.m4
=====================================
@@ -8,11 +8,18 @@
 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;
+
+    if test "$target_cpu" = "javascript"
+    then
+        # See Note [Don't pass --target to emscripten toolchain] in GHC.Toolchain.Program
+        CONF_CC_SUPPORTS_TARGET=NO
+        AC_MSG_RESULT([no])
+    elif "$CC" $$2 --target=$LlvmTarget -o conftest conftest1.o conftest2.o;
     then
         $2="--target=$LlvmTarget $$2"
         AC_MSG_RESULT([yes])


=====================================
utils/ghc-toolchain/exe/Main.hs
=====================================
@@ -380,11 +380,15 @@ mkTarget opts = do
     normalised_triple <- normaliseTriple (optTriple opts)
     -- Use Llvm target if specified, otherwise use triple as llvm target
     let tgtLlvmTarget = fromMaybe normalised_triple (optLlvmTriple opts)
-    cc0 <- findCc tgtLlvmTarget (optCc opts)
-    cxx <- findCxx tgtLlvmTarget (optCxx opts)
+
+    (archOs, tgtVendor) <- do
+      cc0 <- findBasicCc (optCc opts)
+      parseTriple cc0 normalised_triple
+
+    cc0 <- findCc archOs tgtLlvmTarget (optCc opts)
+    cxx <- findCxx archOs tgtLlvmTarget (optCxx opts)
     cpp <- findCpp (optCpp opts) cc0
     hsCpp <- findHsCpp (optHsCpp opts) cc0
-    (archOs, tgtVendor) <- parseTriple cc0 normalised_triple
     cc <- addPlatformDepCcFlags archOs cc0
     readelf <- optional $ findReadelf (optReadelf opts)
     ccLink <- findCcLink tgtLlvmTarget (optLd opts) (optCcLink opts) (ldOverrideWhitelist archOs && fromMaybe True (optLdOverride opts)) archOs cc readelf


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Program.hs
=====================================
@@ -30,6 +30,7 @@ import System.Directory
 import System.Exit
 import System.Process hiding (env)
 
+import GHC.Platform.ArchOS
 import GHC.Toolchain.Prelude
 import GHC.Toolchain.Utils
 
@@ -182,17 +183,37 @@ compile ext extraFlags lens c outPath program = do
     callProgram (view lens c) $ extraFlags ++ ["-o", outPath, srcPath]
     expectFileExists outPath "compiler produced no output"
 
+-- Note [Don't pass --target to emscripten toolchain]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-- Emscripten's CC wrapper is a bit wonky in that it accepts the `--target`
+-- flag when used as a linker yet rejects it as a compiler (e.g. with `-c`).
+-- This is exacerbated by the fact that Cabal currently in some cases
+-- combines (and therefore conflates) link and compilation flags.
+--
+-- Ultimately this should be fixed in Cabal but in the meantime we work around it
+-- by handling this toolchain specifically in the various
+-- "supports --target" checks in `configure` and `ghc-toolchain`.
+--
+-- Fixes #23744.
+
 -- | Does compiler program support the @--target=<triple>@ option? If so, we should
 -- pass it whenever possible to avoid ambiguity and potential compile-time
 -- errors (e.g. see #20162).
-supportsTarget :: Lens compiler Program
+supportsTarget :: ArchOS
+               -> Lens compiler Program
                -> (compiler -> M ()) -- ^ Action to check if compiler with @--target@ flag works
                -> String             -- ^ The LLVM target to use if @cc@ supports @--target@
                -> compiler           -- ^ The compiler to check @--target@ support for
                -> M compiler         -- ^ Return compiler with @--target@ flag if supported
-supportsTarget lens checkWorks llvmTarget c
--- TODO: #23603
-  | any ("--target=" `isPrefixOf`) (view (lens % _prgFlags) c) = return c
+supportsTarget archOs lens checkWorks llvmTarget c
+    -- See Note [Don't pass --target to emscripten toolchain].
+  | ArchJavaScript <- archOS_arch archOs
+  = return c
+
+    -- No reason to check if the options already contain a --target flag
+  | any ("--target=" `isPrefixOf`) (view (lens % _prgFlags) c)
+  = return c
+
   | otherwise
   = let c' = over (lens % _prgFlags) (("--target="++llvmTarget):) c
      in (c' <$ checkWorks (over (lens % _prgFlags) ("-Werror":) c')) <|> return c


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
=====================================
@@ -4,6 +4,7 @@
 module GHC.Toolchain.Tools.Cc
     ( Cc(..)
     , _ccProgram
+    , findBasicCc
     , findCc
       -- * Helpful utilities
     , preprocess
@@ -33,22 +34,29 @@ _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
+-- We use this to find a minimally-functional compiler needed to call
+-- parseTriple.
+findBasicCc :: ProgOpt -> M Cc
+findBasicCc progOpt = checking "for C compiler" $ do
     -- TODO: We keep the candidate order we had in configure, but perhaps
     -- there's a more optimal one
     ccProgram <- findProgram "C compiler" progOpt ["gcc", "clang", "cc"]
+    return $ Cc{ccProgram}
 
-    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"
+findCc :: ArchOS
+       -> String -- ^ The llvm target to use if Cc supports --target
+       -> ProgOpt -> M Cc
+findCc archOs llvmTarget progOpt = do
+    cc0 <- findBasicCc progOpt
+    cc1 <- ignoreUnusedArgs cc0
+    cc2 <- ccSupportsTarget archOs llvmTarget cc1
+    checking "whether Cc works" $ checkCcWorks cc2
+    cc3 <- oneOf "cc doesn't support C99" $ map checkC99Support
+        [ cc2
+        , cc2 & _ccFlags %++ "-std=gnu99"
         ]
-    checkCcSupportsExtraViaCFlags cc2
-    return cc2
+    checkCcSupportsExtraViaCFlags cc3
+    return cc3
 
 checkCcWorks :: Cc -> M ()
 checkCcWorks cc = withTempDir $ \dir -> do
@@ -75,9 +83,10 @@ ignoreUnusedArgs cc
 -- Does Cc support the --target=<triple> option? If so, we should pass it
 -- whenever possible to avoid ambiguity and potential compile-time errors (e.g.
 -- see #20162).
-ccSupportsTarget :: String -> Cc -> M Cc
-ccSupportsTarget target cc = checking "whether Cc supports --target" $
-                             supportsTarget _ccProgram checkCcWorks target cc
+ccSupportsTarget :: ArchOS -> String -> Cc -> M Cc
+ccSupportsTarget archOs target cc =
+    checking "whether Cc supports --target" $
+    supportsTarget archOs _ccProgram checkCcWorks target cc
 
 checkC99Support :: Cc -> M Cc
 checkC99Support cc = checking "for C99 support" $ withTempDir $ \dir -> do


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cxx.hs
=====================================
@@ -8,6 +8,8 @@ module GHC.Toolchain.Tools.Cxx
     ) where
 
 import System.FilePath
+
+import GHC.Platform.ArchOS
 import GHC.Toolchain.Prelude
 import GHC.Toolchain.Program
 import GHC.Toolchain.Utils
@@ -19,18 +21,20 @@ newtype Cxx = Cxx { cxxProgram :: Program
 _cxxProgram :: Lens Cxx Program
 _cxxProgram = Lens cxxProgram (\x o -> o{cxxProgram=x})
 
-findCxx :: String -- ^ The llvm target to use if Cc supports --target
+findCxx :: ArchOS
+        -> String -- ^ The llvm target to use if Cc supports --target
         -> ProgOpt -> M Cxx
-findCxx target progOpt = checking "for C++ compiler" $ do
+findCxx archOs target progOpt = checking "for C++ compiler" $ do
     -- TODO: We use the search order in configure, but there could be a more optimal one
     cxxProgram <- findProgram "C++ compiler" progOpt ["g++", "clang++", "c++"]
-    cxx        <- cxxSupportsTarget target Cxx{cxxProgram}
+    cxx        <- cxxSupportsTarget archOs target Cxx{cxxProgram}
     checkCxxWorks cxx
     return cxx
 
-cxxSupportsTarget :: String -> Cxx -> M Cxx
-cxxSupportsTarget target cxx = checking "whether C++ supports --target" $
-                               supportsTarget _cxxProgram checkCxxWorks target cxx
+cxxSupportsTarget :: ArchOS -> String -> Cxx -> M Cxx
+cxxSupportsTarget archOs target cxx =
+    checking "whether C++ supports --target" $
+    supportsTarget archOs _cxxProgram checkCxxWorks target cxx
 
 checkCxxWorks :: Cxx -> M ()
 checkCxxWorks cxx = withTempDir $ \dir -> do


=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
=====================================
@@ -62,7 +62,7 @@ findCcLink target ld progOpt ldOverride archOs cc readelf = checking "for C comp
                      _ -> do
                          -- If not then try to find decent linker flags
                          findLinkFlags ldOverride cc rawCcLink <|> pure rawCcLink
-  ccLinkProgram <- linkSupportsTarget cc target ccLinkProgram
+  ccLinkProgram <- linkSupportsTarget archOs cc target ccLinkProgram
   ccLinkSupportsNoPie         <- checkSupportsNoPie  cc ccLinkProgram
   ccLinkSupportsCompactUnwind <- checkSupportsCompactUnwind archOs cc ccLinkProgram
   ccLinkSupportsFilelist      <- checkSupportsFilelist cc ccLinkProgram
@@ -94,12 +94,12 @@ findLinkFlags enableOverride cc ccLink
   | otherwise =
     return ccLink
 
-linkSupportsTarget :: Cc -> String -> Program -> M Program
+linkSupportsTarget :: ArchOS -> 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 cc target link
-  = checking "whether cc linker supports --target" $
-    supportsTarget (Lens id const) (checkLinkWorks cc) target link
+linkSupportsTarget archOs cc target link =
+    checking "whether cc linker supports --target" $
+    supportsTarget archOs (Lens id const) (checkLinkWorks cc) target link
 
 -- | Should we attempt to find a more efficient linker on this platform?
 --



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/40b264e85734dda3f94b2dd54f72bdb50b868869
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/20231002/85867023/attachment-0001.html>


More information about the ghc-commits mailing list