Skip to content
Snippets Groups Projects
Commit 44f958c8 authored by Ben Gamari's avatar Ben Gamari
Browse files

testsuite: Add test for #18527

parent b260f31f
No related branches found
Tags ghc-7.4.1-release
No related merge requests found
{-# LANGUAGE ForeignFunctionInterface #-}
module Main where
import Data.Bits (setBit)
import Data.Word (Word32)
import Data.Int (Int64)
main :: IO ()
main = offending 100 0 1
offending :: Int64 -> Int64 -> Word32 -> IO ()
offending h i id = do
oldMask <- sendMessage h (2245) i 0
let newMask = setBit oldMask (fromIntegral id)
sendMessage h (2244) i newMask
return ()
foreign import ccall "func"
sendMessage :: Int64 -> Word32 -> Int64 -> Int64 -> IO Int64
ffi call
ffi call
#include <stdio.h>
#include <stdint.h>
int64_t func(int64_t a, uint32_t b, int64_t c, int64_t d) {
printf("ffi call");
if (a == 1) {
printf(" with corrupted convention\n");
}
else {
printf("\n");
}
return 0;
}
......@@ -205,3 +205,4 @@ test('T16449_2', exit_code(0), compile_and_run, [''])
test('T16846', [only_ways(['optasm']), exit_code(1)], compile_and_run, [''])
test('T17920', cmm_src, compile_and_run, [''])
test('T18527', normal, compile_and_run, ['T18527FFI.c'])
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