[Git][ghc/ghc][master] 2 commits: Test that functions from `mingwex` are available
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Thu Oct 12 10:48:51 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
34fc28b0 by John Ericson at 2023-10-12T06:48:28-04:00
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: Ben Gamari <bgamari.foss at gmail.com>
Co-Authored-By: Ryan Scott <ryan.gl.scott at gmail.com>
- - - - -
bdb54a0e by John Ericson at 2023-10-12T06:48:28-04:00
Do not check for the `mingwex` library in `/configure`
See the recent discussion in !10360 --- Cabal will itself check for the
library for the packages that need it, and while the autoconf check
additionally does some other things like define a `HAS_LIBMINGWEX` C
Preprocessor macro, those other things are also unused and unneeded.
Progress towards #17191, which aims to get rid of `/configure` entirely.
- - - - -
9 changed files:
- configure.ac
- + testsuite/tests/th/T23309.c
- + testsuite/tests/th/T23309.hs
- + testsuite/tests/th/T23309.stderr
- + testsuite/tests/th/T23309A.hs
- + testsuite/tests/th/T23378.hs
- + testsuite/tests/th/T23378.stderr
- + testsuite/tests/th/T23378A.hs
- testsuite/tests/th/all.T
Changes:
=====================================
configure.ac
=====================================
@@ -946,9 +946,6 @@ AC_CHECK_DECLS([program_invocation_short_name], , ,
[#define _GNU_SOURCE 1
#include <errno.h>])
-dnl ** check for mingwex library
-AC_CHECK_LIB([mingwex],[closedir])
-
dnl ** check for math library
dnl Keep that check as early as possible.
dnl as we need to know whether we need libm
=====================================
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;
+}
=====================================
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 [])
=====================================
testsuite/tests/th/T23309.stderr
=====================================
@@ -0,0 +1 @@
+The value of e is: 42
=====================================
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
=====================================
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 [])
=====================================
testsuite/tests/th/T23378.stderr
=====================================
@@ -0,0 +1 @@
+False
=====================================
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
=====================================
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, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f383a242c76f90bcca8a4d7ee001dcb49c172a9a...bdb54a0e9437ecd151693d9c6df76747d6b385ea
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f383a242c76f90bcca8a4d7ee001dcb49c172a9a...bdb54a0e9437ecd151693d9c6df76747d6b385ea
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/20231012/b60ca366/attachment-0001.html>
More information about the ghc-commits
mailing list