[Git][ghc/ghc][master] testsuite: Add broken test for CApiFFI with -fprefer-bytecode

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Apr 12 12:20:26 UTC 2024



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
d23afb8c by Ben Gamari at 2024-04-12T08:17:56-04:00
testsuite: Add broken test for CApiFFI with -fprefer-bytecode

See #24634.

- - - - -


6 changed files:

- + testsuite/tests/bytecode/T24634/Hello.hs
- + testsuite/tests/bytecode/T24634/Main.hs
- + testsuite/tests/bytecode/T24634/Makefile
- + testsuite/tests/bytecode/T24634/all.T
- + testsuite/tests/bytecode/T24634/hello.c
- + testsuite/tests/bytecode/T24634/hello.h


Changes:

=====================================
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) |]


=====================================
testsuite/tests/bytecode/T24634/Main.hs
=====================================
@@ -0,0 +1,10 @@
+{-# LANGUAGE TemplateHaskell #-}
+
+module Main where
+
+import Hello
+
+$(mkHello)
+
+main :: IO ()
+main = hello >>= print


=====================================
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


=====================================
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,
+     [''])


=====================================
testsuite/tests/bytecode/T24634/hello.c
=====================================
@@ -0,0 +1,5 @@
+#include "hello.h"
+
+int say_hello() {
+  return 42;
+}


=====================================
testsuite/tests/bytecode/T24634/hello.h
=====================================
@@ -0,0 +1 @@
+int say_hello(void);



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d23afb8c63d22af310b3c19f7c311934d02e3a31

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d23afb8c63d22af310b3c19f7c311934d02e3a31
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/20240412/fc44124f/attachment-0001.html>


More information about the ghc-commits mailing list