[Git][ghc/ghc][master] Pass preprocessor options to C compiler when building foreign C files (#16737)

Marge Bot gitlab at gitlab.haskell.org
Fri Jun 7 14:27:38 UTC 2019



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


Commits:
cfd3e0f1 by Zejun Wu at 2019-06-07T14:27:34Z
Pass preprocessor options to C compiler when building foreign C files (#16737)

- - - - -


5 changed files:

- compiler/main/DriverPipeline.hs
- + testsuite/tests/driver/T16737.hs
- + testsuite/tests/driver/T16737.stdout
- + testsuite/tests/driver/T16737include/T16737.h
- testsuite/tests/driver/all.T


Changes:

=====================================
compiler/main/DriverPipeline.hs
=====================================
@@ -1190,9 +1190,6 @@ runPhase (RealPhase Cmm) input_fn dflags
 -----------------------------------------------------------------------------
 -- Cc phase
 
--- we don't support preprocessing .c files (with -E) now.  Doing so introduces
--- way too many hacks, and I can't say I've ever used it anyway.
-
 runPhase (RealPhase cc_phase) input_fn dflags
    | any (cc_phase `eqPhase`) [Cc, Ccxx, HCc, Cobjc, Cobjcxx]
    = do
@@ -1214,6 +1211,16 @@ runPhase (RealPhase cc_phase) input_fn dflags
               (includePathsQuote cmdline_include_paths)
         let include_paths = include_paths_quote ++ include_paths_global
 
+        -- pass -D or -optP to preprocessor when compiling foreign C files
+        -- (#16737). Doing it in this way is simpler and also enable the C
+        -- compiler to performs preprocessing and parsing in a single pass,
+        -- but it may introduce inconsistency if a different pgm_P is specified.
+        let more_preprocessor_opts = concat
+              [ ["-Xpreprocessor", i]
+              | not hcc
+              , i <- getOpts dflags opt_P
+              ]
+
         let gcc_extra_viac_flags = extraGccViaCFlags dflags
         let pic_c_flags = picCCOpts dflags
 
@@ -1223,7 +1230,7 @@ runPhase (RealPhase cc_phase) input_fn dflags
         -- hc code doesn't not #include any header files anyway, so these
         -- options aren't necessary.
         pkg_extra_cc_opts <- liftIO $
-          if cc_phase `eqPhase` HCc
+          if hcc
              then return []
              else getPackageExtraCcOpts dflags pkgs
 
@@ -1305,6 +1312,7 @@ runPhase (RealPhase cc_phase) input_fn dflags
                        ++ [ "-include", ghcVersionH ]
                        ++ framework_paths
                        ++ include_paths
+                       ++ more_preprocessor_opts
                        ++ pkg_extra_cc_opts
                        ))
 


=====================================
testsuite/tests/driver/T16737.hs
=====================================
@@ -0,0 +1,32 @@
+{-# LANGUAGE TemplateHaskell #-}
+{-# OPTIONS_GHC -DFOO=2 -optP=-DBAR=3 -optc=-DBAZ=5 -optcxx=-DBAZ=7 #-}
+
+import Language.Haskell.TH.Syntax
+
+do
+  let code = unlines
+        [ "#if defined(__cplusplus)"
+        , "extern \"C\" {"
+        , "#endif"
+        , "#include <T16737.h>"
+        , "int FUN(void) {"
+        , "  return FOO * BAR * BAZ;"
+        , "}"
+        , "#if defined(__cplusplus)"
+        , "}"
+        , "#endif"
+        ]
+  addForeignSource LangC code
+  addForeignSource LangCxx code
+  pure []
+
+foreign import ccall unsafe "c_value"
+  c_value :: IO Int
+
+foreign import ccall unsafe "cxx_value"
+  cxx_value :: IO Int
+
+main :: IO ()
+main = do
+  print =<< c_value
+  print =<< cxx_value


=====================================
testsuite/tests/driver/T16737.stdout
=====================================
@@ -0,0 +1,2 @@
+30
+42


=====================================
testsuite/tests/driver/T16737include/T16737.h
=====================================
@@ -0,0 +1,7 @@
+#pragma once
+
+#if defined(__cplusplus)
+#define FUN cxx_value
+#else
+#define FUN c_value
+#endif


=====================================
testsuite/tests/driver/all.T
=====================================
@@ -270,3 +270,4 @@ test('inline-check', omit_ways(['hpc', 'profasm'])
 
 test('T14452', [], makefile_test, [])
 test('T15396', normal, compile_and_run, ['-package ghc'])
+test('T16737', [extra_files(['T16737include/'])], compile_and_run, ['-optP=-isystem -optP=T16737include'])



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/cfd3e0f1cfd16c8f35cae139d2a871a32eb4d2e1
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/20190607/3d662902/attachment-0001.html>


More information about the ghc-commits mailing list