[Git][ghc/ghc][wip/supersven/ghc-master-riscv-ncg] Try to fix CCallConv test

Sven Tennie (@supersven) gitlab at gitlab.haskell.org
Tue Sep 10 10:05:36 UTC 2024



Sven Tennie pushed to branch wip/supersven/ghc-master-riscv-ncg at Glasgow Haskell Compiler / GHC


Commits:
5ddc125e by Sven Tennie at 2024-09-10T12:04:23+02:00
Try to fix CCallConv test

- Enforce order of thunks
- Use better test config
- Flush stdout

- - - - -


4 changed files:

- testsuite/tests/codeGen/should_run/CCallConv.hs
- testsuite/tests/codeGen/should_run/CCallConv.stdout
- testsuite/tests/codeGen/should_run/CCallConv_c.c
- testsuite/tests/codeGen/should_run/all.T


Changes:

=====================================
testsuite/tests/codeGen/should_run/CCallConv.hs
=====================================
@@ -15,6 +15,7 @@ module Main where
 import Data.Word
 import GHC.Exts
 import GHC.Int
+import System.IO
 
 foreign import ccall "fun8"
   fun8 ::
@@ -87,34 +88,42 @@ foreign import ccall "funDouble"
     Double# -- result
 
 main :: IO ()
-main =
+main = do
   -- N.B. the values here aren't choosen by accident: -1 means all bits one in
   -- 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
       expected_res8 :: Int64 = 2 * (fromInteger . fromIntegral) (maxBound :: Word8) + 8 * (-1)
-      i16 :: Int16# = intToInt16# (-1#)
+  print $ "fun8 result:" ++ show (I64# res8)
+  hFlush stdout
+  assertEqual expected_res8 (I64# res8)
+
+  let i16 :: Int16# = intToInt16# (-1#)
       w16 :: Word16# = wordToWord16# (65535##)
       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#)
+  print $ "fun16 result:" ++ show (I64# res16)
+  hFlush stdout
+  assertEqual expected_res16 (I64# res16)
+
+  let i32 :: Int32# = intToInt32# (-1#)
       w32 :: Word32# = wordToWord32# (4294967295##)
       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##)
-   in do
-        print $ "fun8 result:" ++ show (I64# res8)
-        assertEqual expected_res8 (I64# res8)
-        print $ "fun16 result:" ++ show (I64# res16)
-        assertEqual expected_res16 (I64# res16)
-        print $ "fun32 result:" ++ show (I64# res32)
-        assertEqual expected_res32 (I64# res32)
-        print $ "funFloat result:" ++ show resFloat
-        assertEqual (14.5 :: Float) resFloat
-        print $ "funDouble result:" ++ show resDouble
-        assertEqual (14.5 :: Double) resDouble
+  print $ "fun32 result:" ++ show (I64# res32)
+  hFlush stdout
+  assertEqual expected_res32 (I64# res32)
+
+  let resFloat :: Float = F# (funFloat 1.0# 1.1# 1.2# 1.3# 1.4# 1.5# 1.6# 1.7# 1.8# 1.9#)
+  print $ "funFloat result:" ++ show resFloat
+  hFlush stdout
+  assertEqual (14.5 :: Float) resFloat
+
+  let resDouble :: Double = D# (funDouble 1.0## 1.1## 1.2## 1.3## 1.4## 1.5## 1.6## 1.7## 1.8## 1.9##)
+  print $ "funDouble result:" ++ show resDouble
+  hFlush stdout
+  assertEqual (14.5 :: Double) resDouble
 
 assertEqual :: (Eq a, Show a) => a -> a -> IO ()
 assertEqual a b =


=====================================
testsuite/tests/codeGen/should_run/CCallConv.stdout
=====================================
@@ -1,11 +1,6 @@
-"fun8 result:502"
-"fun16 result:131062"
-"fun32 result:8589934582"
-"funFloat result:14.5"
-"funDouble result:14.5"
-fun32:
+fun8:
 a0: 0xffffffff -1
-a1: 0xffffffff 4294967295
+a1: 0xff 255
 a2: 0xffffffff -1
 a3: 0xffffffff -1
 a4: 0xffffffff -1
@@ -13,7 +8,8 @@ a5: 0xffffffff -1
 a6: 0xffffffff -1
 a7: 0xffffffff -1
 s0: 0xffffffff -1
-s1: 0xffffffff 4294967295
+s1: 0xff 255
+"fun8 result:502"
 fun16:
 a0: 0xffffffff -1
 a1: 0xffff 65535
@@ -25,9 +21,10 @@ a6: 0xffffffff -1
 a7: 0xffffffff -1
 s0: 0xffffffff -1
 s1: 0xffff 65535
-fun8:
+"fun16 result:131062"
+fun32:
 a0: 0xffffffff -1
-a1: 0xff 255
+a1: 0xffffffff 4294967295
 a2: 0xffffffff -1
 a3: 0xffffffff -1
 a4: 0xffffffff -1
@@ -35,7 +32,8 @@ a5: 0xffffffff -1
 a6: 0xffffffff -1
 a7: 0xffffffff -1
 s0: 0xffffffff -1
-s1: 0xff 255
+s1: 0xffffffff 4294967295
+"fun32 result:8589934582"
 funFloat:
 a0: 1.000000
 a1: 1.100000
@@ -47,6 +45,7 @@ a6: 1.600000
 a7: 1.700000
 s0: 1.800000
 s1: 1.900000
+"funFloat result:14.5"
 funDouble:
 a0: 1.000000
 a1: 1.100000
@@ -58,3 +57,4 @@ a6: 1.600000
 a7: 1.700000
 s0: 1.800000
 s1: 1.900000
+"funDouble result:14.5"


=====================================
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) {
@@ -15,6 +15,8 @@ int64_t fun8(int8_t a0, uint8_t a1, int8_t a2, int8_t a3, int8_t a4, int8_t a5,
   printf("s0: %#x %hhd\n", s0, s0);
   printf("s1: %#x %hhu\n", s1, s1);
 
+  fflush(stdout);
+
   return a0 + a1 + a2 + a3 + a4 + a5 + a6 + a7 + s0 + s1;
 }
 
@@ -32,6 +34,8 @@ int64_t fun16(int16_t a0, uint16_t a1, int16_t a2, int16_t a3, int16_t a4,
   printf("s0: %#x %hd\n", s0, s0);
   printf("s1: %#x %hu\n", s1, s1);
 
+  fflush(stdout);
+
   return a0 + a1 + a2 + a3 + a4 + a5 + a6 + a7 + s0 + s1;
 }
 
@@ -49,6 +53,8 @@ int64_t fun32(int32_t a0, uint32_t a1, int32_t a2, int32_t a3, int32_t a4,
   printf("s0: %#x %d\n", s0, s0);
   printf("s1: %#x %u\n", s1, s1);
 
+  fflush(stdout);
+
   // Ensure the addition happens in long int (not just int) precission.
   // Otherwise, the result is truncated during the operation.
   int64_t force_int64_precission = 0;
@@ -70,6 +76,8 @@ float funFloat(float a0, float a1, float a2, float a3, float a4, float a5,
   printf("s0: %f\n", s0);
   printf("s1: %f\n", s1);
 
+  fflush(stdout);
+
   return a0 + a1 + a2 + a3 + a4 + a5 + a6 + a7 + s0 + s1;
 }
 
@@ -87,5 +95,7 @@ double funDouble(double a0, double a1, double a2, double a3, double a4, double a
   printf("s0: %f\n", s0);
   printf("s1: %f\n", s1);
 
+  fflush(stdout);
+
   return a0 + a1 + a2 + a3 + a4 + a5 + a6 + a7 + s0 + 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/5ddc125e968a6fb19c90430523312f7c781e5631

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5ddc125e968a6fb19c90430523312f7c781e5631
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/20240910/5414f022/attachment-0001.html>


More information about the ghc-commits mailing list