[Git][ghc/ghc][master] Add `-optcxx` option (#16477)

Marge Bot gitlab at gitlab.haskell.org
Mon Apr 8 18:47:55 UTC 2019



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


Commits:
97502be8 by Yuriy Syrovetskiy at 2019-04-08T18:41:51Z
Add `-optcxx` option (#16477)

- - - - -


12 changed files:

- compiler/main/DriverPhases.hs
- compiler/main/DriverPipeline.hs
- compiler/main/DynFlags.hs
- compiler/main/HscTypes.hs
- compiler/main/SysTools.hs
- compiler/main/SysTools/ExtraObj.hs
- compiler/main/SysTools/Tasks.hs
- docs/users_guide/phases.rst
- testsuite/tests/ffi/should_compile/all.T
- + testsuite/tests/ffi/should_compile/cc017.hs
- testsuite/tests/ffi/should_run/all.T
- testsuite/tests/th/T13366.hs


Changes:

=====================================
compiler/main/DriverPhases.hs
=====================================
@@ -369,4 +369,3 @@ isHaskellSigFilename     f = isHaskellSigSuffix     (drop 1 $ takeExtension f)
 isObjectFilename, isDynLibFilename :: Platform -> FilePath -> Bool
 isObjectFilename platform f = isObjectSuffix platform (drop 1 $ takeExtension f)
 isDynLibFilename platform f = isDynLibSuffix platform (drop 1 $ takeExtension f)
-


=====================================
compiler/main/DriverPipeline.hs
=====================================
@@ -1218,17 +1218,8 @@ runPhase (RealPhase cc_phase) input_fn dflags
 
         ghcVersionH <- liftIO $ getGhcVersionPathName dflags
 
-        let gcc_lang_opt | cc_phase `eqPhase` Ccxx    = "c++"
-                         | cc_phase `eqPhase` Cobjc   = "objective-c"
-                         | cc_phase `eqPhase` Cobjcxx = "objective-c++"
-                         | otherwise                  = "c"
-        liftIO $ SysTools.runCc dflags (
-                -- force the C compiler to interpret this file as C when
-                -- compiling .hc files, by adding the -x c option.
-                -- Also useful for plain .c files, just in case GHC saw a
-                -- -x c option.
-                        [ SysTools.Option "-x", SysTools.Option gcc_lang_opt
-                        , SysTools.FileOption "" input_fn
+        liftIO $ SysTools.runCc (phaseForeignLanguage cc_phase) dflags (
+                        [ SysTools.FileOption "" input_fn
                         , SysTools.Option "-o"
                         , SysTools.FileOption "" output_fn
                         ]
@@ -1917,7 +1908,7 @@ doCpp dflags raw input_fn output_fn = do
     let verbFlags = getVerbFlags dflags
 
     let cpp_prog args | raw       = SysTools.runCpp dflags args
-                      | otherwise = SysTools.runCc dflags (SysTools.Option "-E" : args)
+                      | otherwise = SysTools.runCc Nothing dflags (SysTools.Option "-E" : args)
 
     let target_defs =
           [ "-D" ++ HOST_OS     ++ "_BUILD_OS",


=====================================
compiler/main/DynFlags.hs
=====================================
@@ -92,7 +92,8 @@ module DynFlags (
         extraGccViaCFlags, systemPackageConfig,
         pgm_L, pgm_P, pgm_F, pgm_c, pgm_a, pgm_l, pgm_dll, pgm_T,
         pgm_windres, pgm_libtool, pgm_ar, pgm_ranlib, pgm_lo, pgm_lc,
-        pgm_lcc, pgm_i, opt_L, opt_P, opt_F, opt_c, opt_a, opt_l, opt_i,
+        pgm_lcc, pgm_i,
+        opt_L, opt_P, opt_F, opt_c, opt_cxx, opt_a, opt_l, opt_i,
         opt_P_signature,
         opt_windres, opt_lo, opt_lc, opt_lcc,
 
@@ -1340,6 +1341,7 @@ data Settings = Settings {
                                          -- See Note [Repeated -optP hashing]
   sOpt_F                 :: [String],
   sOpt_c                 :: [String],
+  sOpt_cxx               :: [String],
   sOpt_a                 :: [String],
   sOpt_l                 :: [String],
   sOpt_windres           :: [String],
@@ -1423,6 +1425,8 @@ opt_F dflags = sOpt_F (settings dflags)
 opt_c                 :: DynFlags -> [String]
 opt_c dflags = concatMap (wayOptc (targetPlatform dflags)) (ways dflags)
             ++ sOpt_c (settings dflags)
+opt_cxx               :: DynFlags -> [String]
+opt_cxx dflags = sOpt_cxx (settings dflags)
 opt_a                 :: DynFlags -> [String]
 opt_a dflags = sOpt_a (settings dflags)
 opt_l                 :: DynFlags -> [String]
@@ -2520,7 +2524,7 @@ setObjectDir, setHiDir, setHieDir, setStubDir, setDumpDir, setOutputDir,
          setDynObjectSuf, setDynHiSuf,
          setDylibInstallName,
          setObjectSuf, setHiSuf, setHieSuf, setHcSuf, parseDynLibLoaderMode,
-         setPgmP, addOptl, addOptc, addOptP,
+         setPgmP, addOptl, addOptc, addOptcxx, addOptP,
          addCmdlineFramework, addHaddockOpts, addGhciScript,
          setInteractivePrint
    :: String -> DynFlags -> DynFlags
@@ -2636,6 +2640,7 @@ setDumpPrefixForce f d = d { dumpPrefixForce = f}
 setPgmP   f = let (pgm:args) = words f in alterSettings (\s -> s { sPgm_P   = (pgm, map Option args)})
 addOptl   f = alterSettings (\s -> s { sOpt_l   = f : sOpt_l s})
 addOptc   f = alterSettings (\s -> s { sOpt_c   = f : sOpt_c s})
+addOptcxx f = alterSettings (\s -> s { sOpt_cxx = f : sOpt_cxx s})
 addOptP   f = alterSettings (\s -> s { sOpt_P   = f : sOpt_P s
                                      , sOpt_P_fingerprint = fingerprintStrings (f : sOpt_P s)
                                      })
@@ -3038,6 +3043,8 @@ dynamic_flags_deps = [
       (hasArg (\f -> alterSettings (\s -> s { sOpt_F   = f : sOpt_F s})))
   , make_ord_flag defFlag "optc"
       (hasArg addOptc)
+  , make_ord_flag defFlag "optcxx"
+      (hasArg addOptcxx)
   , make_ord_flag defFlag "opta"
       (hasArg (\f -> alterSettings (\s -> s { sOpt_a   = f : sOpt_a s})))
   , make_ord_flag defFlag "optl"


=====================================
compiler/main/HscTypes.hs
=====================================
@@ -30,6 +30,7 @@ module HscTypes (
         ModGuts(..), CgGuts(..), ForeignStubs(..), appendStubC,
         ImportedMods, ImportedBy(..), importedByUser, ImportedModsVal(..), SptEntry(..),
         ForeignSrcLang(..),
+        phaseForeignLanguage,
 
         ModSummary(..), ms_imps, ms_installed_mod, ms_mod_name, showModMsg, isBootSummary,
         msHsFilePath, msHiFilePath, msObjFilePath,
@@ -182,6 +183,7 @@ import CmdLineParser
 import DynFlags
 import DriverPhases     ( Phase, HscSource(..), hscSourceString
                         , isHsBootOrSig, isHsigFile )
+import qualified DriverPhases as Phase
 import BasicTypes
 import IfaceSyn
 import Maybes
@@ -3136,3 +3138,15 @@ Also see Note [Typechecking Complete Matches] in TcBinds for a more detailed
 explanation for how GHC ensures that all the conlikes in a COMPLETE set are
 consistent.
 -}
+
+-- | Foreign language of the phase if the phase deals with a foreign code
+phaseForeignLanguage :: Phase -> Maybe ForeignSrcLang
+phaseForeignLanguage phase = case phase of
+  Phase.Cc           -> Just LangC
+  Phase.Ccxx         -> Just LangCxx
+  Phase.Cobjc        -> Just LangObjc
+  Phase.Cobjcxx      -> Just LangObjcxx
+  Phase.HCc          -> Just LangC
+  Phase.As _         -> Just LangAsm
+  Phase.MergeForeign -> Just RawObject
+  _                  -> Nothing


=====================================
compiler/main/SysTools.hs
=====================================
@@ -301,6 +301,7 @@ initSysTools top_dir
                     sOpt_P_fingerprint = fingerprint0,
                     sOpt_F       = [],
                     sOpt_c       = [],
+                    sOpt_cxx     = [],
                     sOpt_a       = [],
                     sOpt_l       = [],
                     sOpt_windres = [],


=====================================
compiler/main/SysTools/ExtraObj.hs
=====================================
@@ -40,7 +40,7 @@ mkExtraObj dflags extn xs
       oFile <- newTempName dflags TFL_GhcSession "o"
       writeFile cFile xs
       ccInfo <- liftIO $ getCompilerInfo dflags
-      runCc dflags
+      runCc Nothing dflags
             ([Option        "-c",
               FileOption "" cFile,
               Option        "-o",


=====================================
compiler/main/SysTools/Tasks.hs
=====================================
@@ -10,6 +10,7 @@ module SysTools.Tasks where
 
 import Exception
 import ErrUtils
+import HscTypes
 import DynFlags
 import Outputable
 import Platform
@@ -58,11 +59,12 @@ runPp dflags args =   do
       opts = map Option (getOpts dflags opt_F)
   runSomething dflags "Haskell pre-processor" prog (args ++ opts)
 
-runCc :: DynFlags -> [Option] -> IO ()
-runCc 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
-      args1 = map Option (getOpts dflags opt_c)
-      args2 = args0 ++ args ++ args1
+      args1 = map Option userOpts
+      args2 = args0 ++ 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
@@ -118,6 +120,21 @@ runCc dflags args =   do
    | "warning: call-clobbered register used" `isContainedIn` w = False
    | otherwise = True
 
+  -- force the C compiler to interpret this file as C when
+  -- compiling .hc files, by adding the -x c option.
+  -- Also useful for plain .c files, just in case GHC saw a
+  -- -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)
+  userOpts_c   = getOpts dflags opt_c
+  userOpts_cxx = getOpts dflags opt_cxx
+
 isContainedIn :: String -> String -> Bool
 xs `isContainedIn` ys = any (xs `isPrefixOf`) (tails ys)
 


=====================================
docs/users_guide/phases.rst
=====================================
@@ -154,6 +154,13 @@ the following flags:
 
     Pass ⟨option⟩ to the C compiler.
 
+.. ghc-flag:: -optcxx ⟨option⟩
+    :shortdesc: pass ⟨option⟩ to the C++ compiler
+    :type: dynamic
+    :category: phase-options
+
+    Pass ⟨option⟩ to the C++ compiler.
+
 .. ghc-flag:: -optlo ⟨option⟩
     :shortdesc: pass ⟨option⟩ to the LLVM optimiser
     :type: dynamic


=====================================
testsuite/tests/ffi/should_compile/all.T
=====================================
@@ -32,3 +32,12 @@ test('cc016', normal, compile, [''])
 test('T10460', normal, compile, [''])
 test('T11983', [omit_ways(['ghci'])], compile, ['T11983.c'])
 test('T14125', normal, compile, [''])
+test(
+    'cc017',
+    normal,
+    compile,
+    [
+        '-optc=-DC -optcxx=-DCXX -optcxx=-std=c++11'
+        + (' -optcxx=-stdlib=libc++' if opsys('darwin') else '')
+    ],
+)


=====================================
testsuite/tests/ffi/should_compile/cc017.hs
=====================================
@@ -0,0 +1,19 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+import Language.Haskell.TH.Syntax
+
+-- Check -optc and -optcxx options passing.
+-- This file must be compiled with -optc=-DC -optcxx=-DCXX
+
+do  addForeignSource LangC
+        "int CXX = 0; // -DCXX must not be passed to C          \n\
+        \_Static_assert(C, \"name C must come from -DC\");      "
+
+    addForeignSource LangCxx
+        "int C = 0; // -DC must not be passed to C++            \n\
+        \static_assert(CXX, \"name CXX must come from -DCXX\"); "
+
+    pure []
+
+main :: IO ()
+main = pure ()


=====================================
testsuite/tests/ffi/should_run/all.T
=====================================
@@ -28,7 +28,7 @@ test('ffi004', skip, compile_and_run, [''])
 # On x86, the test suffers from floating-point differences due to the
 # use of 80-bit internal precision when using the native code generator.
 #
-test('ffi005', [ omit_ways(prof_ways), 
+test('ffi005', [ omit_ways(prof_ways),
                  when(arch('i386'), skip),
                  when(platform('i386-apple-darwin'), expect_broken(4105)),
                  exit_code(3) ],


=====================================
testsuite/tests/th/T13366.hs
=====================================
@@ -1,6 +1,6 @@
 {-# LANGUAGE ForeignFunctionInterface #-}
 {-# LANGUAGE TemplateHaskell #-}
-{-# OPTIONS_GHC -optc-DA_MACRO=1 #-}
+{-# OPTIONS_GHC -optc-DA_MACRO=1 -optcxx-DA_MACRO=1 #-}
 
 import Language.Haskell.TH.Syntax
 import System.IO (hFlush, stdout)



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/97502be8bda9199ac058b9677b4b6ba028022936

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/97502be8bda9199ac058b9677b4b6ba028022936
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/20190408/e1b292a1/attachment-0001.html>


More information about the ghc-commits mailing list