Skip to content
Snippets Groups Projects
Commit 4156b877 authored by Ryan Scott's avatar Ryan Scott Committed by Ben Gamari
Browse files

Prevent -optc arguments from being duplicated in reverse order (#17471)

This reverts a part of commit
7bc5d6c6 that causes all arguments
to `-optc` (and `-optcxx`) to be passed twice to the C/C++ compiler,
once in reverse order and then again in the correct order. While
passing duplicate arguments is usually harmless it can cause breakage
in this pattern, which is employed by Hackage libraries in the wild:

```
ghc Foo.hs foo.c -optc-D -optcFOO
```

As `FOO -D -D FOO` will cause compilers to error.

Fixes #17471.

(cherry picked from commit 9a896a55)
parent 22d64112
No related branches found
No related tags found
No related merge requests found
......@@ -127,10 +127,9 @@ runCc mLanguage dflags args = traceToolCommand dflags "cc" $ do
Nothing -> ([], 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)
LangC -> ("c", userOpts_c)
LangCxx -> ("c++", userOpts_cxx)
LangObjc -> ("objective-c", userOpts_c)
LangObjcxx -> ("objective-c++", userOpts_cxx)
LangAsm -> ("assembler", [])
......
{-# LANGUAGE ForeignFunctionInterface #-}
module Main where
import Foreign.C.Types
foreign import ccall "foo" foo :: IO CInt
main :: IO ()
main = foo >>= print
1
int foo() {
#if defined(FOO)
return 1;
#else
return 0;
#endif
}
......@@ -213,3 +213,6 @@ test('PrimFFIWord16', [omit_ways(['ghci'])], compile_and_run, ['PrimFFIWord16_c.
test('T493', [omit_ways(['ghci'])], compile_and_run, ['T493_c.c'])
test('UnliftedNewtypesByteArrayOffset', [omit_ways(['ghci'])], compile_and_run, ['UnliftedNewtypesByteArrayOffset_c.c'])
test('T17471', [omit_ways(['ghci'])], compile_and_run,
['T17471_c.c -optc-D -optcFOO'])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment