Skip to content
Snippets Groups Projects
Commit 3485c142 authored by Peter Trommler's avatar Peter Trommler :drum:
Browse files

PPC NCG: Fix sign hints in C calls

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

Fixes #23034
parent c8a8727e
Branches wip/simon-perf
No related tags found
1 merge request!12885PPC NCG: Fix sign hints in C calls
Pipeline #97303 passed
......@@ -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)
......
void t_printf(signed long a, signed int b, signed short c, signed char d);
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)
-1 -2 -3 -4
#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);
}
......@@ -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'])
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