[Git][ghc/ghc][wip/T18527] 2 commits: testsuite: Add test for #18527
Ben Gamari
gitlab at gitlab.haskell.org
Thu Aug 6 18:05:16 UTC 2020
Ben Gamari pushed to branch wip/T18527 at Glasgow Haskell Compiler / GHC
Commits:
187e2267 by Ben Gamari at 2020-08-06T14:05:06-04:00
testsuite: Add test for #18527
- - - - -
b39b0afb by Ben Gamari at 2020-08-06T14:05:10-04:00
testsuite: Fix prog001
Previously it failed as the `ghc` package was not visible.
- - - - -
5 changed files:
- + testsuite/tests/codeGen/should_run/T18527.hs
- + testsuite/tests/codeGen/should_run/T18527.stdout
- + testsuite/tests/codeGen/should_run/T18527FFI.c
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/concurrent/prog001/all.T
Changes:
=====================================
testsuite/tests/codeGen/should_run/T18527.hs
=====================================
@@ -0,0 +1,20 @@
+{-# 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
=====================================
testsuite/tests/codeGen/should_run/T18527.stdout
=====================================
@@ -0,0 +1,3 @@
+ffi call
+ffi call
+
=====================================
testsuite/tests/codeGen/should_run/T18527FFI.c
=====================================
@@ -0,0 +1,14 @@
+#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;
+}
+
=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -207,3 +207,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'])
=====================================
testsuite/tests/concurrent/prog001/all.T
=====================================
@@ -16,4 +16,4 @@ test('concprog001', [extra_files(['Arithmetic.hs', 'Converter.hs', 'Mult.hs', 'S
when(fast(), skip), only_ways(['threaded2']),
fragile(16604),
run_timeout_multiplier(2)],
- multimod_compile_and_run, ['Mult', ''])
+ multimod_compile_and_run, ['Mult', '-package ghc'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/78dd499beaafe7d85d70d52d1eafeb87c9fa3c30...b39b0afbe90ae48c34e326fd7cf85b651ff36e17
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/78dd499beaafe7d85d70d52d1eafeb87c9fa3c30...b39b0afbe90ae48c34e326fd7cf85b651ff36e17
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/20200806/441fdfa6/attachment-0001.html>
More information about the ghc-commits
mailing list