[Git][ghc/ghc][wip/ncg-simd] add simd012 test

sheaf (@sheaf) gitlab at gitlab.haskell.org
Tue Jun 18 09:37:14 UTC 2024



sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC


Commits:
4d98b2de by sheaf at 2024-06-18T11:37:06+02:00
add simd012 test

- - - - -


3 changed files:

- testsuite/tests/simd/should_run/all.T
- + testsuite/tests/simd/should_run/simd012.hs
- + testsuite/tests/simd/should_run/simd012.stdout


Changes:

=====================================
testsuite/tests/simd/should_run/all.T
=====================================
@@ -16,3 +16,4 @@ test('simd008', [], compile_and_run, [''])
 test('simd009', [req_th, extra_files(['Simd009b.hs', 'Simd009c.hs'])], multimod_compile_and_run, ['simd009', ''])
 test('simd010', [], compile_and_run, [''])
 test('simd011', [when(have_cpu_feature('fma'), extra_hc_opts('-mfma'))], compile_and_run, [''])
+test('simd012', [], compile_and_run, [''])


=====================================
testsuite/tests/simd/should_run/simd012.hs
=====================================
@@ -0,0 +1,72 @@
+{-# LANGUAGE UnboxedTuples, MagicHash #-}
+
+module Main where
+
+import GHC.Exts
+import GHC.Word
+
+main :: IO ()
+main =
+  print $
+    tuple4b_a tuple4b
+      3000 3001 3002 3003
+      3004 3005 3006 3007
+      3008 3009 3010 3011
+      3012 3013 3014 3015
+      3016 3017 3018 3019
+
+type T4b =  Float -> Double -> Float -> Double
+         -> Float -> Double -> Float -> Double
+         -> Float -> Double -> Float -> Double
+         -> Float -> Double -> Float -> Double
+         -> Float -> Double -> Float -> Double
+         -> (# Float#, Double#, Float#, Double#
+             , Float#, Double#, Float#, Double#
+             , Float#, Double#, Float#, Double#
+             , Float#, Double#, Float#, Double#
+             , Float#, Double#, Float#, Double# #)
+tuple4b :: T4b
+tuple4b (F# f1) (D# d1) (F# f2) (D# d2)
+       (F# f3) (D# d3) (F# f4) (D# d4)
+       (F# f5) (D# d5) (F# f6) (D# d6)
+       (F# f7) (D# d7) (F# f8) (D# d8)
+       (F# f9) (D# d9) (F# f10) (D# d10) =
+    (# f1, d1, f2, d2
+     , f3, d3, f4, d4
+     , f5, d5, f6, d6
+     , f7, d7, f8, d8
+     , f9, d9, f10, d10
+     #)
+
+tuple4b_a :: T4b
+          -> Float -> Double -> Float -> Double
+          -> Float -> Double -> Float -> Double
+          -> Float -> Double -> Float -> Double
+          -> Float -> Double -> Float -> Double
+          -> Float -> Double -> Float -> Double
+          -> ( (Float, Double, Float, Double)
+             , (Float, Double, Float, Double)
+             , (Float, Double, Float, Double)
+             , (Float, Double, Float, Double)
+             , (Float, Double, Float, Double)
+             )
+tuple4b_a h f1 d1 f2 d2
+           f3 d3 f4 d4
+           f5 d5 f6 d6
+           f7 d7 f8 d8
+           f9 d9 f10 d10 =
+    case h f1 d1 f2 d2
+           f3 d3 f4 d4
+           f5 d5 f6 d6
+           f7 d7 f8 d8
+           f9 d9 f10 d10 of
+      (# g1, e1, g2, e2
+       , g3, e3, g4, e4
+       , g5, e5, g6, e6
+       , g7, e7, g8, e8
+       , g9, e9, g10, e10 #) ->
+        ( (F# g1, D# e1, F# g2, D# e2)
+        , (F# g3, D# e3, F# g4, D# e4)
+        , (F# g5, D# e5, F# g6, D# e6)
+        , (F# g7, D# e7, F# g8, D# e8)
+        , (F# g9, D# e9, F# g10, D# e10) )


=====================================
testsuite/tests/simd/should_run/simd012.stdout
=====================================
@@ -0,0 +1 @@
+((3000.0,3001.0,3002.0,3003.0),(3004.0,3005.0,3006.0,3007.0),(3008.0,3009.0,3010.0,3011.0),(3012.0,3013.0,3014.0,3015.0),(3016.0,3017.0,3018.0,3019.0))



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4d98b2de41ba28d5f6403c42250fb97ad168cf80

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4d98b2de41ba28d5f6403c42250fb97ad168cf80
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/20240618/d7a4f788/attachment-0001.html>


More information about the ghc-commits mailing list