[Git][ghc/ghc][wip/romes/configure-cpp] Configure CPP into settings

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Tue May 23 16:43:07 UTC 2023



Rodrigo Mesquita pushed to branch wip/romes/configure-cpp at Glasgow Haskell Compiler / GHC


Commits:
fc1e6c49 by Rodrigo Mesquita at 2023-05-23T17:42:49+01:00
Configure CPP into settings

There is a distinction to be made between the Haskell Preprocessor and
the C preprocessor. The former is used to preprocess haskell files,
while the latter is used in C preprocessing such as Cmm files.

In practice, they are both the same program (usually the C compiler) but
invoked with different flags.

Previously we would, at configure time, configure the haskell
preprocessor and save the configuration in the settings file, but,
instead of doing the same for CPP, we had hardcoded in GHC that the CPP
program was either `cc -E` or `cpp`.

This commit fixes that asymmetry by also configuring CPP at configure
time, and tries to make more explicit the difference between HsCpp and
Cpp (see Note [Preprocessing invocations]).

Note that we don't use the standard CPP and CPPFLAGS to configure Cpp,
but instead use the non-standard --with-cpp and --with-cpp-flags.
The reason is that autoconf sets CPP to "$CC -E", whereas we expect the
CPP command to be configured as a standalone executable rather than a
command. These are symmetrical with --with-hs-cpp and
--with-hs-cpp-flags.

Cleanup: Hadrian no longer needs to pass the CPP configuration for CPP
         to be C99 compatible through -optP, since we now configure that
         into settings.

Closes #23422

- - - - -


18 changed files:

- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/SysTools/Cpp.hs
- compiler/GHC/SysTools/Tasks.hs
- configure.ac
- distrib/configure.ac.in
- hadrian/bindist/Makefile
- hadrian/cfg/system.config.in
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Builders/Ghc.hs
- hadrian/src/Settings/Builders/Hsc2Hs.hs
- m4/fp_cpp_cmd_with_args.m4
- + m4/fp_hs_cpp_cmd_with_args.m4
- m4/fp_settings.m4


Changes:

=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -122,7 +122,7 @@ runPhase (T_CmmCpp pipe_env hsc_env input_fn) = do
         (hsc_dflags hsc_env)
         (hsc_unit_env hsc_env)
         (CppOpts
-          { cppUseCc       = True
+          { useHsCpp       = False
           , cppLinePragmas = True
           })
         input_fn output_fn
@@ -700,7 +700,7 @@ runCppPhase hsc_env input_fn output_fn = do
            (hsc_dflags hsc_env)
            (hsc_unit_env hsc_env)
            (CppOpts
-              { cppUseCc       = False
+              { useHsCpp       = True
               , cppLinePragmas = True
               })
            input_fn output_fn


=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -97,6 +97,7 @@ module GHC.Driver.Session (
         sPgm_F,
         sPgm_c,
         sPgm_cxx,
+        sPgm_cpp,
         sPgm_a,
         sPgm_l,
         sPgm_lm,
@@ -135,8 +136,8 @@ module GHC.Driver.Session (
         ghcUsagePath, ghciUsagePath, topDir,
         versionedAppDir, versionedFilePath,
         extraGccViaCFlags, globalPackageDatabasePath,
-        pgm_L, pgm_P, pgm_F, pgm_c, pgm_cxx, pgm_a, pgm_l, pgm_lm, pgm_dll, pgm_T,
-        pgm_windres, pgm_ar,
+        pgm_L, pgm_P, pgm_F, pgm_c, pgm_cxx, pgm_cpp, pgm_a, pgm_l, pgm_lm,
+        pgm_dll, pgm_T, pgm_windres, pgm_ar,
         pgm_ranlib, pgm_lo, pgm_lc, pgm_lcc, pgm_i,
         opt_L, opt_P, opt_F, opt_c, opt_cxx, opt_a, opt_l, opt_lm, opt_i,
         opt_P_signature,
@@ -393,6 +394,8 @@ pgm_c                 :: DynFlags -> String
 pgm_c dflags = toolSettings_pgm_c $ toolSettings dflags
 pgm_cxx               :: DynFlags -> String
 pgm_cxx dflags = toolSettings_pgm_cxx $ toolSettings dflags
+pgm_cpp               :: DynFlags -> (String,[Option])
+pgm_cpp dflags = toolSettings_pgm_cpp $ toolSettings dflags
 pgm_a                 :: DynFlags -> (String,[Option])
 pgm_a dflags = toolSettings_pgm_a $ toolSettings dflags
 pgm_l                 :: DynFlags -> (String,[Option])


=====================================
compiler/GHC/Settings.hs
=====================================
@@ -29,6 +29,7 @@ module GHC.Settings
   , sPgm_F
   , sPgm_c
   , sPgm_cxx
+  , sPgm_cpp
   , sPgm_a
   , sPgm_l
   , sPgm_lm
@@ -96,10 +97,13 @@ data ToolSettings = ToolSettings
 
   -- commands for particular phases
   , toolSettings_pgm_L       :: String
-  , toolSettings_pgm_P       :: (String, [Option])
+  , -- | The Haskell C preprocessor and default options (not added by -optP)
+    toolSettings_pgm_P       :: (String, [Option])
   , toolSettings_pgm_F       :: String
   , toolSettings_pgm_c       :: String
   , toolSettings_pgm_cxx     :: String
+  , -- | The C preprocessor (distinct from the Haskell C preprocessor!)
+    toolSettings_pgm_cpp     :: (String, [Option])
   , toolSettings_pgm_a       :: (String, [Option])
   , toolSettings_pgm_l       :: (String, [Option])
   , toolSettings_pgm_lm      :: Maybe (String, [Option])
@@ -212,6 +216,8 @@ sPgm_c :: Settings -> String
 sPgm_c = toolSettings_pgm_c . sToolSettings
 sPgm_cxx :: Settings -> String
 sPgm_cxx = toolSettings_pgm_cxx . sToolSettings
+sPgm_cpp :: Settings -> (String, [Option])
+sPgm_cpp = toolSettings_pgm_cpp . sToolSettings
 sPgm_a :: Settings -> (String, [Option])
 sPgm_a = toolSettings_pgm_a . sToolSettings
 sPgm_l :: Settings -> (String, [Option])


=====================================
compiler/GHC/Settings/IO.hs
=====================================
@@ -82,15 +82,18 @@ initSettings top_dir = do
   cc_args_str <- getToolSetting "C compiler flags"
   cxx_args_str <- getToolSetting "C++ compiler flags"
   gccSupportsNoPie <- getBooleanSetting "C compiler supports -no-pie"
-  cpp_prog <- getToolSetting "Haskell CPP command"
-  cpp_args_str <- getToolSetting "Haskell CPP flags"
+  cpp_prog <- getToolSetting "CPP command"
+  cpp_args_str <- getToolSetting "CPP flags"
+  hs_cpp_prog <- getToolSetting "Haskell CPP command"
+  hs_cpp_args_str <- getToolSetting "Haskell CPP flags"
 
   platform <- either pgmError pure $ getTargetPlatform settingsFile mySettings
 
   let unreg_cc_args = if platformUnregisterised platform
                       then ["-DNO_REGS", "-DUSE_MINIINTERPRETER"]
                       else []
-      cpp_args = map Option (words cpp_args_str)
+      cpp_args    = map Option (words cpp_args_str)
+      hs_cpp_args = map Option (words hs_cpp_args_str)
       cc_args  = words cc_args_str ++ unreg_cc_args
       cxx_args = words cxx_args_str
   ldSupportsCompactUnwind <- getBooleanSetting "ld supports compact unwind"
@@ -118,7 +121,6 @@ initSettings top_dir = do
   mkdll_prog <- getToolSetting "dllwrap command"
   let mkdll_args = []
 
-  -- cpp is derived from gcc on all platforms
   -- HACK, see setPgmP below. We keep 'words' here to remember to fix
   -- Config.hs one day.
 
@@ -171,10 +173,11 @@ initSettings top_dir = do
       , toolSettings_arSupportsDashL         = arSupportsDashL
 
       , toolSettings_pgm_L   = unlit_path
-      , toolSettings_pgm_P   = (cpp_prog, cpp_args)
+      , toolSettings_pgm_P   = (hs_cpp_prog, hs_cpp_args)
       , toolSettings_pgm_F   = ""
       , toolSettings_pgm_c   = cc_prog
       , toolSettings_pgm_cxx = cxx_prog
+      , toolSettings_pgm_cpp = (cpp_prog, cpp_args)
       , toolSettings_pgm_a   = (as_prog, as_args)
       , toolSettings_pgm_l   = (ld_prog, ld_args)
       , toolSettings_pgm_lm  = ld_r


=====================================
compiler/GHC/StgToJS/Linker/Linker.hs
=====================================
@@ -827,7 +827,7 @@ embedJsFile logger dflags tmpfs unit_env input_fn output_fn = do
       js_fn <- newTempName logger tmpfs (tmpDir dflags) TFL_CurrentModule "js"
       let
         cpp_opts = CppOpts
-          { cppUseCc       = True
+          { useHsCpp       = False
           , cppLinePragmas = False -- LINE pragmas aren't JS compatible
           }
       doCpp logger


=====================================
compiler/GHC/SysTools/Cpp.hs
=====================================
@@ -5,7 +5,7 @@
 
 module GHC.SysTools.Cpp
   ( doCpp
-  , CppOpts (..)
+  , CppOpts(..)
   , getGhcVersionPathName
   , applyCDefs
   , offsetIncludePaths
@@ -40,11 +40,31 @@ import System.Directory
 import System.FilePath
 
 data CppOpts = CppOpts
-  { cppUseCc       :: !Bool -- ^ Use "cc -E" as preprocessor, otherwise use "cpp"
-  , cppLinePragmas :: !Bool -- ^ Enable generation of LINE pragmas
+  { useHsCpp       :: !Bool
+  -- ^ Use the Haskell C preprocessor, otherwise use the C preprocessor.
+  -- See the Note [Preprocessing invocations]
+  , cppLinePragmas :: !Bool
+  -- ^ Enable generation of LINE pragmas
   }
 
--- | Run CPP
+{-
+Note [Preprocessing invocations]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We must consider two distinct preprocessors when preprocessing Haskell.
+These are:
+
+(1) The Haskell C preprocessor (HsCpp), which preprocesses Haskell files that make use
+  of the CPP language extension
+
+(2) The C preprocessor (Cpp), which is used to preprocess C and Cmm files
+
+These preprocessors are indeed different. Despite often sharing the same
+underlying program (the C compiler), the set of flags passed determines the
+behaviour of the preprocessor, and Cpp and HsCpp behave differently.
+-}
+
+-- | Run either the Haskell preprocessor or the C preprocessor, as per the
+-- 'CppOpts' passed. See Note [Preprocessing invocations].
 --
 -- UnitEnv is needed to compute MIN_VERSION macros
 doCpp :: Logger -> TmpFs -> DynFlags -> UnitEnv -> CppOpts -> FilePath -> FilePath -> IO ()
@@ -73,8 +93,7 @@ doCpp logger tmpfs dflags unit_env opts input_fn output_fn = do
     let verbFlags = getVerbFlags dflags
 
     let cpp_prog args
-          | cppUseCc opts = GHC.SysTools.runCc Nothing logger tmpfs dflags
-                                               (GHC.SysTools.Option "-E" : args)
+          | useHsCpp opts = GHC.SysTools.runHsCpp logger dflags args
           | otherwise     = GHC.SysTools.runCpp logger dflags args
 
     let platform   = targetPlatform dflags


=====================================
compiler/GHC/SysTools/Tasks.hs
=====================================
@@ -60,17 +60,41 @@ augmentImports _ [x] = [x]
 augmentImports dflags ("-include":fp:fps) = "-include" : augmentByWorkingDirectory dflags fp  : augmentImports dflags fps
 augmentImports dflags (fp1: fp2: fps) = fp1 : augmentImports dflags (fp2:fps)
 
-runCpp :: Logger -> DynFlags -> [Option] -> IO ()
-runCpp logger dflags args = traceSystoolCommand logger "cpp" $ do
-  let opts = getOpts dflags opt_P
-      modified_imports = augmentImports dflags opts
-  let (p,args0) = pgm_P dflags
-      args1 = map Option modified_imports
-      args2 = [Option "-Werror" | gopt Opt_WarnIsError dflags]
-                ++ [Option "-Wundef" | wopt Opt_WarnCPPUndef dflags]
+-- | Run a preprocessing command, be it either the HsCpp or Cpp.
+-- This is the common implementation to 'runCpp' and 'runHsCpp'.
+-- See also Note [Preprocessing invocations] in GHC.SysTools.Cpp
+run_some_cpp :: Logger
+           -> DynFlags
+           -> String
+           -- ^ A short description of the preprocessor being run
+           -> (DynFlags -> (String, [Option]))
+           -- ^ Field accessor to get the preprocessor program and configured flags
+           -> [Option]
+           -- ^ Additional arguments to pass to the preprocessor
+           -> IO ()
+run_some_cpp logger dflags desc getPgm args1 = do
+  let (p,args0) = getPgm dflags
+      args2     = [Option "-Werror" | gopt Opt_WarnIsError dflags]
+                    ++ [Option "-Wundef" | wopt Opt_WarnCPPUndef dflags]
   mb_env <- getGccEnv args2
-  runSomethingFiltered logger id  "C pre-processor" p
-                       (args0 ++ args1 ++ args2 ++ args) Nothing mb_env
+  runSomethingFiltered logger id desc p
+                       (args0 ++ args1 ++ args2) Nothing mb_env
+
+-- | Run the C preprocessor, which is different from running the
+-- Haskell C preprocessor (they're configured separately!).
+-- See also Note [Preprocessing invocations] in GHC.SysTools.Cpp
+runCpp :: Logger -> DynFlags -> [Option] -> IO ()
+runCpp logger dflags args = traceSystoolCommand logger "cpp" $
+  -- ROMES: we're no longer using runSomethingResponseFile for CPP, nor passing the C options
+  run_some_cpp logger dflags "C pre-processor" pgm_cpp args
+
+-- | Run the Haskell C preprocessor.
+-- See also Note [Preprocessing invocations] in GHC.SysTools.Cpp
+runHsCpp :: Logger -> DynFlags -> [Option] -> IO ()
+runHsCpp logger dflags args = traceSystoolCommand logger "hs-cpp" $
+  let optPs = getOpts dflags opt_P
+      args0 = map Option (augmentImports dflags optPs)
+   in run_some_cpp logger dflags "Haskell C pre-processor" pgm_P (args0 ++ args)
 
 runPp :: Logger -> DynFlags -> [Option] -> IO ()
 runPp logger dflags args = traceSystoolCommand logger "pp" $ do


=====================================
configure.ac
=====================================
@@ -466,7 +466,7 @@ dnl make extensions visible to allow feature-tests to detect them lateron
 AC_USE_SYSTEM_EXTENSIONS
 
 # --with-hs-cpp/--with-hs-cpp-flags
-FP_CPP_CMD_WITH_ARGS(HaskellCPPCmd, HaskellCPPArgs)
+FP_HSCPP_CMD_WITH_ARGS(HaskellCPPCmd, HaskellCPPArgs)
 AC_SUBST([HaskellCPPCmd])
 AC_SUBST([HaskellCPPArgs])
 
@@ -475,6 +475,17 @@ FP_SET_CFLAGS_C99([CC_STAGE0],[CONF_CC_OPTS_STAGE0],[CONF_CPP_OPTS_STAGE0])
 FP_SET_CFLAGS_C99([CC],[CONF_CC_OPTS_STAGE1],[CONF_CPP_OPTS_STAGE1])
 FP_SET_CFLAGS_C99([CC],[CONF_CC_OPTS_STAGE2],[CONF_CPP_OPTS_STAGE2])
 
+# CPP, CPPFLAGS
+# --with-cpp/-with-cpp-flags
+dnl Note that we must do this after setting the C99 flags, or otherwise we
+dnl might end up trying to configure the C99 flags using -E as a CPPFLAG
+FP_CPP_CMD_WITH_ARGS([$CC_STAGE0],[CPPCmd_STAGE0],[CONF_CPP_OPTS_STAGE0])
+FP_CPP_CMD_WITH_ARGS([$CC],[CPPCmd],[CONF_CPP_OPTS_STAGE1])
+FP_CPP_CMD_WITH_ARGS([$CC],[CPPCmd],[CONF_CPP_OPTS_STAGE2])
+AC_SUBST([CPPCmd_STAGE0])
+AC_SUBST([CPPCmd])
+
+
 dnl ** Which ld to use
 dnl --------------------------------------------------------------
 AC_ARG_VAR(LD,[Use as the path to ld. See also --disable-ld-override.])
@@ -1230,6 +1241,8 @@ echo "\
    Unregisterised            : $Unregisterised
    TablesNextToCode          : $TablesNextToCode
    Build GMP in tree         : $GMP_FORCE_INTREE
+   cpp          : $CPPCmd
+   cpp-flags    : $CONF_CPP_OPTS_STAGE2
    hs-cpp       : $HaskellCPPCmd
    hs-cpp-flags : $HaskellCPPArgs
    ar           : $ArCmd


=====================================
distrib/configure.ac.in
=====================================
@@ -110,10 +110,18 @@ dnl ** figure out how to invoke the C preprocessor (i.e. `gcc -E`)
 AC_PROG_CPP
 
 # --with-hs-cpp/--with-hs-cpp-flags
-FP_CPP_CMD_WITH_ARGS(HaskellCPPCmd, HaskellCPPArgs)
+FP_HSCPP_CMD_WITH_ARGS(HaskellCPPCmd, HaskellCPPArgs)
 AC_SUBST([HaskellCPPCmd])
 AC_SUBST([HaskellCPPArgs])
 
+# CPP, CPPFLAGS
+# For now, we assume CPP args are shared accross stages
+FP_CPP_CMD_WITH_ARGS([$CC_STAGE0],[CPPCmd_STAGE0],[CONF_CPP_OPTS_STAGE0])
+FP_CPP_CMD_WITH_ARGS([$CC],[CPPCmd],[CONF_CPP_OPTS_STAGE1])
+FP_CPP_CMD_WITH_ARGS([$CC],[CPPCmd],[CONF_CPP_OPTS_STAGE2])
+AC_SUBST([CPPCmd_STAGE0])
+AC_SUBST([CPPCmd])
+
 FP_SET_CFLAGS_C99([CC],[CFLAGS],[CPPFLAGS])
 dnl FP_SET_CFLAGS_C99([CC_STAGE0],[CONF_CC_OPTS_STAGE0],[CONF_CPP_OPTS_STAGE0])
 FP_SET_CFLAGS_C99([CC],[CONF_CC_OPTS_STAGE1],[CONF_CPP_OPTS_STAGE1])


=====================================
hadrian/bindist/Makefile
=====================================
@@ -86,6 +86,8 @@ lib/settings : config.mk
 	@echo ',("C++ compiler flags", "$(SettingsCxxCompilerFlags)")' >> $@
 	@echo ',("C compiler link flags", "$(SettingsCCompilerLinkFlags)")' >> $@
 	@echo ',("C compiler supports -no-pie", "$(SettingsCCompilerSupportsNoPie)")' >> $@
+	@echo ',("CPP command", "$(SettingsCPPCommand)")' >> $@
+	@echo ',("CPP flags", "$(SettingsCPPFlags)")' >> $@
 	@echo ',("Haskell CPP command", "$(SettingsHaskellCPPCommand)")' >> $@
 	@echo ',("Haskell CPP flags", "$(SettingsHaskellCPPFlags)")' >> $@
 	@echo ',("ld command", "$(SettingsLdCommand)")' >> $@


=====================================
hadrian/cfg/system.config.in
=====================================
@@ -10,6 +10,7 @@ ar             = @ArCmd@
 autoreconf     = @AutoreconfCmd@
 cc             = @CC@
 happy          = @HappyCmd@
+cpp            = @CPPCmd@
 hs-cpp         = @HaskellCPPCmd@
 ld             = @LdCmd@
 make           = @MakeCmd@
@@ -21,6 +22,7 @@ ranlib         = @REAL_RANLIB_CMD@
 sphinx-build   = @SPHINXBUILD@
 system-ar      = @AR_STAGE0@
 system-cc      = @CC_STAGE0@
+system-cpp     = @CPPCmd_STAGE0@
 system-ghc     = @WithGhc@
 system-ghc-pkg = @GhcPkgCmd@
 tar            = @TarCmd@
@@ -108,11 +110,6 @@ conf-cc-args-stage1         = @CONF_CC_OPTS_STAGE1@
 conf-cc-args-stage2         = @CONF_CC_OPTS_STAGE2@
 conf-cc-args-stage3         = @CONF_CC_OPTS_STAGE3@
 
-conf-cpp-args-stage0        = @CONF_CPP_OPTS_STAGE0@
-conf-cpp-args-stage1        = @CONF_CPP_OPTS_STAGE1@
-conf-cpp-args-stage2        = @CONF_CPP_OPTS_STAGE2@
-conf-cpp-args-stage3        = @CONF_CPP_OPTS_STAGE3@
-
 conf-gcc-linker-args-stage0 = @CONF_GCC_LINKER_OPTS_STAGE0@
 conf-gcc-linker-args-stage1 = @CONF_GCC_LINKER_OPTS_STAGE1@
 conf-gcc-linker-args-stage2 = @CONF_GCC_LINKER_OPTS_STAGE2@
@@ -146,6 +143,8 @@ ar-args = @ArArgs@
 
 settings-c-compiler-command = @SettingsCCompilerCommand@
 settings-cxx-compiler-command = @SettingsCxxCompilerCommand@
+settings-cpp-command = @SettingsCPPCommand@
+settings-cpp-flags = @SettingsCPPFlags@
 settings-haskell-cpp-command = @SettingsHaskellCPPCommand@
 settings-haskell-cpp-flags = @SettingsHaskellCPPFlags@
 settings-c-compiler-flags = @SettingsCCompilerFlags@


=====================================
hadrian/src/Oracles/Setting.hs
=====================================
@@ -81,7 +81,6 @@ data Setting = BuildArch
              | TargetWordSize
              | BourneShell
 
--- TODO: Reduce the variety of similar flags (e.g. CPP and non-CPP versions).
 -- | Each 'SettingList' comes from the file @hadrian/cfg/system.config@,
 -- generated by the @configure@ script from the input file
 -- @hadrian/cfg/system.config.in at . For example, the line
@@ -92,7 +91,6 @@ data Setting = BuildArch
 -- the value of the setting and returns the list of strings
 -- @["-E", "-undef", "-traditional"]@, tracking the result in the Shake database.
 data SettingList = ConfCcArgs Stage
-                 | ConfCppArgs Stage
                  | ConfGccLinkerArgs Stage
                  | ConfLdLinkerArgs Stage
                  | ConfMergeObjectsArgs Stage
@@ -107,6 +105,8 @@ data SettingList = ConfCcArgs Stage
 data SettingsFileSetting
     = SettingsFileSetting_CCompilerCommand
     | SettingsFileSetting_CxxCompilerCommand
+    | SettingsFileSetting_CPPCommand
+    | SettingsFileSetting_CPPFlags
     | SettingsFileSetting_HaskellCPPCommand
     | SettingsFileSetting_HaskellCPPFlags
     | SettingsFileSetting_CCompilerFlags
@@ -191,7 +191,6 @@ bootIsStage0 s = s
 settingList :: SettingList -> Action [String]
 settingList key = fmap words $ lookupSystemConfig $ case key of
     ConfCcArgs        stage -> "conf-cc-args-"         ++ stageString (bootIsStage0 stage)
-    ConfCppArgs       stage -> "conf-cpp-args-"        ++ stageString (bootIsStage0 stage)
     ConfGccLinkerArgs stage -> "conf-gcc-linker-args-" ++ stageString (bootIsStage0 stage)
     ConfLdLinkerArgs  stage -> "conf-ld-linker-args-"  ++ stageString (bootIsStage0 stage)
     ConfMergeObjectsArgs stage -> "conf-merge-objects-args-"  ++ stageString (bootIsStage0 stage)
@@ -204,6 +203,8 @@ settingsFileSetting :: SettingsFileSetting -> Action String
 settingsFileSetting key = lookupSystemConfig $ case key of
     SettingsFileSetting_CCompilerCommand -> "settings-c-compiler-command"
     SettingsFileSetting_CxxCompilerCommand -> "settings-cxx-compiler-command"
+    SettingsFileSetting_CPPCommand -> "settings-cpp-command"
+    SettingsFileSetting_CPPFlags -> "settings-cpp-flags"
     SettingsFileSetting_HaskellCPPCommand -> "settings-haskell-cpp-command"
     SettingsFileSetting_HaskellCPPFlags -> "settings-haskell-cpp-flags"
     SettingsFileSetting_CCompilerFlags -> "settings-c-compiler-flags"


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -418,6 +418,8 @@ generateSettings = do
         , ("C++ compiler flags", expr $ settingsFileSetting SettingsFileSetting_CxxCompilerFlags)
         , ("C compiler link flags", expr $ settingsFileSetting SettingsFileSetting_CCompilerLinkFlags)
         , ("C compiler supports -no-pie", expr $ settingsFileSetting SettingsFileSetting_CCompilerSupportsNoPie)
+        , ("CPP command", expr $ settingsFileSetting SettingsFileSetting_CPPCommand)
+        , ("CPP flags", expr $ settingsFileSetting SettingsFileSetting_CPPFlags)
         , ("Haskell CPP command", expr $ settingsFileSetting SettingsFileSetting_HaskellCPPCommand)
         , ("Haskell CPP flags", expr $ settingsFileSetting SettingsFileSetting_HaskellCPPFlags)
         , ("ld command", expr $ settingsFileSetting SettingsFileSetting_LdCommand)


=====================================
hadrian/src/Settings/Builders/Ghc.hs
=====================================
@@ -37,7 +37,6 @@ toolArgs = do
               [ packageGhcArgs
               , includeGhcArgs
               , map ("-optc" ++) <$> getStagedSettingList ConfCcArgs
-              , map ("-optP" ++) <$> getStagedSettingList ConfCppArgs
               , map ("-optP" ++) <$> getContextData cppOpts
               , getContextData hcOpts
               ]
@@ -217,7 +216,6 @@ commonGhcArgs = do
             -- RTS package in the package database and failing.
             , package rts ? notStage0 ? arg "-ghcversion-file=rts/include/ghcversion.h"
             , map ("-optc" ++) <$> getStagedSettingList ConfCcArgs
-            , map ("-optP" ++) <$> getStagedSettingList ConfCppArgs
             , map ("-optP" ++) <$> getContextData cppOpts
             , arg "-outputdir", arg path
               -- we need to enable color explicitly because the output is


=====================================
hadrian/src/Settings/Builders/Hsc2Hs.hs
=====================================
@@ -50,7 +50,6 @@ getCFlags = do
     let cabalMacros = autogen -/- "cabal_macros.h"
     expr $ need [cabalMacros]
     mconcat [ remove ["-O"] (cArgs <> getStagedSettingList ConfCcArgs)
-            , getStagedSettingList ConfCppArgs
             , cIncludeArgs
             , getContextData ccOpts
             -- we might be able to leave out cppOpts, to be investigated.


=====================================
m4/fp_cpp_cmd_with_args.m4
=====================================
@@ -2,98 +2,58 @@
 # ----------------------
 # sets CPP command and its arguments
 #
-# $1 = the variable to set to CPP command
-# $2 = the variable to set to CPP command arguments
-
+# $1 = CC (unmodified)
+# $2 = the variable to set to CPP command
+# $3 = the variable to set to CPP command arguments
+#
+# The reason for using the non-standard --with-cpp and --with-cpp-flags instead
+# of the standard CPP and CPPFLAGS is that autoconf sets CPP to "$CC -E",
+# whereas we expect the CPP command to be configured as a standalone executable
+# rather than a command. These are symmetrical with --with-hs-cpp and
+--with-hs-cpp-flags.
 AC_DEFUN([FP_CPP_CMD_WITH_ARGS],[
-dnl ** what cpp to use?
-dnl --------------------------------------------------------------
-AC_ARG_WITH(hs-cpp,
-[AS_HELP_STRING([--with-hs-cpp=ARG],
-      [Path to the (C) preprocessor for Haskell files [default=autodetect]])],
+
+AC_ARG_WITH(cpp,
+[AS_HELP_STRING([--with-cpp=ARG],
+      [Path to the (C) preprocessor [default=autodetect]])],
 [
     if test "$HostOS" = "mingw32"
     then
         AC_MSG_WARN([Request to use $withval will be ignored])
     else
-        HS_CPP_CMD=$withval
+        CPP_CMD="$withval"
     fi
 ],
 [
-
-    # We can't use $CPP here, since HS_CPP_CMD is expected to be a single
-    # command (no flags), and AC_PROG_CPP defines CPP as "/usr/bin/gcc -E".
-    HS_CPP_CMD=$CC
-
-    SOLARIS_GCC_CPP_BROKEN=NO
-    SOLARIS_FOUND_GOOD_CPP=NO
-    case $host in
-        i386-*-solaris2)
-        GCC_MAJOR_MINOR=`$CC --version|grep "gcc (GCC)"|cut -d ' ' -f 3-3|cut -d '.' -f 1-2`
-        if test "$GCC_MAJOR_MINOR" != "3.4"; then
-          # this is not 3.4.x release so with broken CPP
-          SOLARIS_GCC_CPP_BROKEN=YES
-        fi
-        ;;
-    esac
-
-    if test "$SOLARIS_GCC_CPP_BROKEN" = "YES"; then
-      # let's try to find if GNU C 3.4.x is installed
-      if test -x /usr/sfw/bin/gcc; then
-        # something executable is in expected path so let's
-        # see if it's really GNU C
-        NEW_GCC_MAJOR_MINOR=`/usr/sfw/bin/gcc --version|grep "gcc (GCC)"|cut -d ' ' -f 3-3|cut -d '.' -f 1-2`
-        if test "$NEW_GCC_MAJOR_MINOR" = "3.4"; then
-          # this is GNU C 3.4.x which provides non-broken CPP on Solaris
-          # let's use it as CPP then.
-          HS_CPP_CMD=/usr/sfw/bin/gcc
-          SOLARIS_FOUND_GOOD_CPP=YES
-        fi
-      fi
-      if test "$SOLARIS_FOUND_GOOD_CPP" = "NO"; then
-        AC_MSG_WARN([Your GNU C provides broken CPP and you do not have GNU C 3.4.x installed.])
-        AC_MSG_WARN([Please install GNU C 3.4.x to solve this issue. It will be used as CPP only.])
-      fi
-    fi
+    # We can't use the CPP var here, since CPP_CMD is expected to be a single
+    # command (no flags), and autoconf defines CPP as "/usr/bin/gcc -E".
+    # So we use CC with -E by default
+    CPP_CMD="$1"
+    CPP_ARGS="-E"
 ]
 )
 
-dnl ** what cpp flags to use?
-dnl -----------------------------------------------------------
-AC_ARG_WITH(hs-cpp-flags,
-  [AS_HELP_STRING([--with-hs-cpp-flags=ARG],
-      [Flags to the (C) preprocessor for Haskell files [default=autodetect]])],
-  [
-      if test "$HostOS" = "mingw32"
-      then
-          AC_MSG_WARN([Request to use $withval will be ignored])
-      else
-          HS_CPP_ARGS=$withval
-      fi
-  ],
+AC_ARG_WITH(cpp-flags,
+[AS_HELP_STRING([--with-cpp-flags=ARG],
+  [Flags to the (C) preprocessor [default=autodetect]])],
 [
-  $HS_CPP_CMD -x c /dev/null -dM -E > conftest.txt 2>&1
-  if grep "__clang__" conftest.txt >/dev/null 2>&1; then
-    HS_CPP_ARGS="-E -undef -traditional -Wno-invalid-pp-token -Wno-unicode -Wno-trigraphs"
+  if test "$HostOS" = "mingw32"
+  then
+      AC_MSG_WARN([Request to use $withval will be ignored])
   else
-      $HS_CPP_CMD  -v > conftest.txt 2>&1
-      if  grep "gcc" conftest.txt >/dev/null 2>&1; then
-          HS_CPP_ARGS="-E -undef -traditional"
-        else
-          $HS_CPP_CMD  --version > conftest.txt 2>&1
-          if grep "cpphs" conftest.txt >/dev/null 2>&1; then
-            HS_CPP_ARGS="--cpp -traditional"
-          else
-            AC_MSG_WARN([configure can't recognize your CPP program, you may need to set --with-hs-cpp-flags=FLAGS explicitly])
-            HS_CPP_ARGS=""
-          fi
-      fi
+      # Use whatever flags were manually set, ignoring previously configured
+      # flags; and add CPP_ARGS (which will be -E if CPP_CMD was not specified)
+      CPP_ARGS="$CPP_ARGS $withval"
   fi
-  ]
-)
+],
+[
+  # Augment CPP_ARGS with whatever flags were previously configured and passed
+  # as an argument.
+  CPP_ARGS="$CPP_ARGS $$3"
+])
 
-$1=$HS_CPP_CMD
-$2=$HS_CPP_ARGS
+$2="$CPP_CMD"
+$3="$CPP_ARGS"
 
 ])
 


=====================================
m4/fp_hs_cpp_cmd_with_args.m4
=====================================
@@ -0,0 +1,98 @@
+# FP_HSCPP_CMD_WITH_ARGS()
+# ----------------------
+# sets HS CPP command and its arguments
+#
+# $1 = the variable to set to HS CPP command
+# $2 = the variable to set to HS CPP command arguments
+
+AC_DEFUN([FP_HSCPP_CMD_WITH_ARGS],[
+dnl ** what hs-cpp to use?
+dnl --------------------------------------------------------------
+AC_ARG_WITH(hs-cpp,
+[AS_HELP_STRING([--with-hs-cpp=ARG],
+      [Path to the Haskell (C) preprocessor for Haskell files [default=autodetect]])],
+[
+    if test "$HostOS" = "mingw32"
+    then
+        AC_MSG_WARN([Request to use $withval will be ignored])
+    else
+        HS_CPP_CMD=$withval
+    fi
+],
+[
+
+    # We can't use $CPP here, since HS_CPP_CMD is expected to be a single
+    # command (no flags), and AC_PROG_CPP defines CPP as "/usr/bin/gcc -E".
+    HS_CPP_CMD=$CC
+
+    SOLARIS_GCC_CPP_BROKEN=NO
+    SOLARIS_FOUND_GOOD_CPP=NO
+    case $host in
+        i386-*-solaris2)
+        GCC_MAJOR_MINOR=`$CC --version|grep "gcc (GCC)"|cut -d ' ' -f 3-3|cut -d '.' -f 1-2`
+        if test "$GCC_MAJOR_MINOR" != "3.4"; then
+          # this is not 3.4.x release so with broken CPP
+          SOLARIS_GCC_CPP_BROKEN=YES
+        fi
+        ;;
+    esac
+
+    if test "$SOLARIS_GCC_CPP_BROKEN" = "YES"; then
+      # let's try to find if GNU C 3.4.x is installed
+      if test -x /usr/sfw/bin/gcc; then
+        # something executable is in expected path so let's
+        # see if it's really GNU C
+        NEW_GCC_MAJOR_MINOR=`/usr/sfw/bin/gcc --version|grep "gcc (GCC)"|cut -d ' ' -f 3-3|cut -d '.' -f 1-2`
+        if test "$NEW_GCC_MAJOR_MINOR" = "3.4"; then
+          # this is GNU C 3.4.x which provides non-broken CPP on Solaris
+          # let's use it as CPP then.
+          HS_CPP_CMD=/usr/sfw/bin/gcc
+          SOLARIS_FOUND_GOOD_CPP=YES
+        fi
+      fi
+      if test "$SOLARIS_FOUND_GOOD_CPP" = "NO"; then
+        AC_MSG_WARN([Your GNU C provides broken CPP and you do not have GNU C 3.4.x installed.])
+        AC_MSG_WARN([Please install GNU C 3.4.x to solve this issue. It will be used as CPP only.])
+      fi
+    fi
+]
+)
+
+dnl ** what hs-cpp flags to use?
+dnl -----------------------------------------------------------
+AC_ARG_WITH(hs-cpp-flags,
+  [AS_HELP_STRING([--with-hs-cpp-flags=ARG],
+      [Flags to the Haskell (C) preprocessor for Haskell files [default=autodetect]])],
+  [
+      if test "$HostOS" = "mingw32"
+      then
+          AC_MSG_WARN([Request to use $withval will be ignored])
+      else
+          HS_CPP_ARGS=$withval
+      fi
+  ],
+[
+  $HS_CPP_CMD -x c /dev/null -dM -E > conftest.txt 2>&1
+  if grep "__clang__" conftest.txt >/dev/null 2>&1; then
+    HS_CPP_ARGS="-E -undef -traditional -Wno-invalid-pp-token -Wno-unicode -Wno-trigraphs"
+  else
+      $HS_CPP_CMD  -v > conftest.txt 2>&1
+      if  grep "gcc" conftest.txt >/dev/null 2>&1; then
+          HS_CPP_ARGS="-E -undef -traditional"
+        else
+          $HS_CPP_CMD  --version > conftest.txt 2>&1
+          if grep "cpphs" conftest.txt >/dev/null 2>&1; then
+            HS_CPP_ARGS="--cpp -traditional"
+          else
+            AC_MSG_WARN([configure can't recognize your CPP program, you may need to set --with-hs-cpp-flags=FLAGS explicitly])
+            HS_CPP_ARGS=""
+          fi
+      fi
+  fi
+  ]
+)
+
+$1=$HS_CPP_CMD
+$2=$HS_CPP_ARGS
+
+])


=====================================
m4/fp_settings.m4
=====================================
@@ -14,6 +14,8 @@ AC_DEFUN([FP_SETTINGS],
         SettingsCxxCompilerCommand="${mingw_bin_prefix}clang++.exe"
         SettingsCxxCompilerFlags="$CONF_CXX_OPTS_STAGE2 -I\$\$tooldir/mingw/include"
         SettingsCCompilerLinkFlags="$CONF_GCC_LINKER_OPTS_STAGE2 -L\$\$tooldir/mingw/lib -L\$\$tooldir/mingw/x86_64-w64-mingw32/lib"
+        SettingsCPPCommand="${mingw_bin_prefix}clang.exe"
+        SettingsCPPFlags="$CONF_CPP_OPTS_STAGE2 -I\$\$tooldir/mingw/include"
         SettingsHaskellCPPCommand="${mingw_bin_prefix}clang.exe"
         SettingsHaskellCPPFlags="$HaskellCPPArgs -I\$\$tooldir/mingw/include"
         SettingsLdCommand="${mingw_bin_prefix}ld.lld.exe"
@@ -35,6 +37,8 @@ AC_DEFUN([FP_SETTINGS],
         SettingsCCompilerFlags="$CONF_CC_OPTS_STAGE2"
         SettingsCxxCompilerCommand="$CXX"
         SettingsCxxCompilerFlags="$CONF_CXX_OPTS_STAGE2"
+        SettingsCPPCommand="$CPPCmd"
+        SettingsCPPFlags="$CONF_CPP_OPTS_STAGE2"
         SettingsHaskellCPPCommand="$HaskellCPPCmd"
         SettingsHaskellCPPFlags="$HaskellCPPArgs"
         SettingsCCompilerLinkFlags="$CONF_GCC_LINKER_OPTS_STAGE2"
@@ -107,6 +111,8 @@ AC_DEFUN([FP_SETTINGS],
 
     AC_SUBST(SettingsCCompilerCommand)
     AC_SUBST(SettingsCxxCompilerCommand)
+    AC_SUBST(SettingsCPPCommand)
+    AC_SUBST(SettingsCPPFlags)
     AC_SUBST(SettingsHaskellCPPCommand)
     AC_SUBST(SettingsHaskellCPPFlags)
     AC_SUBST(SettingsCCompilerFlags)



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fc1e6c4943ffffe7d7894feabdf877b5d9c6649a
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/20230523/675514b7/attachment-0001.html>


More information about the ghc-commits mailing list