[Git][ghc/ghc][wip/supersven/ghc-master-riscv-ncg] Try to fix CCallConv test
Sven Tennie (@supersven)
gitlab at gitlab.haskell.org
Mon Sep 9 19:19:40 UTC 2024
Sven Tennie pushed to branch wip/supersven/ghc-master-riscv-ncg at Glasgow Haskell Compiler / GHC
Commits:
69230df5 by Sven Tennie at 2024-09-09T21:19:17+02:00
Try to fix CCallConv test
- Make ccalls's results strict
- Use better test config
- - - - -
3 changed files:
- testsuite/tests/codeGen/should_run/CCallConv.hs
- testsuite/tests/codeGen/should_run/CCallConv_c.c
- testsuite/tests/codeGen/should_run/all.T
Changes:
=====================================
testsuite/tests/codeGen/should_run/CCallConv.hs
=====================================
@@ -3,6 +3,7 @@
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UnliftedFFITypes #-}
+{-# LANGUAGE BangPatterns #-}
-- | This test ensures that sub-word signed and unsigned parameters are correctly
-- handed over to C functions. I.e. it asserts the calling-convention.
@@ -92,18 +93,18 @@ main =
-- twos-complement, which is the same as the max word value.
let i8 :: Int8# = intToInt8# (-1#)
w8 :: Word8# = wordToWord8# (255##)
- res8 :: Int64# = fun8 i8 w8 i8 i8 i8 i8 i8 i8 w8 i8
+ !res8 :: Int64# = fun8 i8 w8 i8 i8 i8 i8 i8 i8 w8 i8
expected_res8 :: Int64 = 2 * (fromInteger . fromIntegral) (maxBound :: Word8) + 8 * (-1)
i16 :: Int16# = intToInt16# (-1#)
w16 :: Word16# = wordToWord16# (65535##)
- res16 :: Int64# = fun16 i16 w16 i16 i16 i16 i16 i16 i16 w16 i16
+ !res16 :: Int64# = fun16 i16 w16 i16 i16 i16 i16 i16 i16 w16 i16
expected_res16 :: Int64 = 2 * (fromInteger . fromIntegral) (maxBound :: Word16) + 8 * (-1)
i32 :: Int32# = intToInt32# (-1#)
w32 :: Word32# = wordToWord32# (4294967295##)
- res32 :: Int64# = fun32 i32 w32 i32 i32 i32 i32 i32 i32 w32 i32
+ !res32 :: Int64# = fun32 i32 w32 i32 i32 i32 i32 i32 i32 w32 i32
expected_res32 :: Int64 = 2 * (fromInteger . fromIntegral) (maxBound :: Word32) + 8 * (-1)
- resFloat :: Float = F# (funFloat 1.0# 1.1# 1.2# 1.3# 1.4# 1.5# 1.6# 1.7# 1.8# 1.9#)
- resDouble :: Double = D# (funDouble 1.0## 1.1## 1.2## 1.3## 1.4## 1.5## 1.6## 1.7## 1.8## 1.9##)
+ !resFloat :: Float = F# (funFloat 1.0# 1.1# 1.2# 1.3# 1.4# 1.5# 1.6# 1.7# 1.8# 1.9#)
+ !resDouble :: Double = D# (funDouble 1.0## 1.1## 1.2## 1.3## 1.4## 1.5## 1.6## 1.7## 1.8## 1.9##)
in do
print $ "fun8 result:" ++ show (I64# res8)
assertEqual expected_res8 (I64# res8)
=====================================
testsuite/tests/codeGen/should_run/CCallConv_c.c
=====================================
@@ -1,5 +1,5 @@
-#include "stdint.h"
-#include "stdio.h"
+#include <stdint.h>
+#include <stdio.h>
int64_t fun8(int8_t a0, uint8_t a1, int8_t a2, int8_t a3, int8_t a4, int8_t a5,
int8_t a6, int8_t a7, int8_t s0, uint8_t s1) {
=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -251,7 +251,4 @@ test('T23034', req_c, compile_and_run, ['-O2 T23034_c.c'])
test('T24700', normal, compile_and_run, ['-O'])
test('T24893', normal, compile_and_run, ['-O'])
-test('CCallConv',
- [],
- multi_compile_and_run,
- ['CCallConv', [('CCallConv_c.c', '')], ''])
+test('CCallConv', req_c, compile_and_run, ['CCallConv_c.c'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/69230df530a8035c2f1c682904b868d2c5b8a9af
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/69230df530a8035c2f1c682904b868d2c5b8a9af
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/20240909/c74a872e/attachment-0001.html>
More information about the ghc-commits
mailing list