diff --git a/testsuite/tests/th/T23309.c b/testsuite/tests/th/T23309.c new file mode 100644 index 0000000000000000000000000000000000000000..e8997710cd8e1692ce3c5486ec2dc767fb50e1ce --- /dev/null +++ b/testsuite/tests/th/T23309.c @@ -0,0 +1,8 @@ +#define _GNU_SOURCE 1 +#include <stdio.h> + +const char* foo(int e) { + static char s[256]; + sprintf(s, "The value of e is: %u", e); + return s; +} diff --git a/testsuite/tests/th/T23309.hs b/testsuite/tests/th/T23309.hs new file mode 100644 index 0000000000000000000000000000000000000000..ec1dd79c98ea395251761458479c86968b4438d3 --- /dev/null +++ b/testsuite/tests/th/T23309.hs @@ -0,0 +1,15 @@ +{-# LANGUAGE TemplateHaskell #-} +module T23309 where + +import Foreign.C.String +import Language.Haskell.TH +import System.IO + +import T23309A + +$(do runIO $ do + cstr <- c_foo 42 + str <- peekCString cstr + hPutStrLn stderr str + hFlush stderr + return []) diff --git a/testsuite/tests/th/T23309.stderr b/testsuite/tests/th/T23309.stderr new file mode 100644 index 0000000000000000000000000000000000000000..0eb8b205e86f2e1e0637d977714737dbf1e5f4be --- /dev/null +++ b/testsuite/tests/th/T23309.stderr @@ -0,0 +1 @@ +The value of e is: 42 diff --git a/testsuite/tests/th/T23309A.hs b/testsuite/tests/th/T23309A.hs new file mode 100644 index 0000000000000000000000000000000000000000..749017fad60b6b2e7fabd06dd682df7114c42c5f --- /dev/null +++ b/testsuite/tests/th/T23309A.hs @@ -0,0 +1,19 @@ +{-# LANGUAGE CPP #-} +module T23309A (c_foo) where + +import Foreign.C.String +import Foreign.C.Types + +#if defined(mingw32_HOST_OS) +# if defined(i386_HOST_ARCH) +# define CALLCONV stdcall +# elif defined(x86_64_HOST_ARCH) +# define CALLCONV ccall +# else +# error Unknown mingw32 arch +# endif +#else +# define CALLCONV ccall +#endif + +foreign import CALLCONV unsafe "foo" c_foo :: CInt -> IO CString diff --git a/testsuite/tests/th/T23378.hs b/testsuite/tests/th/T23378.hs new file mode 100644 index 0000000000000000000000000000000000000000..60b6500354792474506b2ef579771c40c8c624fa --- /dev/null +++ b/testsuite/tests/th/T23378.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE TemplateHaskell #-} +module T23378 where + +import Foreign.C.String +import Language.Haskell.TH +import System.IO + +import T23378A + +$(do runIO $ do + hPrint stderr isatty + hFlush stderr + return []) diff --git a/testsuite/tests/th/T23378.stderr b/testsuite/tests/th/T23378.stderr new file mode 100644 index 0000000000000000000000000000000000000000..bc59c12aa16bda1942655872af699a2d418c472b --- /dev/null +++ b/testsuite/tests/th/T23378.stderr @@ -0,0 +1 @@ +False diff --git a/testsuite/tests/th/T23378A.hs b/testsuite/tests/th/T23378A.hs new file mode 100644 index 0000000000000000000000000000000000000000..88594b58c3e76a862201258aec294573c1930f3c --- /dev/null +++ b/testsuite/tests/th/T23378A.hs @@ -0,0 +1,19 @@ +{-# LANGUAGE CPP #-} +module T23378A where + +import Foreign.C.Types +import System.IO.Unsafe + +isatty :: Bool +isatty = + unsafePerformIO (c_isatty 1) == 1 +{-# NOINLINE isatty #-} + +#if defined(mingw32_HOST_OS) +# define SYM "_isatty" +#else +# define SYM "isatty" +#endif + +foreign import ccall unsafe SYM + c_isatty :: CInt -> IO CInt diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index c3800d395f4f0a961417fff8bbda36cd874adf3b..cdcdd479798ec08c088aa4f546a755269f482f32 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -591,6 +591,8 @@ test('T23829_hasty', normal, compile_fail, ['']) test('T23829_hasty_b', normal, compile_fail, ['']) test('T23927', normal, compile_and_run, ['']) test('T23954', normal, compile_and_run, ['']) +test('T23309', [extra_files(['T23309A.hs']), req_c], multimod_compile, ['T23309', '-v0 T23309.c -optc-fPIC']) +test('T23378', [extra_files(['T23378A.hs']), js_skip], multimod_compile, ['T23378', '-v0']) test('T23962', normal, compile_and_run, ['']) test('T23968', normal, compile_and_run, ['']) test('T23971', normal, compile_and_run, [''])