Skip to content
Snippets Groups Projects
Commit d23afb8c authored by Ben Gamari's avatar Ben Gamari Committed by Marge Bot
Browse files

testsuite: Add broken test for CApiFFI with -fprefer-bytecode

See #24634.
parent 23c3e624
No related branches found
No related tags found
No related merge requests found
{-# 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) |]
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Hello
$(mkHello)
main :: IO ()
main = hello >>= print
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
test('T24634',
[extra_files(['hello.h', 'hello.c', 'Hello.hs', 'Main.hs']),
req_interp,
expect_broken(24634),
],
makefile_test,
[''])
#include "hello.h"
int say_hello() {
return 42;
}
int say_hello(void);
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