Skip to content
Snippets Groups Projects
Commit 34fc28b0 authored by John Ericson's avatar John Ericson Committed by Marge Bot
Browse files

Test that functions from `mingwex` are available


Ryan wrote these two minimizations, but they never got added to the test
suite.

See #23309, #23378

Co-Authored-By: default avatarBen Gamari <bgamari.foss@gmail.com>
Co-Authored-By: default avatarRyan Scott <ryan.gl.scott@gmail.com>
parent f383a242
No related branches found
No related tags found
No related merge requests found
#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;
}
{-# 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 [])
The value of e is: 42
{-# 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
{-# 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 [])
False
{-# 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
......@@ -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, [''])
......
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