From d23afb8c63d22af310b3c19f7c311934d02e3a31 Mon Sep 17 00:00:00 2001
From: Ben Gamari <ben@smart-cactus.org>
Date: Fri, 5 Apr 2024 17:28:46 -0400
Subject: [PATCH] testsuite: Add broken test for CApiFFI with -fprefer-bytecode

See #24634.
---
 testsuite/tests/bytecode/T24634/Hello.hs | 16 ++++++++++++++++
 testsuite/tests/bytecode/T24634/Main.hs  | 10 ++++++++++
 testsuite/tests/bytecode/T24634/Makefile |  9 +++++++++
 testsuite/tests/bytecode/T24634/all.T    |  7 +++++++
 testsuite/tests/bytecode/T24634/hello.c  |  5 +++++
 testsuite/tests/bytecode/T24634/hello.h  |  1 +
 6 files changed, 48 insertions(+)
 create mode 100644 testsuite/tests/bytecode/T24634/Hello.hs
 create mode 100644 testsuite/tests/bytecode/T24634/Main.hs
 create mode 100644 testsuite/tests/bytecode/T24634/Makefile
 create mode 100644 testsuite/tests/bytecode/T24634/all.T
 create mode 100644 testsuite/tests/bytecode/T24634/hello.c
 create mode 100644 testsuite/tests/bytecode/T24634/hello.h

diff --git a/testsuite/tests/bytecode/T24634/Hello.hs b/testsuite/tests/bytecode/T24634/Hello.hs
new file mode 100644
index 000000000000..0d6c835484d4
--- /dev/null
+++ b/testsuite/tests/bytecode/T24634/Hello.hs
@@ -0,0 +1,16 @@
+{-# LANGUAGE CApiFFI #-}
+{-# LANGUAGE ForeignFunctionInterface #-}
+{-# LANGUAGE TemplateHaskell #-}
+
+module Hello where
+
+import Language.Haskell.TH
+import Language.Haskell.TH.Syntax
+
+foreign import capi "hello.h say_hello" say_hello :: IO Int
+
+mkHello :: DecsQ
+mkHello = do
+  n <- runIO say_hello
+  [d| hello :: IO Int
+      hello = return $(lift n) |]
diff --git a/testsuite/tests/bytecode/T24634/Main.hs b/testsuite/tests/bytecode/T24634/Main.hs
new file mode 100644
index 000000000000..71a7f927fd67
--- /dev/null
+++ b/testsuite/tests/bytecode/T24634/Main.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module Main where
+
+import Hello
+
+$(mkHello)
+
+main :: IO ()
+main = hello >>= print
diff --git a/testsuite/tests/bytecode/T24634/Makefile b/testsuite/tests/bytecode/T24634/Makefile
new file mode 100644
index 000000000000..7659061b0301
--- /dev/null
+++ b/testsuite/tests/bytecode/T24634/Makefile
@@ -0,0 +1,9 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
+
+bytecode-capi:
+	$(TEST_HC) -c hello.c
+	$(TEST_HC) -c -fbyte-code-and-object-code Hello.hs
+	$(TEST_HC) -fprefer-byte-code hello.o Main.hs
+	./Main
diff --git a/testsuite/tests/bytecode/T24634/all.T b/testsuite/tests/bytecode/T24634/all.T
new file mode 100644
index 000000000000..66cffe7e65aa
--- /dev/null
+++ b/testsuite/tests/bytecode/T24634/all.T
@@ -0,0 +1,7 @@
+test('T24634',
+     [extra_files(['hello.h', 'hello.c', 'Hello.hs', 'Main.hs']),
+      req_interp,
+      expect_broken(24634),
+      ],
+     makefile_test,
+     [''])
diff --git a/testsuite/tests/bytecode/T24634/hello.c b/testsuite/tests/bytecode/T24634/hello.c
new file mode 100644
index 000000000000..0ff975274022
--- /dev/null
+++ b/testsuite/tests/bytecode/T24634/hello.c
@@ -0,0 +1,5 @@
+#include "hello.h"
+
+int say_hello() {
+  return 42;
+}
diff --git a/testsuite/tests/bytecode/T24634/hello.h b/testsuite/tests/bytecode/T24634/hello.h
new file mode 100644
index 000000000000..dfe2c8de531e
--- /dev/null
+++ b/testsuite/tests/bytecode/T24634/hello.h
@@ -0,0 +1 @@
+int say_hello(void);
-- 
GitLab