Skip to content
Snippets Groups Projects
Commit 3a815f30 authored by Ryan Scott's avatar Ryan Scott Committed by Marge Bot
Browse files

Windows: Always define _UCRT when compiling C code

As seen in #22159, this is required to ensure correct behavior when MinGW-w64
headers are in the `C_INCLUDE_PATH`.

Fixes #22159.
parent a5f9c35f
No related branches found
No related tags found
No related merge requests found
......@@ -82,7 +82,11 @@ AC_DEFUN([FP_SETUP_WINDOWS_TOOLCHAIN],[
CC="${mingwbin}clang.exe"
CXX="${mingwbin}clang++.exe"
cflags="--rtlib=compiler-rt"
# Signal that we are linking against UCRT with the _UCRT macro. This is
# necessary to ensure correct behavior when MinGW-w64 headers are in the
# header include path (#22159).
cflags="--rtlib=compiler-rt -D_UCRT"
CFLAGS="$cflags"
CONF_CC_OPTS_STAGE1="$cflags"
CONF_CC_OPTS_STAGE2="$cflags"
......
......@@ -49,3 +49,10 @@ T15933:
'$(TEST_HC)' $(TEST_HC_OPTS) -c T15933.hs
'$(TEST_HC)' $(TEST_HC_OPTS) T15933_c.o T15933.o -o T15933
./T15933
.PHONY: T22159
T22159:
C_INCLUDE_PATH=/mingw64/include '$(TEST_HC)' $(TEST_HC_OPTS) -c T22159.hs
C_INCLUDE_PATH=/mingw64/include '$(TEST_HC)' $(TEST_HC_OPTS) -c T22159_c.c
C_INCLUDE_PATH=/mingw64/include '$(TEST_HC)' $(TEST_HC_OPTS) T22159.o T22159_c.o -o T22159
./T22159
{-# LANGUAGE CPP #-}
module Main (main) where
#if defined(i386_HOST_ARCH)
# define WINDOWS_CCONV stdcall
#elif defined(x86_64_HOST_ARCH)
# define WINDOWS_CCONV ccall
#else
# error Unknown mingw32 arch
#endif
import Foreign.C.String (peekCWString)
import Foreign.C.Types (CWchar)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (Ptr)
foreign import WINDOWS_CCONV "hello" c_hello :: Ptr CWchar -> IO ()
main :: IO ()
main = allocaBytes 12 $ \buf -> do
c_hello buf
str <- peekCWString buf
putStrLn str
hello
#include <stdio.h>
#include <wchar.h>
void hello(wchar_t *buf) {
swprintf_s(buf, 12, L"hello");
}
......@@ -229,3 +229,8 @@ test('T19237', normal, compile_and_run, ['T19237_c.c'])
test('T21305', omit_ways(['ghci']), multi_compile_and_run,
['T21305', [('T21305_cmm.cmm', '')], ''])
test('T22159',
[unless(opsys('mingw32'), skip),
extra_files(['T22159_c.c'])],
makefile_test, ['T22159'])
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