[Git][ghc/ghc][wip/T23034] PPC NCG: Fix sign hints in C calls

Peter Trommler (@trommler) gitlab at gitlab.haskell.org
Mon Jun 24 13:18:19 UTC 2024



Peter Trommler pushed to branch wip/T23034 at Glasgow Haskell Compiler / GHC


Commits:
3485c142 by Peter Trommler at 2024-06-24T15:18:03+02:00
PPC NCG: Fix sign hints in C calls

Sign hints for parameters are in the second component of the pair.

Fixes #23034

- - - - -


6 changed files:

- compiler/GHC/CmmToAsm/PPC/CodeGen.hs
- + testsuite/tests/codeGen/should_run/T23034.h
- + testsuite/tests/codeGen/should_run/T23034.hs
- + testsuite/tests/codeGen/should_run/T23034.stdout
- + testsuite/tests/codeGen/should_run/T23034_c.c
- testsuite/tests/codeGen/should_run/all.T


Changes:

=====================================
compiler/GHC/CmmToAsm/PPC/CodeGen.hs
=====================================
@@ -1770,7 +1770,7 @@ genCCall' config gcp target dest_regs args
                                 _ -> panic "genCall': unknown calling conv."
 
         argReps = map (cmmExprType platform) args
-        (argHints, _) = foreignTargetHints target
+        (_, argHints) = foreignTargetHints target
 
         roundTo a x | x `mod` a == 0 = x
                     | otherwise = x + a - (x `mod` a)


=====================================
testsuite/tests/codeGen/should_run/T23034.h
=====================================
@@ -0,0 +1 @@
+void t_printf(signed long a, signed int b, signed short c, signed char d);


=====================================
testsuite/tests/codeGen/should_run/T23034.hs
=====================================
@@ -0,0 +1,8 @@
+module Main where
+
+import Foreign.C
+
+foreign import ccall unsafe "T23034.h t_printf"
+  t_printf :: CLong -> CInt -> CShort -> CSChar -> IO ()
+
+main = t_printf (-1) (-2) (-3) (-4)


=====================================
testsuite/tests/codeGen/should_run/T23034.stdout
=====================================
@@ -0,0 +1 @@
+-1 -2 -3 -4


=====================================
testsuite/tests/codeGen/should_run/T23034_c.c
=====================================
@@ -0,0 +1,6 @@
+#include "T23034.h"
+#include <stdio.h>
+
+void t_printf(signed long a, signed int b, signed short c, signed char d) {
+  printf("%ld %ld %ld %ld\n", a, 0L + b, 0L + c, 0L + d);
+}


=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -247,3 +247,6 @@ test('T24295b', normal, compile_and_run, ['-O -floopification -fpedantic-bottoms
 test('T24664a', normal, compile_and_run, ['-O'])
 test('T24664b', normal, compile_and_run, ['-O'])
 test('CtzClz0', normal, compile_and_run, [''])
+test('T23034', [req_c
+               , when(arch('x86_64') and opsys('darwin'), expect_broken(25018))
+               ], compile_and_run, ['-O2 T23034_c.c'])



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3485c142300a13de0d4aecfc3d4d6d886de350fb
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/20240624/1dac04b7/attachment-0001.html>


More information about the ghc-commits mailing list