[Git][ghc/ghc][master] Maintain separate flags for C++ compiler invocations

Marge Bot gitlab at gitlab.haskell.org
Fri Jun 14 03:34:46 UTC 2019



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
7bc5d6c6 by Ben Gamari at 2019-06-14T03:34:41Z
Maintain separate flags for C++ compiler invocations

Previously we would pass flags intended for the C compiler to the C++
compiler (see #16738). This would cause, for instance, `-std=gnu99` to
be passed to the C++ compiler, causing spurious test failures. Fix this
by maintaining a separate set of flags for C++ compilation invocations.

- - - - -


13 changed files:

- aclocal.m4
- compiler/ghci/Linker.hs
- compiler/main/DynFlags.hs
- compiler/main/Settings.hs
- compiler/main/SysTools.hs
- compiler/main/SysTools/Info.hs
- compiler/main/SysTools/Tasks.hs
- compiler/main/ToolSettings.hs
- hadrian/cfg/system.config.in
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/Generate.hs
- includes/ghc.mk
- mk/config.mk.in


Changes:

=====================================
aclocal.m4
=====================================
@@ -511,6 +511,7 @@ AC_DEFUN([FP_SETTINGS],
     then
         SettingsCCompilerCommand="$(basename $CC)"
         SettingsCCompilerFlags="$CONF_CC_OPTS_STAGE2"
+        SettingsCxxCompilerFlags="$CONF_CXX_OPTS_STAGE2"
         SettingsHaskellCPPCommand="$(basename $HaskellCPPCmd)"
         SettingsHaskellCPPFlags="$HaskellCPPArgs"
         SettingsLdCommand="$(basename $LdCmd)"
@@ -564,6 +565,7 @@ AC_DEFUN([FP_SETTINGS],
       SettingsOptCommand="$OptCmd"
     fi
     SettingsCCompilerFlags="$CONF_CC_OPTS_STAGE2"
+    SettingsCxxCompilerFlags="$CONF_CXX_OPTS_STAGE2"
     SettingsCCompilerLinkFlags="$CONF_GCC_LINKER_OPTS_STAGE2"
     SettingsCCompilerSupportsNoPie="$CONF_GCC_SUPPORTS_NO_PIE"
     SettingsLdFlags="$CONF_LD_LINKER_OPTS_STAGE2"
@@ -571,6 +573,7 @@ AC_DEFUN([FP_SETTINGS],
     AC_SUBST(SettingsHaskellCPPCommand)
     AC_SUBST(SettingsHaskellCPPFlags)
     AC_SUBST(SettingsCCompilerFlags)
+    AC_SUBST(SettingsCxxCompilerFlags)
     AC_SUBST(SettingsCCompilerLinkFlags)
     AC_SUBST(SettingsCCompilerSupportsNoPie)
     AC_SUBST(SettingsLdCommand)


=====================================
compiler/ghci/Linker.hs
=====================================
@@ -343,7 +343,7 @@ linkCmdLineLibs' hsc_env pls =
 
       -- Add directories to library search paths, this only has an effect
       -- on Windows. On Unix OSes this function is a NOP.
-      let all_paths = let paths = takeDirectory (fst $ pgm_c dflags)
+      let all_paths = let paths = takeDirectory (pgm_c dflags)
                                 : framework_paths
                                ++ lib_paths_base
                                ++ [ takeDirectory dll | DLLPath dll <- libspecs ]


=====================================
compiler/main/DynFlags.hs
=====================================
@@ -1421,7 +1421,7 @@ pgm_P                 :: DynFlags -> (String,[Option])
 pgm_P dflags = toolSettings_pgm_P $ toolSettings dflags
 pgm_F                 :: DynFlags -> String
 pgm_F dflags = toolSettings_pgm_F $ toolSettings dflags
-pgm_c                 :: DynFlags -> (String,[Option])
+pgm_c                 :: DynFlags -> String
 pgm_c dflags = toolSettings_pgm_c $ toolSettings dflags
 pgm_a                 :: DynFlags -> (String,[Option])
 pgm_a dflags = toolSettings_pgm_a $ toolSettings dflags
@@ -3049,7 +3049,7 @@ dynamic_flags_deps = [
       $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_F   = f }
   , make_ord_flag defFlag "pgmc"
       $ hasArg $ \f -> alterToolSettings $ \s -> s
-         { toolSettings_pgm_c   = (f,[])
+         { toolSettings_pgm_c   = f
          , -- Don't pass -no-pie with -pgmc
            -- (see #15319)
            toolSettings_ccSupportsNoPie = False


=====================================
compiler/main/Settings.hs
=====================================
@@ -119,7 +119,7 @@ sPgm_P :: Settings -> (String, [Option])
 sPgm_P = toolSettings_pgm_P . sToolSettings
 sPgm_F :: Settings -> String
 sPgm_F = toolSettings_pgm_F . sToolSettings
-sPgm_c :: Settings -> (String, [Option])
+sPgm_c :: Settings -> String
 sPgm_c = toolSettings_pgm_c . sToolSettings
 sPgm_a :: Settings -> (String, [Option])
 sPgm_a = toolSettings_pgm_a . sToolSettings


=====================================
compiler/main/SysTools.hs
=====================================
@@ -194,17 +194,18 @@ initSysTools top_dir
        -- It would perhaps be nice to be able to override this
        -- with the settings file, but it would be a little fiddly
        -- to make that possible, so for now you can't.
-       gcc_prog <- getToolSetting "C compiler command"
-       gcc_args_str <- getSetting "C compiler flags"
+       cc_prog <- getToolSetting "C compiler command"
+       cc_args_str <- getSetting "C compiler flags"
+       cxx_args_str <- getSetting "C++ compiler flags"
        gccSupportsNoPie <- getBooleanSetting "C compiler supports -no-pie"
        cpp_prog <- getToolSetting "Haskell CPP command"
        cpp_args_str <- getSetting "Haskell CPP flags"
-       let unreg_gcc_args = if targetUnregisterised
-                            then ["-DNO_REGS", "-DUSE_MINIINTERPRETER"]
-                            else []
-           cpp_args= map Option (words cpp_args_str)
-           gcc_args = map Option (words gcc_args_str
-                               ++ unreg_gcc_args)
+       let unreg_cc_args = if targetUnregisterised
+                           then ["-DNO_REGS", "-DUSE_MINIINTERPRETER"]
+                           else []
+           cpp_args = map Option (words cpp_args_str)
+           cc_args  = words cc_args_str ++ unreg_cc_args
+           cxx_args = words cxx_args_str
        ldSupportsCompactUnwind <- getBooleanSetting "ld supports compact unwind"
        ldSupportsBuildId       <- getBooleanSetting "ld supports build-id"
        ldSupportsFilelist      <- getBooleanSetting "ld supports filelist"
@@ -236,11 +237,11 @@ initSysTools top_dir
 
 
        -- Other things being equal, as and ld are simply gcc
-       gcc_link_args_str <- getSetting "C compiler link flags"
-       let   as_prog  = gcc_prog
-             as_args  = gcc_args
-             ld_prog  = gcc_prog
-             ld_args  = gcc_args ++ map Option (words gcc_link_args_str)
+       cc_link_args_str <- getSetting "C compiler link flags"
+       let   as_prog  = cc_prog
+             as_args  = map Option cc_args
+             ld_prog  = cc_prog
+             ld_args  = map Option (cc_args ++ words cc_link_args_str)
 
        -- We just assume on command line
        lc_prog <- getSetting "LLVM llc command"
@@ -308,7 +309,7 @@ initSysTools top_dir
            , toolSettings_pgm_L   = unlit_path
            , toolSettings_pgm_P   = (cpp_prog, cpp_args)
            , toolSettings_pgm_F   = ""
-           , toolSettings_pgm_c   = (gcc_prog, gcc_args)
+           , toolSettings_pgm_c   = cc_prog
            , toolSettings_pgm_a   = (as_prog, as_args)
            , toolSettings_pgm_l   = (ld_prog, ld_args)
            , toolSettings_pgm_dll = (mkdll_prog,mkdll_args)
@@ -325,8 +326,8 @@ initSysTools top_dir
            , toolSettings_opt_P       = []
            , toolSettings_opt_P_fingerprint = fingerprint0
            , toolSettings_opt_F       = []
-           , toolSettings_opt_c       = []
-           , toolSettings_opt_cxx     = []
+           , toolSettings_opt_c       = cc_args
+           , toolSettings_opt_cxx     = cxx_args
            , toolSettings_opt_a       = []
            , toolSettings_opt_l       = []
            , toolSettings_opt_windres = []


=====================================
compiler/main/SysTools/Info.hs
=====================================
@@ -219,7 +219,7 @@ getCompilerInfo dflags = do
 -- See Note [Run-time linker info].
 getCompilerInfo' :: DynFlags -> IO CompilerInfo
 getCompilerInfo' dflags = do
-  let (pgm,_) = pgm_c dflags
+  let pgm = pgm_c dflags
       -- Try to grab the info from the process output.
       parseCompilerInfo _stdo stde _exitc
         -- Regular GCC


=====================================
compiler/main/SysTools/Tasks.hs
=====================================
@@ -62,9 +62,9 @@ runPp dflags args =   do
 -- | Run compiler of C-like languages and raw objects (such as gcc or clang).
 runCc :: Maybe ForeignSrcLang -> DynFlags -> [Option] -> IO ()
 runCc mLanguage dflags args =   do
-  let (p,args0) = pgm_c dflags
+  let p = pgm_c dflags
       args1 = map Option userOpts
-      args2 = args0 ++ languageOptions ++ args ++ args1
+      args2 = languageOptions ++ args ++ args1
       -- We take care to pass -optc flags in args1 last to ensure that the
       -- user can override flags passed by GHC. See #14452.
   mb_env <- getGccEnv args2
@@ -126,12 +126,16 @@ runCc mLanguage dflags args =   do
   -- -x c option.
   (languageOptions, userOpts) = case mLanguage of
     Nothing -> ([], userOpts_c)
-    Just language -> ([Option "-x", Option languageName], opts) where
-      (languageName, opts) = case language of
-        LangCxx    -> ("c++",           userOpts_cxx)
-        LangObjc   -> ("objective-c",   userOpts_c)
-        LangObjcxx -> ("objective-c++", userOpts_cxx)
-        _          -> ("c",             userOpts_c)
+    Just language -> ([Option "-x", Option languageName], opts)
+      where
+        s = settings dflags
+        (languageName, opts) = case language of
+          LangC      -> ("c",             sOpt_c s ++ userOpts_c)
+          LangCxx    -> ("c++",           sOpt_cxx s ++ userOpts_cxx)
+          LangObjc   -> ("objective-c",   userOpts_c)
+          LangObjcxx -> ("objective-c++", userOpts_cxx)
+          LangAsm    -> ("assembler",     [])
+          RawObject  -> ("c",             []) -- claim C for lack of a better idea
   userOpts_c   = getOpts dflags opt_c
   userOpts_cxx = getOpts dflags opt_cxx
 
@@ -333,7 +337,8 @@ runMkDLL dflags args = do
 
 runWindres :: DynFlags -> [Option] -> IO ()
 runWindres dflags args = do
-  let (gcc, gcc_args) = pgm_c dflags
+  let cc = pgm_c dflags
+      cc_args = map Option (sOpt_c (settings dflags))
       windres = pgm_windres dflags
       opts = map Option (getOpts dflags opt_windres)
       quote x = "\"" ++ x ++ "\""
@@ -341,8 +346,7 @@ runWindres dflags args = do
               -- spaces then windres fails to run gcc. We therefore need
               -- to tell it what command to use...
               Option ("--preprocessor=" ++
-                      unwords (map quote (gcc :
-                                          map showOpt gcc_args ++
+                      unwords (map quote (cc :
                                           map showOpt opts ++
                                           ["-E", "-xc", "-DRC_INVOKED"])))
               -- ...but if we do that then if windres calls popen then
@@ -351,7 +355,7 @@ runWindres dflags args = do
               -- See #1828.
             : Option "--use-temp-file"
             : args
-  mb_env <- getGccEnv gcc_args
+  mb_env <- getGccEnv cc_args
   runSomethingFiltered dflags id "Windres" windres args' Nothing mb_env
 
 touch :: DynFlags -> String -> String -> IO ()


=====================================
compiler/main/ToolSettings.hs
=====================================
@@ -22,7 +22,7 @@ data ToolSettings = ToolSettings
   , toolSettings_pgm_L       :: String
   , toolSettings_pgm_P       :: (String, [Option])
   , toolSettings_pgm_F       :: String
-  , toolSettings_pgm_c       :: (String, [Option])
+  , toolSettings_pgm_c       :: String
   , toolSettings_pgm_a       :: (String, [Option])
   , toolSettings_pgm_l       :: (String, [Option])
   , toolSettings_pgm_dll     :: (String, [Option])


=====================================
hadrian/cfg/system.config.in
=====================================
@@ -126,6 +126,7 @@ settings-c-compiler-command = @SettingsCCompilerCommand@
 settings-haskell-cpp-command = @SettingsHaskellCPPCommand@
 settings-haskell-cpp-flags = @SettingsHaskellCPPFlags@
 settings-c-compiler-flags = @SettingsCCompilerFlags@
+settings-cxx-compiler-flags = @SettingsCxxCompilerFlags@
 settings-c-compiler-link-flags = @SettingsCCompilerLinkFlags@
 settings-c-compiler-supports-no-pie = @SettingsCCompilerSupportsNoPie@
 settings-ld-command = @SettingsLdCommand@


=====================================
hadrian/src/Oracles/Setting.hs
=====================================
@@ -88,6 +88,7 @@ data SettingsFileSetting
     | SettingsFileSetting_HaskellCPPCommand
     | SettingsFileSetting_HaskellCPPFlags
     | SettingsFileSetting_CCompilerFlags
+    | SettingsFileSetting_CxxCompilerFlags
     | SettingsFileSetting_CCompilerLinkFlags
     | SettingsFileSetting_CCompilerSupportsNoPie
     | SettingsFileSetting_LdCommand
@@ -162,6 +163,7 @@ settingsFileSetting key = lookupValueOrError configFile $ case key of
     SettingsFileSetting_HaskellCPPCommand -> "settings-haskell-cpp-command"
     SettingsFileSetting_HaskellCPPFlags -> "settings-haskell-cpp-flags"
     SettingsFileSetting_CCompilerFlags -> "settings-c-compiler-flags"
+    SettingsFileSetting_CxxCompilerFlags -> "settings-cxx-compiler-flags"
     SettingsFileSetting_CCompilerLinkFlags -> "settings-c-compiler-link-flags"
     SettingsFileSetting_CCompilerSupportsNoPie -> "settings-c-compiler-supports-no-pie"
     SettingsFileSetting_LdCommand -> "settings-ld-command"


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -277,6 +277,7 @@ generateSettings = do
         [ ("GCC extra via C opts", expr $ lookupValueOrError configFile "gcc-extra-via-c-opts")
         , ("C compiler command", expr $ settingsFileSetting SettingsFileSetting_CCompilerCommand)
         , ("C compiler flags", expr $ settingsFileSetting SettingsFileSetting_CCompilerFlags)
+        , ("C++ compiler flags", expr $ settingsFileSetting SettingsFileSetting_CxxCompilerFlags)
         , ("C compiler link flags", expr $ settingsFileSetting SettingsFileSetting_CCompilerLinkFlags)
         , ("C compiler supports -no-pie", expr $ settingsFileSetting SettingsFileSetting_CCompilerSupportsNoPie)
         , ("Haskell CPP command", expr $ settingsFileSetting SettingsFileSetting_HaskellCPPCommand)


=====================================
includes/ghc.mk
=====================================
@@ -179,6 +179,7 @@ $(includes_SETTINGS) : includes/Makefile | $$(dir $$@)/.
 	@echo '[("GCC extra via C opts", "$(GccExtraViaCOpts)")' >> $@
 	@echo ',("C compiler command", "$(SettingsCCompilerCommand)")' >> $@
 	@echo ',("C compiler flags", "$(SettingsCCompilerFlags)")' >> $@
+	@echo ',("C++ compiler flags", "$(SettingsCxxCompilerFlags)")' >> $@
 	@echo ',("C compiler link flags", "$(SettingsCCompilerLinkFlags)")' >> $@
 	@echo ',("C compiler supports -no-pie", "$(SettingsCCompilerSupportsNoPie)")' >> $@
 	@echo ',("Haskell CPP command", "$(SettingsHaskellCPPCommand)")' >> $@


=====================================
mk/config.mk.in
=====================================
@@ -510,6 +510,7 @@ SettingsCCompilerCommand = @SettingsCCompilerCommand@
 SettingsHaskellCPPCommand = @SettingsHaskellCPPCommand@
 SettingsHaskellCPPFlags = @SettingsHaskellCPPFlags@
 SettingsCCompilerFlags = @SettingsCCompilerFlags@
+SettingsCxxCompilerFlags = @SettingsCxxCompilerFlags@
 SettingsCCompilerLinkFlags = @SettingsCCompilerLinkFlags@
 SettingsCCompilerSupportsNoPie = @SettingsCCompilerSupportsNoPie@
 SettingsLdCommand = @SettingsLdCommand@



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/7bc5d6c6578ab9d60a83b81c7cc14819afef32ba

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/7bc5d6c6578ab9d60a83b81c7cc14819afef32ba
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/20190613/f456e631/attachment-0001.html>


More information about the ghc-commits mailing list