From 25850b22e76a2c23f549caff38ccd0da134051de Mon Sep 17 00:00:00 2001 From: ARATA Mizuki <minorinoki@gmail.com> Date: Sat, 15 Mar 2025 21:39:07 +0900 Subject: [PATCH] Fix code generation for SSE vector operations The new implementation generates correct code even if the registers overlap. Closes #25859 --- compiler/GHC/CmmToAsm/X86/CodeGen.hs | 22 ++- testsuite/tests/simd/should_run/all.T | 10 ++ .../tests/simd/should_run/doublex2_arith.hs | 95 +++++++++++++ .../simd/should_run/doublex2_arith.stdout | 21 +++ .../should_run/doublex2_arith_baseline.hs | 95 +++++++++++++ .../should_run/doublex2_arith_baseline.stdout | 21 +++ .../tests/simd/should_run/doublex2_fma.hs | 133 ++++++++++++++++++ .../tests/simd/should_run/doublex2_fma.stdout | 48 +++++++ .../tests/simd/should_run/floatx4_arith.hs | 95 +++++++++++++ .../simd/should_run/floatx4_arith.stdout | 21 +++ .../simd/should_run/floatx4_arith_baseline.hs | 95 +++++++++++++ .../should_run/floatx4_arith_baseline.stdout | 21 +++ .../tests/simd/should_run/floatx4_fma.hs | 133 ++++++++++++++++++ .../tests/simd/should_run/floatx4_fma.stdout | 48 +++++++ 14 files changed, 852 insertions(+), 6 deletions(-) create mode 100644 testsuite/tests/simd/should_run/doublex2_arith.hs create mode 100644 testsuite/tests/simd/should_run/doublex2_arith.stdout create mode 100644 testsuite/tests/simd/should_run/doublex2_arith_baseline.hs create mode 100644 testsuite/tests/simd/should_run/doublex2_arith_baseline.stdout create mode 100644 testsuite/tests/simd/should_run/doublex2_fma.hs create mode 100644 testsuite/tests/simd/should_run/doublex2_fma.stdout create mode 100644 testsuite/tests/simd/should_run/floatx4_arith.hs create mode 100644 testsuite/tests/simd/should_run/floatx4_arith.stdout create mode 100644 testsuite/tests/simd/should_run/floatx4_arith_baseline.hs create mode 100644 testsuite/tests/simd/should_run/floatx4_arith_baseline.stdout create mode 100644 testsuite/tests/simd/should_run/floatx4_fma.hs create mode 100644 testsuite/tests/simd/should_run/floatx4_fma.stdout diff --git a/compiler/GHC/CmmToAsm/X86/CodeGen.hs b/compiler/GHC/CmmToAsm/X86/CodeGen.hs index 5047fc3dc8b..b6f27e5af12 100644 --- a/compiler/GHC/CmmToAsm/X86/CodeGen.hs +++ b/compiler/GHC/CmmToAsm/X86/CodeGen.hs @@ -1666,14 +1666,20 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps -> CmmExpr -> NatM Register vector_float_op_sse op l w expr1 expr2 = do - (reg1, exp1) <- getSomeReg expr1 - (reg2, exp2) <- getSomeReg expr2 + -- This function is similar to genTrivialCode, but re-using it would require + -- handling alignment correctly: SSE vector instructions typically require 16-byte + -- alignment for their memory operand (this restriction is relaxed with VEX-encoded + -- instructions). + -- For now, we always load the value into a register and avoid the alignment issue. + exp1_code <- getAnyReg expr1 + (reg2, exp2_code) <- getSomeReg expr2 let format = case w of W32 -> VecFormat l FmtFloat W64 -> VecFormat l FmtDouble _ -> pprPanic "Floating-point SSE vector operation not supported at this width" (text "width:" <+> ppr w) - code dst = case op of + tmp <- getNewRegNat format + let code dst = case op of VA_Add -> arithInstr ADD VA_Sub -> arithInstr SUB VA_Mul -> arithInstr MUL @@ -1683,9 +1689,13 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps where -- opcode src2 src1 <==> src1 = src1 `opcode` src2 arithInstr instr - = exp1 `appOL` exp2 `snocOL` - (MOVU format (OpReg reg1) (OpReg dst)) `snocOL` - (instr format (OpReg reg2) (OpReg dst)) + | dst == reg2 = exp2_code `snocOL` + (MOVU format (OpReg reg2) (OpReg tmp)) `appOL` + exp1_code dst `snocOL` + instr format (OpReg tmp) (OpReg dst) + | otherwise = exp2_code `appOL` + exp1_code dst `snocOL` + instr format (OpReg reg2) (OpReg dst) return (Any format code) -------------------- vector_float_extract :: Length diff --git a/testsuite/tests/simd/should_run/all.T b/testsuite/tests/simd/should_run/all.T index b18dd002489..f0ccd391d63 100644 --- a/testsuite/tests/simd/should_run/all.T +++ b/testsuite/tests/simd/should_run/all.T @@ -24,6 +24,8 @@ test('word8x16_basic_baseline', [], compile_and_run, ['']) test('word16x8_basic_baseline', [], compile_and_run, ['']) test('word32x4_basic_baseline', [], compile_and_run, ['']) test('word64x2_basic_baseline', [], compile_and_run, ['']) +test('floatx4_arith_baseline', [], compile_and_run, ['']) +test('doublex2_arith_baseline', [], compile_and_run, ['']) test('T25658', [], compile_and_run, ['']) # #25658 is a bug with SSE2 code generation test('T25659', [], compile_and_run, ['']) @@ -81,6 +83,14 @@ test('word8x16_basic', [], compile_and_run, ['']) test('word16x8_basic', [], compile_and_run, ['']) test('word32x4_basic', [], compile_and_run, ['']) test('word64x2_basic', [], compile_and_run, ['']) +test('floatx4_arith', [], compile_and_run, ['']) +test('doublex2_arith', [], compile_and_run, ['']) +test('floatx4_fma', [ unless(have_cpu_feature('fma'), skip) + , extra_hc_opts('-mfma') + ], compile_and_run, ['']) +test('doublex2_fma', [ unless(have_cpu_feature('fma'), skip) + , extra_hc_opts('-mfma') + ], compile_and_run, ['']) test('T22187', [],compile,['']) test('T22187_run', [],compile_and_run,['']) diff --git a/testsuite/tests/simd/should_run/doublex2_arith.hs b/testsuite/tests/simd/should_run/doublex2_arith.hs new file mode 100644 index 00000000000..9db2d77c1dd --- /dev/null +++ b/testsuite/tests/simd/should_run/doublex2_arith.hs @@ -0,0 +1,95 @@ +{-# LANGUAGE MagicHash, UnboxedTuples #-} +import Control.Monad +import Data.Array.Base +import Foreign.Marshal.Array +import GHC.Int +import GHC.IO +import GHC.Prim +import GHC.Ptr + +data DoubleX2 = DoubleX2 DoubleX2# + +indexAsDoubleX2 :: UArray Int Double -> Int -> DoubleX2# +indexAsDoubleX2 (UArray l _ _ ba) i = case i - l of + I# i# -> indexDoubleArrayAsDoubleX2# ba i# + +readAsDoubleX2 :: Ptr Double -> Int -> IO DoubleX2 +readAsDoubleX2 (Ptr addr) (I# i) = IO $ \s -> + case readDoubleOffAddrAsDoubleX2# addr i s of + (# s', v #) -> (# s', DoubleX2 v #) + +writeAsDoubleX2 :: Ptr Double -> Int -> DoubleX2# -> IO () +writeAsDoubleX2 (Ptr addr) (I# i) v = IO $ \s -> + (# writeDoubleOffAddrAsDoubleX2# addr i v s, () #) + +arr1 :: UArray Int Double +arr1 = listArray (0,63) [86.1704805043268,-87.055309160875,77.09385349363602,70.43981517796,50.02907568304664,-79.93253267799825,-94.4734175782,30.062138137255715,12.350686811659486,-23.78391700268743,-96.44925698909766,-67.13139854675774,77.84360517385772,-32.84892092508137,-58.02803492421746,-50.79004702787717,-11.908674906547787,-92.38400254440369,36.41222449165823,-68.6479119817805,87.23932115197337,-37.42852497445781,-64.82933137985788,84.16399940800329,-55.35002818965286,8.630163006731266,73.63479275711025,14.555315332112912,-59.0235004342909,27.431362647878856,36.75482002856153,30.991841701036876,-22.897831600115012,-93.89256411789064,17.639582620461923,94.24572581296609,46.564865390415235,-23.14689831583175,44.286969376764674,-61.7495951058958,37.602886696272556,-47.99709400665984,44.97168988769863,87.51005084451836,-57.245772080078,-74.15908041965238,-22.163672693129797,-36.26569085317567,81.28128900464503,-33.53676733222679,29.57596290010983,0.6835164364159141,-61.13183256365945,5.712281466153783,52.13503127014405,-75.17328181431184,-80.3499374345099,69.19728646446558,63.7669473494779,27.17066306772783,-91.12320723332579,65.78107094275762,-29.222084470705,55.14981850187309] + +input2 :: [Double] +input2 = [-2.1274469530639664,-7.177109378829002,-98.24323405063399,-26.03855917426543,-82.35787006428066,86.84756206888044,66.51501361884274,-69.12618497150666,12.336044450377486,-0.9895575202943405,-10.826450417702162,-23.706389595256866,12.884863406302358,85.91465494902334,-10.791922059638424,83.5855338741751,68.54940218977418,-51.043267529916946,74.89746292225463,74.48290415522592,8.172249887162096,-6.426143126204735,-71.09523683330931,-67.16904290667816,-66.06993212850568,86.03428946847885,25.702893242346008,98.90487021469829,-51.28337546267276,-53.05672041384456,-39.24117195492243,91.65414155791501,87.26058482732314,68.14308311155132,95.0497956861045,-52.545861855432456,-17.050384860987847,-39.54129448813424,94.0049004311935,-87.37548839080712,-15.707343289828259,49.289832041364654,34.873616921124494,-7.712670991606458,-46.75167972060545,-67.53197682090646,-94.04146452769466,-53.28374327444284,-88.55039606421403,-20.010295314180937,16.90312028906486,-70.34859808800593,41.88668735114813,-56.73476319101437,23.34349297210754,97.33003908727085,65.43278416798937,26.006050520144072,4.234841735331756,21.139356688092775,79.81443499673723,-89.92184005873219,-36.90383017318868,-94.20848066738576] + +run :: (DoubleX2# -> DoubleX2# -> DoubleX2#) -> UArray Int Double -> Ptr Double -> IO [Double] +run f a b = allocaArray 64 $ \result -> do + forM_ [0,4..63] $ \i -> do + let v = indexAsDoubleX2 a i + DoubleX2 w <- readAsDoubleX2 b i + writeAsDoubleX2 result i (f v w) + peekArray 64 result +{-# INLINE run #-} + +runN :: (DoubleX2# -> DoubleX2# -> DoubleX2#) -> UArray Int Double -> Ptr Double -> IO [Double] +runN f a b = allocaArray 64 $ \result -> do + forM_ [0,4..63] $ \i -> do + let v = indexAsDoubleX2 a i + DoubleX2 w <- readAsDoubleX2 b i + writeAsDoubleX2 result i (f v w) + peekArray 64 result +{-# NOINLINE runN #-} + +main :: IO () +main = do + withArray input2 $ \arr2 -> do + run (\x _ -> negateDoubleX2# x) arr1 arr2 >>= print + run plusDoubleX2# arr1 arr2 >>= print + run minusDoubleX2# arr1 arr2 >>= print + run timesDoubleX2# arr1 arr2 >>= print + run divideDoubleX2# arr1 arr2 >>= print + -- minDoubleX2# and maxDoubleX2# are not well-defined if the arguments are signed zeros or NaNs. + -- This test case doesn't contain such cases. + run minDoubleX2# arr1 arr2 >>= print + run maxDoubleX2# arr1 arr2 >>= print + runN (\x _ -> negateDoubleX2# x) arr1 arr2 >>= print + runN plusDoubleX2# arr1 arr2 >>= print + runN minusDoubleX2# arr1 arr2 >>= print + runN timesDoubleX2# arr1 arr2 >>= print + runN divideDoubleX2# arr1 arr2 >>= print + runN minDoubleX2# arr1 arr2 >>= print + runN maxDoubleX2# arr1 arr2 >>= print + runN (\_ y -> negateDoubleX2# y) arr1 arr2 >>= print + runN (\x y -> plusDoubleX2# y x) arr1 arr2 >>= print + runN (\x y -> minusDoubleX2# y x) arr1 arr2 >>= print + runN (\x y -> timesDoubleX2# y x) arr1 arr2 >>= print + runN (\x y -> divideDoubleX2# y x) arr1 arr2 >>= print + runN (\x y -> minDoubleX2# y x) arr1 arr2 >>= print + runN (\x y -> maxDoubleX2# y x) arr1 arr2 >>= print + +{- +The values was generated by: +{- cabal: +build-depends: base, random >= 1.3.0 +-} +import System.Random.Stateful +import qualified Data.List as List +import Control.Monad + +main :: IO () +main = do + let xs, ys :: [Double] + (xs, ys) = runStateGen_ (mkStdGen 42) $ \g -> do + a <- replicateM 64 (uniformRM (-100.0, 100.0) g) + b <- replicateM 64 (uniformRM (-100.0, 100.0) g) + pure (a, b) + print $ or $ zipWith (\x y -> isNaN x || isNaN y || (x == 0 && y == 0 && isNegativeZero x /= isNegativeZero y)) xs ys -- should be False + print xs + print ys +-} diff --git a/testsuite/tests/simd/should_run/doublex2_arith.stdout b/testsuite/tests/simd/should_run/doublex2_arith.stdout new file mode 100644 index 00000000000..726044644ea --- /dev/null +++ b/testsuite/tests/simd/should_run/doublex2_arith.stdout @@ -0,0 +1,21 @@ +[-86.1704805043268,87.055309160875,0.0,0.0,-50.02907568304664,79.93253267799825,0.0,0.0,-12.350686811659486,23.78391700268743,0.0,0.0,-77.84360517385772,32.84892092508137,0.0,0.0,11.908674906547787,92.38400254440369,0.0,0.0,-87.23932115197337,37.42852497445781,0.0,0.0,55.35002818965286,-8.630163006731266,0.0,0.0,59.0235004342909,-27.431362647878856,0.0,0.0,22.897831600115012,93.89256411789064,0.0,0.0,-46.564865390415235,23.14689831583175,0.0,0.0,-37.602886696272556,47.99709400665984,0.0,0.0,57.245772080078,74.15908041965238,0.0,0.0,-81.28128900464503,33.53676733222679,0.0,0.0,61.13183256365945,-5.712281466153783,0.0,0.0,80.3499374345099,-69.19728646446558,0.0,0.0,91.12320723332579,-65.78107094275762,0.0,0.0] +[84.04303355126284,-94.232418539704,0.0,0.0,-32.32879438123402,6.915029390882182,0.0,0.0,24.68673126203697,-24.773474522981772,0.0,0.0,90.72846858016008,53.06573402394197,0.0,0.0,56.6407272832264,-143.42727007432063,0.0,0.0,95.41157103913547,-43.85466810066254,0.0,0.0,-121.41996031815854,94.66445247521011,0.0,0.0,-110.30687589696366,-25.625357765965703,0.0,0.0,64.36275322720813,-25.749481006339323,0.0,0.0,29.514480529427388,-62.68819280396599,0.0,0.0,21.895543406444297,1.2927380347048114,0.0,0.0,-103.99745180068345,-141.69105724055885,0.0,0.0,-7.269107059568995,-53.547062646407724,0.0,0.0,-19.245145212511318,-51.02248172486059,0.0,0.0,-14.917153266520529,95.20333698460965,0.0,0.0,-11.308772236588553,-24.140769115974564,0.0,0.0] +[88.29792745739077,-79.878199782046,0.0,0.0,132.3869457473273,-166.7800947468787,0.0,0.0,1.4642361282000138e-2,-22.79435948239309,0.0,0.0,64.95874176755537,-118.76357587410472,0.0,0.0,-80.45807709632197,-41.34073501448674,0.0,0.0,79.06707126481128,-31.002381848253073,0.0,0.0,10.719903938852823,-77.40412646174758,0.0,0.0,-7.740124971618144,80.48808306172342,0.0,0.0,-110.15841642743815,-162.03564722944196,0.0,0.0,63.61525025140308,16.394396172302493,0.0,0.0,53.310229986100815,-97.2869260480245,0.0,0.0,-10.494092359472546,-6.627103598745919,0.0,0.0,169.83168506885906,-13.526472018045851,0.0,0.0,-103.01851991480758,62.447044657168156,0.0,0.0,-145.78272160249927,43.191235944321505,0.0,0.0,-170.93764223006303,155.7029110014898,0.0,0.0] +[-183.32312619298798,624.8054758553743,0.0,0.0,-4120.288114540419,-6941.945593075267,0.0,0.0,152.3586215013224,23.535553932065778,0.0,0.0,1003.0042197192884,-2822.203706726119,0.0,0.0,-816.3325457162158,4715.581357358526,0.0,0.0,712.9415324403122,240.52105848859432,0.0,0.0,3656.9726058012407,742.4899422812755,0.0,0.0,3026.924333892969,-1455.4181385792872,0.0,0.0,-1998.0781767035965,-6398.128800242083,0.0,0.0,-793.9488759066729,915.2583227932016,0.0,0.0,-590.641450026869,-2365.7687020618537,0.0,0.0,2676.3360016465845,5008.109299959703,0.0,0.0,-7197.490333971163,671.080618200834,0.0,0.0,-2560.6099577967398,-324.0849362626553,0.0,0.0,-5257.5201140637355,1799.5481276517735,0.0,0.0,-7272.947300418497,-5915.154940206767,0.0,0.0] +[-40.504173502527706,12.129578158258292,0.0,0.0,-0.6074595620794799,-0.920377391994058,0.0,0.0,1.0011869575649552,24.03490096827619,0.0,0.0,6.0414769422997665,-0.3823436286227533,0.0,0.0,-0.17372397900100517,1.8099155288257465,0.0,0.0,10.675067742240588,5.824415086839656,0.0,0.0,0.837749130451615,0.10031073726590345,0.0,0.0,1.1509285397419264,-0.5170195676233496,0.0,0.0,-0.262407496413492,-1.3778737302535462,0.0,0.0,-2.7310155031724843,0.5853854461638273,0.0,0.0,-2.39396860452037,-0.9737727238830935,0.0,0.0,1.224464498862644,1.0981328240445394,0.0,0.0,-0.9179099430080735,1.6759756318268768,0.0,0.0,-1.4594573223509832,-0.10068397477789229,0.0,0.0,-1.2279767467669243,2.6608148903989064,0.0,0.0,-1.14168830784871,-0.73153608622547,0.0,0.0] +[-2.1274469530639664,-87.055309160875,0.0,0.0,-82.35787006428066,-79.93253267799825,0.0,0.0,12.336044450377486,-23.78391700268743,0.0,0.0,12.884863406302358,-32.84892092508137,0.0,0.0,-11.908674906547787,-92.38400254440369,0.0,0.0,8.172249887162096,-37.42852497445781,0.0,0.0,-66.06993212850568,8.630163006731266,0.0,0.0,-59.0235004342909,-53.05672041384456,0.0,0.0,-22.897831600115012,-93.89256411789064,0.0,0.0,-17.050384860987847,-39.54129448813424,0.0,0.0,-15.707343289828259,-47.99709400665984,0.0,0.0,-57.245772080078,-74.15908041965238,0.0,0.0,-88.55039606421403,-33.53676733222679,0.0,0.0,-61.13183256365945,-56.73476319101437,0.0,0.0,-80.3499374345099,26.006050520144072,0.0,0.0,-91.12320723332579,-89.92184005873219,0.0,0.0] +[86.1704805043268,-7.177109378829002,0.0,0.0,50.02907568304664,86.84756206888044,0.0,0.0,12.350686811659486,-0.9895575202943405,0.0,0.0,77.84360517385772,85.91465494902334,0.0,0.0,68.54940218977418,-51.043267529916946,0.0,0.0,87.23932115197337,-6.426143126204735,0.0,0.0,-55.35002818965286,86.03428946847885,0.0,0.0,-51.28337546267276,27.431362647878856,0.0,0.0,87.26058482732314,68.14308311155132,0.0,0.0,46.564865390415235,-23.14689831583175,0.0,0.0,37.602886696272556,49.289832041364654,0.0,0.0,-46.75167972060545,-67.53197682090646,0.0,0.0,81.28128900464503,-20.010295314180937,0.0,0.0,41.88668735114813,5.712281466153783,0.0,0.0,65.43278416798937,69.19728646446558,0.0,0.0,79.81443499673723,65.78107094275762,0.0,0.0] +[-86.1704805043268,87.055309160875,0.0,0.0,-50.02907568304664,79.93253267799825,0.0,0.0,-12.350686811659486,23.78391700268743,0.0,0.0,-77.84360517385772,32.84892092508137,0.0,0.0,11.908674906547787,92.38400254440369,0.0,0.0,-87.23932115197337,37.42852497445781,0.0,0.0,55.35002818965286,-8.630163006731266,0.0,0.0,59.0235004342909,-27.431362647878856,0.0,0.0,22.897831600115012,93.89256411789064,0.0,0.0,-46.564865390415235,23.14689831583175,0.0,0.0,-37.602886696272556,47.99709400665984,0.0,0.0,57.245772080078,74.15908041965238,0.0,0.0,-81.28128900464503,33.53676733222679,0.0,0.0,61.13183256365945,-5.712281466153783,0.0,0.0,80.3499374345099,-69.19728646446558,0.0,0.0,91.12320723332579,-65.78107094275762,0.0,0.0] +[84.04303355126284,-94.232418539704,0.0,0.0,-32.32879438123402,6.915029390882182,0.0,0.0,24.68673126203697,-24.773474522981772,0.0,0.0,90.72846858016008,53.06573402394197,0.0,0.0,56.6407272832264,-143.42727007432063,0.0,0.0,95.41157103913547,-43.85466810066254,0.0,0.0,-121.41996031815854,94.66445247521011,0.0,0.0,-110.30687589696366,-25.625357765965703,0.0,0.0,64.36275322720813,-25.749481006339323,0.0,0.0,29.514480529427388,-62.68819280396599,0.0,0.0,21.895543406444297,1.2927380347048114,0.0,0.0,-103.99745180068345,-141.69105724055885,0.0,0.0,-7.269107059568995,-53.547062646407724,0.0,0.0,-19.245145212511318,-51.02248172486059,0.0,0.0,-14.917153266520529,95.20333698460965,0.0,0.0,-11.308772236588553,-24.140769115974564,0.0,0.0] +[88.29792745739077,-79.878199782046,0.0,0.0,132.3869457473273,-166.7800947468787,0.0,0.0,1.4642361282000138e-2,-22.79435948239309,0.0,0.0,64.95874176755537,-118.76357587410472,0.0,0.0,-80.45807709632197,-41.34073501448674,0.0,0.0,79.06707126481128,-31.002381848253073,0.0,0.0,10.719903938852823,-77.40412646174758,0.0,0.0,-7.740124971618144,80.48808306172342,0.0,0.0,-110.15841642743815,-162.03564722944196,0.0,0.0,63.61525025140308,16.394396172302493,0.0,0.0,53.310229986100815,-97.2869260480245,0.0,0.0,-10.494092359472546,-6.627103598745919,0.0,0.0,169.83168506885906,-13.526472018045851,0.0,0.0,-103.01851991480758,62.447044657168156,0.0,0.0,-145.78272160249927,43.191235944321505,0.0,0.0,-170.93764223006303,155.7029110014898,0.0,0.0] +[-183.32312619298798,624.8054758553743,0.0,0.0,-4120.288114540419,-6941.945593075267,0.0,0.0,152.3586215013224,23.535553932065778,0.0,0.0,1003.0042197192884,-2822.203706726119,0.0,0.0,-816.3325457162158,4715.581357358526,0.0,0.0,712.9415324403122,240.52105848859432,0.0,0.0,3656.9726058012407,742.4899422812755,0.0,0.0,3026.924333892969,-1455.4181385792872,0.0,0.0,-1998.0781767035965,-6398.128800242083,0.0,0.0,-793.9488759066729,915.2583227932016,0.0,0.0,-590.641450026869,-2365.7687020618537,0.0,0.0,2676.3360016465845,5008.109299959703,0.0,0.0,-7197.490333971163,671.080618200834,0.0,0.0,-2560.6099577967398,-324.0849362626553,0.0,0.0,-5257.5201140637355,1799.5481276517735,0.0,0.0,-7272.947300418497,-5915.154940206767,0.0,0.0] +[-40.504173502527706,12.129578158258292,0.0,0.0,-0.6074595620794799,-0.920377391994058,0.0,0.0,1.0011869575649552,24.03490096827619,0.0,0.0,6.0414769422997665,-0.3823436286227533,0.0,0.0,-0.17372397900100517,1.8099155288257465,0.0,0.0,10.675067742240588,5.824415086839656,0.0,0.0,0.837749130451615,0.10031073726590345,0.0,0.0,1.1509285397419264,-0.5170195676233496,0.0,0.0,-0.262407496413492,-1.3778737302535462,0.0,0.0,-2.7310155031724843,0.5853854461638273,0.0,0.0,-2.39396860452037,-0.9737727238830935,0.0,0.0,1.224464498862644,1.0981328240445394,0.0,0.0,-0.9179099430080735,1.6759756318268768,0.0,0.0,-1.4594573223509832,-0.10068397477789229,0.0,0.0,-1.2279767467669243,2.6608148903989064,0.0,0.0,-1.14168830784871,-0.73153608622547,0.0,0.0] +[-2.1274469530639664,-87.055309160875,0.0,0.0,-82.35787006428066,-79.93253267799825,0.0,0.0,12.336044450377486,-23.78391700268743,0.0,0.0,12.884863406302358,-32.84892092508137,0.0,0.0,-11.908674906547787,-92.38400254440369,0.0,0.0,8.172249887162096,-37.42852497445781,0.0,0.0,-66.06993212850568,8.630163006731266,0.0,0.0,-59.0235004342909,-53.05672041384456,0.0,0.0,-22.897831600115012,-93.89256411789064,0.0,0.0,-17.050384860987847,-39.54129448813424,0.0,0.0,-15.707343289828259,-47.99709400665984,0.0,0.0,-57.245772080078,-74.15908041965238,0.0,0.0,-88.55039606421403,-33.53676733222679,0.0,0.0,-61.13183256365945,-56.73476319101437,0.0,0.0,-80.3499374345099,26.006050520144072,0.0,0.0,-91.12320723332579,-89.92184005873219,0.0,0.0] +[86.1704805043268,-7.177109378829002,0.0,0.0,50.02907568304664,86.84756206888044,0.0,0.0,12.350686811659486,-0.9895575202943405,0.0,0.0,77.84360517385772,85.91465494902334,0.0,0.0,68.54940218977418,-51.043267529916946,0.0,0.0,87.23932115197337,-6.426143126204735,0.0,0.0,-55.35002818965286,86.03428946847885,0.0,0.0,-51.28337546267276,27.431362647878856,0.0,0.0,87.26058482732314,68.14308311155132,0.0,0.0,46.564865390415235,-23.14689831583175,0.0,0.0,37.602886696272556,49.289832041364654,0.0,0.0,-46.75167972060545,-67.53197682090646,0.0,0.0,81.28128900464503,-20.010295314180937,0.0,0.0,41.88668735114813,5.712281466153783,0.0,0.0,65.43278416798937,69.19728646446558,0.0,0.0,79.81443499673723,65.78107094275762,0.0,0.0] +[2.1274469530639664,7.177109378829002,0.0,0.0,82.35787006428066,-86.84756206888044,0.0,0.0,-12.336044450377486,0.9895575202943405,0.0,0.0,-12.884863406302358,-85.91465494902334,0.0,0.0,-68.54940218977418,51.043267529916946,0.0,0.0,-8.172249887162096,6.426143126204735,0.0,0.0,66.06993212850568,-86.03428946847885,0.0,0.0,51.28337546267276,53.05672041384456,0.0,0.0,-87.26058482732314,-68.14308311155132,0.0,0.0,17.050384860987847,39.54129448813424,0.0,0.0,15.707343289828259,-49.289832041364654,0.0,0.0,46.75167972060545,67.53197682090646,0.0,0.0,88.55039606421403,20.010295314180937,0.0,0.0,-41.88668735114813,56.73476319101437,0.0,0.0,-65.43278416798937,-26.006050520144072,0.0,0.0,-79.81443499673723,89.92184005873219,0.0,0.0] +[84.04303355126284,-94.232418539704,0.0,0.0,-32.32879438123402,6.915029390882182,0.0,0.0,24.68673126203697,-24.773474522981772,0.0,0.0,90.72846858016008,53.06573402394197,0.0,0.0,56.6407272832264,-143.42727007432063,0.0,0.0,95.41157103913547,-43.85466810066254,0.0,0.0,-121.41996031815854,94.66445247521011,0.0,0.0,-110.30687589696366,-25.625357765965703,0.0,0.0,64.36275322720813,-25.749481006339323,0.0,0.0,29.514480529427388,-62.68819280396599,0.0,0.0,21.895543406444297,1.2927380347048114,0.0,0.0,-103.99745180068345,-141.69105724055885,0.0,0.0,-7.269107059568995,-53.547062646407724,0.0,0.0,-19.245145212511318,-51.02248172486059,0.0,0.0,-14.917153266520529,95.20333698460965,0.0,0.0,-11.308772236588553,-24.140769115974564,0.0,0.0] +[-88.29792745739077,79.878199782046,0.0,0.0,-132.3869457473273,166.7800947468787,0.0,0.0,-1.4642361282000138e-2,22.79435948239309,0.0,0.0,-64.95874176755537,118.76357587410472,0.0,0.0,80.45807709632197,41.34073501448674,0.0,0.0,-79.06707126481128,31.002381848253073,0.0,0.0,-10.719903938852823,77.40412646174758,0.0,0.0,7.740124971618144,-80.48808306172342,0.0,0.0,110.15841642743815,162.03564722944196,0.0,0.0,-63.61525025140308,-16.394396172302493,0.0,0.0,-53.310229986100815,97.2869260480245,0.0,0.0,10.494092359472546,6.627103598745919,0.0,0.0,-169.83168506885906,13.526472018045851,0.0,0.0,103.01851991480758,-62.447044657168156,0.0,0.0,145.78272160249927,-43.191235944321505,0.0,0.0,170.93764223006303,-155.7029110014898,0.0,0.0] +[-183.32312619298798,624.8054758553743,0.0,0.0,-4120.288114540419,-6941.945593075267,0.0,0.0,152.3586215013224,23.535553932065778,0.0,0.0,1003.0042197192884,-2822.203706726119,0.0,0.0,-816.3325457162158,4715.581357358526,0.0,0.0,712.9415324403122,240.52105848859432,0.0,0.0,3656.9726058012407,742.4899422812755,0.0,0.0,3026.924333892969,-1455.4181385792872,0.0,0.0,-1998.0781767035965,-6398.128800242083,0.0,0.0,-793.9488759066729,915.2583227932016,0.0,0.0,-590.641450026869,-2365.7687020618537,0.0,0.0,2676.3360016465845,5008.109299959703,0.0,0.0,-7197.490333971163,671.080618200834,0.0,0.0,-2560.6099577967398,-324.0849362626553,0.0,0.0,-5257.5201140637355,1799.5481276517735,0.0,0.0,-7272.947300418497,-5915.154940206767,0.0,0.0] +[-2.4688813856122604e-2,8.244309793404982e-2,0.0,0.0,-1.6462001134310238,-1.086510825557584,0.0,0.0,0.9988144496330215,4.160616269315634e-2,0.0,0.0,0.16552243922317067,-2.6154483170077074,0.0,0.0,-5.7562577472060665,0.552511973113347,0.0,0.0,9.367622053048538e-2,0.1716910599760504,0.0,0.0,1.1936747692724174,9.96902253194693,0.0,0.0,0.8688636743895765,-1.9341627718208594,0.0,0.0,-3.8108667384419426,-0.7257559078479473,0.0,0.0,-0.36616416085457953,1.7082761564252107,0.0,0.0,-0.41771642205823717,-1.0269336729953993,0.0,0.0,0.8166835387460067,0.9106366535123632,0.0,0.0,-1.0894314933803964,0.5966673864523687,0.0,0.0,-0.6851861885136448,-9.93206716566354,0.0,0.0,-0.8143476679284422,0.37582471580729954,0.0,0.0,-0.8758958054710273,-1.3669865626994997,0.0,0.0] +[-2.1274469530639664,-87.055309160875,0.0,0.0,-82.35787006428066,-79.93253267799825,0.0,0.0,12.336044450377486,-23.78391700268743,0.0,0.0,12.884863406302358,-32.84892092508137,0.0,0.0,-11.908674906547787,-92.38400254440369,0.0,0.0,8.172249887162096,-37.42852497445781,0.0,0.0,-66.06993212850568,8.630163006731266,0.0,0.0,-59.0235004342909,-53.05672041384456,0.0,0.0,-22.897831600115012,-93.89256411789064,0.0,0.0,-17.050384860987847,-39.54129448813424,0.0,0.0,-15.707343289828259,-47.99709400665984,0.0,0.0,-57.245772080078,-74.15908041965238,0.0,0.0,-88.55039606421403,-33.53676733222679,0.0,0.0,-61.13183256365945,-56.73476319101437,0.0,0.0,-80.3499374345099,26.006050520144072,0.0,0.0,-91.12320723332579,-89.92184005873219,0.0,0.0] +[86.1704805043268,-7.177109378829002,0.0,0.0,50.02907568304664,86.84756206888044,0.0,0.0,12.350686811659486,-0.9895575202943405,0.0,0.0,77.84360517385772,85.91465494902334,0.0,0.0,68.54940218977418,-51.043267529916946,0.0,0.0,87.23932115197337,-6.426143126204735,0.0,0.0,-55.35002818965286,86.03428946847885,0.0,0.0,-51.28337546267276,27.431362647878856,0.0,0.0,87.26058482732314,68.14308311155132,0.0,0.0,46.564865390415235,-23.14689831583175,0.0,0.0,37.602886696272556,49.289832041364654,0.0,0.0,-46.75167972060545,-67.53197682090646,0.0,0.0,81.28128900464503,-20.010295314180937,0.0,0.0,41.88668735114813,5.712281466153783,0.0,0.0,65.43278416798937,69.19728646446558,0.0,0.0,79.81443499673723,65.78107094275762,0.0,0.0] diff --git a/testsuite/tests/simd/should_run/doublex2_arith_baseline.hs b/testsuite/tests/simd/should_run/doublex2_arith_baseline.hs new file mode 100644 index 00000000000..9db2d77c1dd --- /dev/null +++ b/testsuite/tests/simd/should_run/doublex2_arith_baseline.hs @@ -0,0 +1,95 @@ +{-# LANGUAGE MagicHash, UnboxedTuples #-} +import Control.Monad +import Data.Array.Base +import Foreign.Marshal.Array +import GHC.Int +import GHC.IO +import GHC.Prim +import GHC.Ptr + +data DoubleX2 = DoubleX2 DoubleX2# + +indexAsDoubleX2 :: UArray Int Double -> Int -> DoubleX2# +indexAsDoubleX2 (UArray l _ _ ba) i = case i - l of + I# i# -> indexDoubleArrayAsDoubleX2# ba i# + +readAsDoubleX2 :: Ptr Double -> Int -> IO DoubleX2 +readAsDoubleX2 (Ptr addr) (I# i) = IO $ \s -> + case readDoubleOffAddrAsDoubleX2# addr i s of + (# s', v #) -> (# s', DoubleX2 v #) + +writeAsDoubleX2 :: Ptr Double -> Int -> DoubleX2# -> IO () +writeAsDoubleX2 (Ptr addr) (I# i) v = IO $ \s -> + (# writeDoubleOffAddrAsDoubleX2# addr i v s, () #) + +arr1 :: UArray Int Double +arr1 = listArray (0,63) [86.1704805043268,-87.055309160875,77.09385349363602,70.43981517796,50.02907568304664,-79.93253267799825,-94.4734175782,30.062138137255715,12.350686811659486,-23.78391700268743,-96.44925698909766,-67.13139854675774,77.84360517385772,-32.84892092508137,-58.02803492421746,-50.79004702787717,-11.908674906547787,-92.38400254440369,36.41222449165823,-68.6479119817805,87.23932115197337,-37.42852497445781,-64.82933137985788,84.16399940800329,-55.35002818965286,8.630163006731266,73.63479275711025,14.555315332112912,-59.0235004342909,27.431362647878856,36.75482002856153,30.991841701036876,-22.897831600115012,-93.89256411789064,17.639582620461923,94.24572581296609,46.564865390415235,-23.14689831583175,44.286969376764674,-61.7495951058958,37.602886696272556,-47.99709400665984,44.97168988769863,87.51005084451836,-57.245772080078,-74.15908041965238,-22.163672693129797,-36.26569085317567,81.28128900464503,-33.53676733222679,29.57596290010983,0.6835164364159141,-61.13183256365945,5.712281466153783,52.13503127014405,-75.17328181431184,-80.3499374345099,69.19728646446558,63.7669473494779,27.17066306772783,-91.12320723332579,65.78107094275762,-29.222084470705,55.14981850187309] + +input2 :: [Double] +input2 = [-2.1274469530639664,-7.177109378829002,-98.24323405063399,-26.03855917426543,-82.35787006428066,86.84756206888044,66.51501361884274,-69.12618497150666,12.336044450377486,-0.9895575202943405,-10.826450417702162,-23.706389595256866,12.884863406302358,85.91465494902334,-10.791922059638424,83.5855338741751,68.54940218977418,-51.043267529916946,74.89746292225463,74.48290415522592,8.172249887162096,-6.426143126204735,-71.09523683330931,-67.16904290667816,-66.06993212850568,86.03428946847885,25.702893242346008,98.90487021469829,-51.28337546267276,-53.05672041384456,-39.24117195492243,91.65414155791501,87.26058482732314,68.14308311155132,95.0497956861045,-52.545861855432456,-17.050384860987847,-39.54129448813424,94.0049004311935,-87.37548839080712,-15.707343289828259,49.289832041364654,34.873616921124494,-7.712670991606458,-46.75167972060545,-67.53197682090646,-94.04146452769466,-53.28374327444284,-88.55039606421403,-20.010295314180937,16.90312028906486,-70.34859808800593,41.88668735114813,-56.73476319101437,23.34349297210754,97.33003908727085,65.43278416798937,26.006050520144072,4.234841735331756,21.139356688092775,79.81443499673723,-89.92184005873219,-36.90383017318868,-94.20848066738576] + +run :: (DoubleX2# -> DoubleX2# -> DoubleX2#) -> UArray Int Double -> Ptr Double -> IO [Double] +run f a b = allocaArray 64 $ \result -> do + forM_ [0,4..63] $ \i -> do + let v = indexAsDoubleX2 a i + DoubleX2 w <- readAsDoubleX2 b i + writeAsDoubleX2 result i (f v w) + peekArray 64 result +{-# INLINE run #-} + +runN :: (DoubleX2# -> DoubleX2# -> DoubleX2#) -> UArray Int Double -> Ptr Double -> IO [Double] +runN f a b = allocaArray 64 $ \result -> do + forM_ [0,4..63] $ \i -> do + let v = indexAsDoubleX2 a i + DoubleX2 w <- readAsDoubleX2 b i + writeAsDoubleX2 result i (f v w) + peekArray 64 result +{-# NOINLINE runN #-} + +main :: IO () +main = do + withArray input2 $ \arr2 -> do + run (\x _ -> negateDoubleX2# x) arr1 arr2 >>= print + run plusDoubleX2# arr1 arr2 >>= print + run minusDoubleX2# arr1 arr2 >>= print + run timesDoubleX2# arr1 arr2 >>= print + run divideDoubleX2# arr1 arr2 >>= print + -- minDoubleX2# and maxDoubleX2# are not well-defined if the arguments are signed zeros or NaNs. + -- This test case doesn't contain such cases. + run minDoubleX2# arr1 arr2 >>= print + run maxDoubleX2# arr1 arr2 >>= print + runN (\x _ -> negateDoubleX2# x) arr1 arr2 >>= print + runN plusDoubleX2# arr1 arr2 >>= print + runN minusDoubleX2# arr1 arr2 >>= print + runN timesDoubleX2# arr1 arr2 >>= print + runN divideDoubleX2# arr1 arr2 >>= print + runN minDoubleX2# arr1 arr2 >>= print + runN maxDoubleX2# arr1 arr2 >>= print + runN (\_ y -> negateDoubleX2# y) arr1 arr2 >>= print + runN (\x y -> plusDoubleX2# y x) arr1 arr2 >>= print + runN (\x y -> minusDoubleX2# y x) arr1 arr2 >>= print + runN (\x y -> timesDoubleX2# y x) arr1 arr2 >>= print + runN (\x y -> divideDoubleX2# y x) arr1 arr2 >>= print + runN (\x y -> minDoubleX2# y x) arr1 arr2 >>= print + runN (\x y -> maxDoubleX2# y x) arr1 arr2 >>= print + +{- +The values was generated by: +{- cabal: +build-depends: base, random >= 1.3.0 +-} +import System.Random.Stateful +import qualified Data.List as List +import Control.Monad + +main :: IO () +main = do + let xs, ys :: [Double] + (xs, ys) = runStateGen_ (mkStdGen 42) $ \g -> do + a <- replicateM 64 (uniformRM (-100.0, 100.0) g) + b <- replicateM 64 (uniformRM (-100.0, 100.0) g) + pure (a, b) + print $ or $ zipWith (\x y -> isNaN x || isNaN y || (x == 0 && y == 0 && isNegativeZero x /= isNegativeZero y)) xs ys -- should be False + print xs + print ys +-} diff --git a/testsuite/tests/simd/should_run/doublex2_arith_baseline.stdout b/testsuite/tests/simd/should_run/doublex2_arith_baseline.stdout new file mode 100644 index 00000000000..726044644ea --- /dev/null +++ b/testsuite/tests/simd/should_run/doublex2_arith_baseline.stdout @@ -0,0 +1,21 @@ +[-86.1704805043268,87.055309160875,0.0,0.0,-50.02907568304664,79.93253267799825,0.0,0.0,-12.350686811659486,23.78391700268743,0.0,0.0,-77.84360517385772,32.84892092508137,0.0,0.0,11.908674906547787,92.38400254440369,0.0,0.0,-87.23932115197337,37.42852497445781,0.0,0.0,55.35002818965286,-8.630163006731266,0.0,0.0,59.0235004342909,-27.431362647878856,0.0,0.0,22.897831600115012,93.89256411789064,0.0,0.0,-46.564865390415235,23.14689831583175,0.0,0.0,-37.602886696272556,47.99709400665984,0.0,0.0,57.245772080078,74.15908041965238,0.0,0.0,-81.28128900464503,33.53676733222679,0.0,0.0,61.13183256365945,-5.712281466153783,0.0,0.0,80.3499374345099,-69.19728646446558,0.0,0.0,91.12320723332579,-65.78107094275762,0.0,0.0] +[84.04303355126284,-94.232418539704,0.0,0.0,-32.32879438123402,6.915029390882182,0.0,0.0,24.68673126203697,-24.773474522981772,0.0,0.0,90.72846858016008,53.06573402394197,0.0,0.0,56.6407272832264,-143.42727007432063,0.0,0.0,95.41157103913547,-43.85466810066254,0.0,0.0,-121.41996031815854,94.66445247521011,0.0,0.0,-110.30687589696366,-25.625357765965703,0.0,0.0,64.36275322720813,-25.749481006339323,0.0,0.0,29.514480529427388,-62.68819280396599,0.0,0.0,21.895543406444297,1.2927380347048114,0.0,0.0,-103.99745180068345,-141.69105724055885,0.0,0.0,-7.269107059568995,-53.547062646407724,0.0,0.0,-19.245145212511318,-51.02248172486059,0.0,0.0,-14.917153266520529,95.20333698460965,0.0,0.0,-11.308772236588553,-24.140769115974564,0.0,0.0] +[88.29792745739077,-79.878199782046,0.0,0.0,132.3869457473273,-166.7800947468787,0.0,0.0,1.4642361282000138e-2,-22.79435948239309,0.0,0.0,64.95874176755537,-118.76357587410472,0.0,0.0,-80.45807709632197,-41.34073501448674,0.0,0.0,79.06707126481128,-31.002381848253073,0.0,0.0,10.719903938852823,-77.40412646174758,0.0,0.0,-7.740124971618144,80.48808306172342,0.0,0.0,-110.15841642743815,-162.03564722944196,0.0,0.0,63.61525025140308,16.394396172302493,0.0,0.0,53.310229986100815,-97.2869260480245,0.0,0.0,-10.494092359472546,-6.627103598745919,0.0,0.0,169.83168506885906,-13.526472018045851,0.0,0.0,-103.01851991480758,62.447044657168156,0.0,0.0,-145.78272160249927,43.191235944321505,0.0,0.0,-170.93764223006303,155.7029110014898,0.0,0.0] +[-183.32312619298798,624.8054758553743,0.0,0.0,-4120.288114540419,-6941.945593075267,0.0,0.0,152.3586215013224,23.535553932065778,0.0,0.0,1003.0042197192884,-2822.203706726119,0.0,0.0,-816.3325457162158,4715.581357358526,0.0,0.0,712.9415324403122,240.52105848859432,0.0,0.0,3656.9726058012407,742.4899422812755,0.0,0.0,3026.924333892969,-1455.4181385792872,0.0,0.0,-1998.0781767035965,-6398.128800242083,0.0,0.0,-793.9488759066729,915.2583227932016,0.0,0.0,-590.641450026869,-2365.7687020618537,0.0,0.0,2676.3360016465845,5008.109299959703,0.0,0.0,-7197.490333971163,671.080618200834,0.0,0.0,-2560.6099577967398,-324.0849362626553,0.0,0.0,-5257.5201140637355,1799.5481276517735,0.0,0.0,-7272.947300418497,-5915.154940206767,0.0,0.0] +[-40.504173502527706,12.129578158258292,0.0,0.0,-0.6074595620794799,-0.920377391994058,0.0,0.0,1.0011869575649552,24.03490096827619,0.0,0.0,6.0414769422997665,-0.3823436286227533,0.0,0.0,-0.17372397900100517,1.8099155288257465,0.0,0.0,10.675067742240588,5.824415086839656,0.0,0.0,0.837749130451615,0.10031073726590345,0.0,0.0,1.1509285397419264,-0.5170195676233496,0.0,0.0,-0.262407496413492,-1.3778737302535462,0.0,0.0,-2.7310155031724843,0.5853854461638273,0.0,0.0,-2.39396860452037,-0.9737727238830935,0.0,0.0,1.224464498862644,1.0981328240445394,0.0,0.0,-0.9179099430080735,1.6759756318268768,0.0,0.0,-1.4594573223509832,-0.10068397477789229,0.0,0.0,-1.2279767467669243,2.6608148903989064,0.0,0.0,-1.14168830784871,-0.73153608622547,0.0,0.0] +[-2.1274469530639664,-87.055309160875,0.0,0.0,-82.35787006428066,-79.93253267799825,0.0,0.0,12.336044450377486,-23.78391700268743,0.0,0.0,12.884863406302358,-32.84892092508137,0.0,0.0,-11.908674906547787,-92.38400254440369,0.0,0.0,8.172249887162096,-37.42852497445781,0.0,0.0,-66.06993212850568,8.630163006731266,0.0,0.0,-59.0235004342909,-53.05672041384456,0.0,0.0,-22.897831600115012,-93.89256411789064,0.0,0.0,-17.050384860987847,-39.54129448813424,0.0,0.0,-15.707343289828259,-47.99709400665984,0.0,0.0,-57.245772080078,-74.15908041965238,0.0,0.0,-88.55039606421403,-33.53676733222679,0.0,0.0,-61.13183256365945,-56.73476319101437,0.0,0.0,-80.3499374345099,26.006050520144072,0.0,0.0,-91.12320723332579,-89.92184005873219,0.0,0.0] +[86.1704805043268,-7.177109378829002,0.0,0.0,50.02907568304664,86.84756206888044,0.0,0.0,12.350686811659486,-0.9895575202943405,0.0,0.0,77.84360517385772,85.91465494902334,0.0,0.0,68.54940218977418,-51.043267529916946,0.0,0.0,87.23932115197337,-6.426143126204735,0.0,0.0,-55.35002818965286,86.03428946847885,0.0,0.0,-51.28337546267276,27.431362647878856,0.0,0.0,87.26058482732314,68.14308311155132,0.0,0.0,46.564865390415235,-23.14689831583175,0.0,0.0,37.602886696272556,49.289832041364654,0.0,0.0,-46.75167972060545,-67.53197682090646,0.0,0.0,81.28128900464503,-20.010295314180937,0.0,0.0,41.88668735114813,5.712281466153783,0.0,0.0,65.43278416798937,69.19728646446558,0.0,0.0,79.81443499673723,65.78107094275762,0.0,0.0] +[-86.1704805043268,87.055309160875,0.0,0.0,-50.02907568304664,79.93253267799825,0.0,0.0,-12.350686811659486,23.78391700268743,0.0,0.0,-77.84360517385772,32.84892092508137,0.0,0.0,11.908674906547787,92.38400254440369,0.0,0.0,-87.23932115197337,37.42852497445781,0.0,0.0,55.35002818965286,-8.630163006731266,0.0,0.0,59.0235004342909,-27.431362647878856,0.0,0.0,22.897831600115012,93.89256411789064,0.0,0.0,-46.564865390415235,23.14689831583175,0.0,0.0,-37.602886696272556,47.99709400665984,0.0,0.0,57.245772080078,74.15908041965238,0.0,0.0,-81.28128900464503,33.53676733222679,0.0,0.0,61.13183256365945,-5.712281466153783,0.0,0.0,80.3499374345099,-69.19728646446558,0.0,0.0,91.12320723332579,-65.78107094275762,0.0,0.0] +[84.04303355126284,-94.232418539704,0.0,0.0,-32.32879438123402,6.915029390882182,0.0,0.0,24.68673126203697,-24.773474522981772,0.0,0.0,90.72846858016008,53.06573402394197,0.0,0.0,56.6407272832264,-143.42727007432063,0.0,0.0,95.41157103913547,-43.85466810066254,0.0,0.0,-121.41996031815854,94.66445247521011,0.0,0.0,-110.30687589696366,-25.625357765965703,0.0,0.0,64.36275322720813,-25.749481006339323,0.0,0.0,29.514480529427388,-62.68819280396599,0.0,0.0,21.895543406444297,1.2927380347048114,0.0,0.0,-103.99745180068345,-141.69105724055885,0.0,0.0,-7.269107059568995,-53.547062646407724,0.0,0.0,-19.245145212511318,-51.02248172486059,0.0,0.0,-14.917153266520529,95.20333698460965,0.0,0.0,-11.308772236588553,-24.140769115974564,0.0,0.0] +[88.29792745739077,-79.878199782046,0.0,0.0,132.3869457473273,-166.7800947468787,0.0,0.0,1.4642361282000138e-2,-22.79435948239309,0.0,0.0,64.95874176755537,-118.76357587410472,0.0,0.0,-80.45807709632197,-41.34073501448674,0.0,0.0,79.06707126481128,-31.002381848253073,0.0,0.0,10.719903938852823,-77.40412646174758,0.0,0.0,-7.740124971618144,80.48808306172342,0.0,0.0,-110.15841642743815,-162.03564722944196,0.0,0.0,63.61525025140308,16.394396172302493,0.0,0.0,53.310229986100815,-97.2869260480245,0.0,0.0,-10.494092359472546,-6.627103598745919,0.0,0.0,169.83168506885906,-13.526472018045851,0.0,0.0,-103.01851991480758,62.447044657168156,0.0,0.0,-145.78272160249927,43.191235944321505,0.0,0.0,-170.93764223006303,155.7029110014898,0.0,0.0] +[-183.32312619298798,624.8054758553743,0.0,0.0,-4120.288114540419,-6941.945593075267,0.0,0.0,152.3586215013224,23.535553932065778,0.0,0.0,1003.0042197192884,-2822.203706726119,0.0,0.0,-816.3325457162158,4715.581357358526,0.0,0.0,712.9415324403122,240.52105848859432,0.0,0.0,3656.9726058012407,742.4899422812755,0.0,0.0,3026.924333892969,-1455.4181385792872,0.0,0.0,-1998.0781767035965,-6398.128800242083,0.0,0.0,-793.9488759066729,915.2583227932016,0.0,0.0,-590.641450026869,-2365.7687020618537,0.0,0.0,2676.3360016465845,5008.109299959703,0.0,0.0,-7197.490333971163,671.080618200834,0.0,0.0,-2560.6099577967398,-324.0849362626553,0.0,0.0,-5257.5201140637355,1799.5481276517735,0.0,0.0,-7272.947300418497,-5915.154940206767,0.0,0.0] +[-40.504173502527706,12.129578158258292,0.0,0.0,-0.6074595620794799,-0.920377391994058,0.0,0.0,1.0011869575649552,24.03490096827619,0.0,0.0,6.0414769422997665,-0.3823436286227533,0.0,0.0,-0.17372397900100517,1.8099155288257465,0.0,0.0,10.675067742240588,5.824415086839656,0.0,0.0,0.837749130451615,0.10031073726590345,0.0,0.0,1.1509285397419264,-0.5170195676233496,0.0,0.0,-0.262407496413492,-1.3778737302535462,0.0,0.0,-2.7310155031724843,0.5853854461638273,0.0,0.0,-2.39396860452037,-0.9737727238830935,0.0,0.0,1.224464498862644,1.0981328240445394,0.0,0.0,-0.9179099430080735,1.6759756318268768,0.0,0.0,-1.4594573223509832,-0.10068397477789229,0.0,0.0,-1.2279767467669243,2.6608148903989064,0.0,0.0,-1.14168830784871,-0.73153608622547,0.0,0.0] +[-2.1274469530639664,-87.055309160875,0.0,0.0,-82.35787006428066,-79.93253267799825,0.0,0.0,12.336044450377486,-23.78391700268743,0.0,0.0,12.884863406302358,-32.84892092508137,0.0,0.0,-11.908674906547787,-92.38400254440369,0.0,0.0,8.172249887162096,-37.42852497445781,0.0,0.0,-66.06993212850568,8.630163006731266,0.0,0.0,-59.0235004342909,-53.05672041384456,0.0,0.0,-22.897831600115012,-93.89256411789064,0.0,0.0,-17.050384860987847,-39.54129448813424,0.0,0.0,-15.707343289828259,-47.99709400665984,0.0,0.0,-57.245772080078,-74.15908041965238,0.0,0.0,-88.55039606421403,-33.53676733222679,0.0,0.0,-61.13183256365945,-56.73476319101437,0.0,0.0,-80.3499374345099,26.006050520144072,0.0,0.0,-91.12320723332579,-89.92184005873219,0.0,0.0] +[86.1704805043268,-7.177109378829002,0.0,0.0,50.02907568304664,86.84756206888044,0.0,0.0,12.350686811659486,-0.9895575202943405,0.0,0.0,77.84360517385772,85.91465494902334,0.0,0.0,68.54940218977418,-51.043267529916946,0.0,0.0,87.23932115197337,-6.426143126204735,0.0,0.0,-55.35002818965286,86.03428946847885,0.0,0.0,-51.28337546267276,27.431362647878856,0.0,0.0,87.26058482732314,68.14308311155132,0.0,0.0,46.564865390415235,-23.14689831583175,0.0,0.0,37.602886696272556,49.289832041364654,0.0,0.0,-46.75167972060545,-67.53197682090646,0.0,0.0,81.28128900464503,-20.010295314180937,0.0,0.0,41.88668735114813,5.712281466153783,0.0,0.0,65.43278416798937,69.19728646446558,0.0,0.0,79.81443499673723,65.78107094275762,0.0,0.0] +[2.1274469530639664,7.177109378829002,0.0,0.0,82.35787006428066,-86.84756206888044,0.0,0.0,-12.336044450377486,0.9895575202943405,0.0,0.0,-12.884863406302358,-85.91465494902334,0.0,0.0,-68.54940218977418,51.043267529916946,0.0,0.0,-8.172249887162096,6.426143126204735,0.0,0.0,66.06993212850568,-86.03428946847885,0.0,0.0,51.28337546267276,53.05672041384456,0.0,0.0,-87.26058482732314,-68.14308311155132,0.0,0.0,17.050384860987847,39.54129448813424,0.0,0.0,15.707343289828259,-49.289832041364654,0.0,0.0,46.75167972060545,67.53197682090646,0.0,0.0,88.55039606421403,20.010295314180937,0.0,0.0,-41.88668735114813,56.73476319101437,0.0,0.0,-65.43278416798937,-26.006050520144072,0.0,0.0,-79.81443499673723,89.92184005873219,0.0,0.0] +[84.04303355126284,-94.232418539704,0.0,0.0,-32.32879438123402,6.915029390882182,0.0,0.0,24.68673126203697,-24.773474522981772,0.0,0.0,90.72846858016008,53.06573402394197,0.0,0.0,56.6407272832264,-143.42727007432063,0.0,0.0,95.41157103913547,-43.85466810066254,0.0,0.0,-121.41996031815854,94.66445247521011,0.0,0.0,-110.30687589696366,-25.625357765965703,0.0,0.0,64.36275322720813,-25.749481006339323,0.0,0.0,29.514480529427388,-62.68819280396599,0.0,0.0,21.895543406444297,1.2927380347048114,0.0,0.0,-103.99745180068345,-141.69105724055885,0.0,0.0,-7.269107059568995,-53.547062646407724,0.0,0.0,-19.245145212511318,-51.02248172486059,0.0,0.0,-14.917153266520529,95.20333698460965,0.0,0.0,-11.308772236588553,-24.140769115974564,0.0,0.0] +[-88.29792745739077,79.878199782046,0.0,0.0,-132.3869457473273,166.7800947468787,0.0,0.0,-1.4642361282000138e-2,22.79435948239309,0.0,0.0,-64.95874176755537,118.76357587410472,0.0,0.0,80.45807709632197,41.34073501448674,0.0,0.0,-79.06707126481128,31.002381848253073,0.0,0.0,-10.719903938852823,77.40412646174758,0.0,0.0,7.740124971618144,-80.48808306172342,0.0,0.0,110.15841642743815,162.03564722944196,0.0,0.0,-63.61525025140308,-16.394396172302493,0.0,0.0,-53.310229986100815,97.2869260480245,0.0,0.0,10.494092359472546,6.627103598745919,0.0,0.0,-169.83168506885906,13.526472018045851,0.0,0.0,103.01851991480758,-62.447044657168156,0.0,0.0,145.78272160249927,-43.191235944321505,0.0,0.0,170.93764223006303,-155.7029110014898,0.0,0.0] +[-183.32312619298798,624.8054758553743,0.0,0.0,-4120.288114540419,-6941.945593075267,0.0,0.0,152.3586215013224,23.535553932065778,0.0,0.0,1003.0042197192884,-2822.203706726119,0.0,0.0,-816.3325457162158,4715.581357358526,0.0,0.0,712.9415324403122,240.52105848859432,0.0,0.0,3656.9726058012407,742.4899422812755,0.0,0.0,3026.924333892969,-1455.4181385792872,0.0,0.0,-1998.0781767035965,-6398.128800242083,0.0,0.0,-793.9488759066729,915.2583227932016,0.0,0.0,-590.641450026869,-2365.7687020618537,0.0,0.0,2676.3360016465845,5008.109299959703,0.0,0.0,-7197.490333971163,671.080618200834,0.0,0.0,-2560.6099577967398,-324.0849362626553,0.0,0.0,-5257.5201140637355,1799.5481276517735,0.0,0.0,-7272.947300418497,-5915.154940206767,0.0,0.0] +[-2.4688813856122604e-2,8.244309793404982e-2,0.0,0.0,-1.6462001134310238,-1.086510825557584,0.0,0.0,0.9988144496330215,4.160616269315634e-2,0.0,0.0,0.16552243922317067,-2.6154483170077074,0.0,0.0,-5.7562577472060665,0.552511973113347,0.0,0.0,9.367622053048538e-2,0.1716910599760504,0.0,0.0,1.1936747692724174,9.96902253194693,0.0,0.0,0.8688636743895765,-1.9341627718208594,0.0,0.0,-3.8108667384419426,-0.7257559078479473,0.0,0.0,-0.36616416085457953,1.7082761564252107,0.0,0.0,-0.41771642205823717,-1.0269336729953993,0.0,0.0,0.8166835387460067,0.9106366535123632,0.0,0.0,-1.0894314933803964,0.5966673864523687,0.0,0.0,-0.6851861885136448,-9.93206716566354,0.0,0.0,-0.8143476679284422,0.37582471580729954,0.0,0.0,-0.8758958054710273,-1.3669865626994997,0.0,0.0] +[-2.1274469530639664,-87.055309160875,0.0,0.0,-82.35787006428066,-79.93253267799825,0.0,0.0,12.336044450377486,-23.78391700268743,0.0,0.0,12.884863406302358,-32.84892092508137,0.0,0.0,-11.908674906547787,-92.38400254440369,0.0,0.0,8.172249887162096,-37.42852497445781,0.0,0.0,-66.06993212850568,8.630163006731266,0.0,0.0,-59.0235004342909,-53.05672041384456,0.0,0.0,-22.897831600115012,-93.89256411789064,0.0,0.0,-17.050384860987847,-39.54129448813424,0.0,0.0,-15.707343289828259,-47.99709400665984,0.0,0.0,-57.245772080078,-74.15908041965238,0.0,0.0,-88.55039606421403,-33.53676733222679,0.0,0.0,-61.13183256365945,-56.73476319101437,0.0,0.0,-80.3499374345099,26.006050520144072,0.0,0.0,-91.12320723332579,-89.92184005873219,0.0,0.0] +[86.1704805043268,-7.177109378829002,0.0,0.0,50.02907568304664,86.84756206888044,0.0,0.0,12.350686811659486,-0.9895575202943405,0.0,0.0,77.84360517385772,85.91465494902334,0.0,0.0,68.54940218977418,-51.043267529916946,0.0,0.0,87.23932115197337,-6.426143126204735,0.0,0.0,-55.35002818965286,86.03428946847885,0.0,0.0,-51.28337546267276,27.431362647878856,0.0,0.0,87.26058482732314,68.14308311155132,0.0,0.0,46.564865390415235,-23.14689831583175,0.0,0.0,37.602886696272556,49.289832041364654,0.0,0.0,-46.75167972060545,-67.53197682090646,0.0,0.0,81.28128900464503,-20.010295314180937,0.0,0.0,41.88668735114813,5.712281466153783,0.0,0.0,65.43278416798937,69.19728646446558,0.0,0.0,79.81443499673723,65.78107094275762,0.0,0.0] diff --git a/testsuite/tests/simd/should_run/doublex2_fma.hs b/testsuite/tests/simd/should_run/doublex2_fma.hs new file mode 100644 index 00000000000..3d7b4479caa --- /dev/null +++ b/testsuite/tests/simd/should_run/doublex2_fma.hs @@ -0,0 +1,133 @@ +{-# LANGUAGE MagicHash, UnboxedTuples #-} +import Control.Monad +import Data.Array.Base +import Foreign.Marshal.Array +import GHC.Int +import GHC.IO +import GHC.Prim +import GHC.Ptr + +data DoubleX2 = DoubleX2 DoubleX2# + +indexAsDoubleX2 :: UArray Int Double -> Int -> DoubleX2# +indexAsDoubleX2 (UArray l _ _ ba) i = case i - l of + I# i# -> indexDoubleArrayAsDoubleX2# ba i# + +readAsDoubleX2 :: Ptr Double -> Int -> IO DoubleX2 +readAsDoubleX2 (Ptr addr) (I# i) = IO $ \s -> + case readDoubleOffAddrAsDoubleX2# addr i s of + (# s', v #) -> (# s', DoubleX2 v #) + +writeAsDoubleX2 :: Ptr Double -> Int -> DoubleX2# -> IO () +writeAsDoubleX2 (Ptr addr) (I# i) v = IO $ \s -> + (# writeDoubleOffAddrAsDoubleX2# addr i v s, () #) + +arr1 :: UArray Int Double +arr1 = listArray (0,63) [86.1704805043268,-87.055309160875,77.09385349363602,70.43981517796,50.02907568304664,-79.93253267799825,-94.4734175782,30.062138137255715,12.350686811659486,-23.78391700268743,-96.44925698909766,-67.13139854675774,77.84360517385772,-32.84892092508137,-58.02803492421746,-50.79004702787717,-11.908674906547787,-92.38400254440369,36.41222449165823,-68.6479119817805,87.23932115197337,-37.42852497445781,-64.82933137985788,84.16399940800329,-55.35002818965286,8.630163006731266,73.63479275711025,14.555315332112912,-59.0235004342909,27.431362647878856,36.75482002856153,30.991841701036876,-22.897831600115012,-93.89256411789064,17.639582620461923,94.24572581296609,46.564865390415235,-23.14689831583175,44.286969376764674,-61.7495951058958,37.602886696272556,-47.99709400665984,44.97168988769863,87.51005084451836,-57.245772080078,-74.15908041965238,-22.163672693129797,-36.26569085317567,81.28128900464503,-33.53676733222679,29.57596290010983,0.6835164364159141,-61.13183256365945,5.712281466153783,52.13503127014405,-75.17328181431184,-80.3499374345099,69.19728646446558,63.7669473494779,27.17066306772783,-91.12320723332579,65.78107094275762,-29.222084470705,55.14981850187309] + +input2 :: [Double] +input2 = [-2.1274469530639664,-7.177109378829002,-98.24323405063399,-26.03855917426543,-82.35787006428066,86.84756206888044,66.51501361884274,-69.12618497150666,12.336044450377486,-0.9895575202943405,-10.826450417702162,-23.706389595256866,12.884863406302358,85.91465494902334,-10.791922059638424,83.5855338741751,68.54940218977418,-51.043267529916946,74.89746292225463,74.48290415522592,8.172249887162096,-6.426143126204735,-71.09523683330931,-67.16904290667816,-66.06993212850568,86.03428946847885,25.702893242346008,98.90487021469829,-51.28337546267276,-53.05672041384456,-39.24117195492243,91.65414155791501,87.26058482732314,68.14308311155132,95.0497956861045,-52.545861855432456,-17.050384860987847,-39.54129448813424,94.0049004311935,-87.37548839080712,-15.707343289828259,49.289832041364654,34.873616921124494,-7.712670991606458,-46.75167972060545,-67.53197682090646,-94.04146452769466,-53.28374327444284,-88.55039606421403,-20.010295314180937,16.90312028906486,-70.34859808800593,41.88668735114813,-56.73476319101437,23.34349297210754,97.33003908727085,65.43278416798937,26.006050520144072,4.234841735331756,21.139356688092775,79.81443499673723,-89.92184005873219,-36.90383017318868,-94.20848066738576] + +arr3 :: UArray Int Double +arr3 = listArray (0,63) [-59.65425141222654,69.64349283945359,83.9284747794684,12.817033474692124,62.27335504509297,-18.237252362613106,-27.440844934578607,86.99583598227946,60.27511044722207,99.105767009872,-17.302109168036182,-52.97040384897619,-40.87827233682159,-12.965680691542133,-7.085664028521066,-24.62739386751332,-46.726152845099044,96.32406472850488,-74.91671402250174,68.79700002196601,4.924046272240773,-95.05505737760092,-15.860493489780893,44.16404678304456,-78.88924777259722,96.26040871939944,10.733429436230978,-96.82282239343006,4.807453036471273,94.98957580192541,-81.10639072830648,60.06291064241987,33.176918791107624,15.812814601682973,20.525838187336277,74.97849506952045,-32.05634249924189,-33.75972083595386,-87.97178483130338,64.4790977515402,22.619625038491137,50.005386892628295,-39.866736828488335,-45.632596031698114,14.569082560676776,32.74340801994042,-57.011231518845086,-1.1165315306058403,76.29399105390189,91.78812120984722,-5.161503833356846,-35.47834180738009,-29.87208820642647,-0.34845820369714886,39.65825554726061,-52.50503328017441,-99.11169685924439,56.229972696709645,-87.58597819570255,11.270880346195128,-52.398349186440754,83.16647409648112,-27.946311069976417,-45.94266833398757] + +run :: (DoubleX2# -> DoubleX2# -> DoubleX2# -> DoubleX2#) -> UArray Int Double -> Ptr Double -> UArray Int Double -> IO [Double] +run f a b c = allocaArray 64 $ \result -> do + forM_ [0,4..63] $ \i -> do + let v = indexAsDoubleX2 a i + DoubleX2 w <- readAsDoubleX2 b i + let x = indexAsDoubleX2 c i + writeAsDoubleX2 result i (f v w x) + peekArray 64 result +{-# INLINE run #-} + +runN :: (DoubleX2# -> DoubleX2# -> DoubleX2# -> DoubleX2#) -> UArray Int Double -> Ptr Double -> UArray Int Double -> IO [Double] +runN f a b c = allocaArray 64 $ \result -> do + forM_ [0,4..63] $ \i -> do + let v = indexAsDoubleX2 a i + DoubleX2 w <- readAsDoubleX2 b i + let x = indexAsDoubleX2 c i + writeAsDoubleX2 result i (f v w x) + peekArray 64 result +{-# NOINLINE runN #-} + +main :: IO () +main = do + withArray input2 $ \arr2 -> do + run (\x y z -> fmaddDoubleX2# x y z) arr1 arr2 arr3 >>= print + run (\x y z -> fmaddDoubleX2# y x z) arr1 arr2 arr3 >>= print + run (\x y z -> fmaddDoubleX2# z y x) arr1 arr2 arr3 >>= print + run (\x y z -> fmaddDoubleX2# y z x) arr1 arr2 arr3 >>= print + run (\x y z -> fmaddDoubleX2# z x y) arr1 arr2 arr3 >>= print + run (\x y z -> fmaddDoubleX2# x z y) arr1 arr2 arr3 >>= print + run (\x y z -> fmsubDoubleX2# x y z) arr1 arr2 arr3 >>= print + run (\x y z -> fmsubDoubleX2# y x z) arr1 arr2 arr3 >>= print + run (\x y z -> fmsubDoubleX2# z y x) arr1 arr2 arr3 >>= print + run (\x y z -> fmsubDoubleX2# y z x) arr1 arr2 arr3 >>= print + run (\x y z -> fmsubDoubleX2# z x y) arr1 arr2 arr3 >>= print + run (\x y z -> fmsubDoubleX2# x z y) arr1 arr2 arr3 >>= print + run (\x y z -> fnmaddDoubleX2# x y z) arr1 arr2 arr3 >>= print + run (\x y z -> fnmaddDoubleX2# y x z) arr1 arr2 arr3 >>= print + run (\x y z -> fnmaddDoubleX2# z y x) arr1 arr2 arr3 >>= print + run (\x y z -> fnmaddDoubleX2# y z x) arr1 arr2 arr3 >>= print + run (\x y z -> fnmaddDoubleX2# z x y) arr1 arr2 arr3 >>= print + run (\x y z -> fnmaddDoubleX2# x z y) arr1 arr2 arr3 >>= print + run (\x y z -> fnmsubDoubleX2# x y z) arr1 arr2 arr3 >>= print + run (\x y z -> fnmsubDoubleX2# y x z) arr1 arr2 arr3 >>= print + run (\x y z -> fnmsubDoubleX2# z y x) arr1 arr2 arr3 >>= print + run (\x y z -> fnmsubDoubleX2# y z x) arr1 arr2 arr3 >>= print + run (\x y z -> fnmsubDoubleX2# z x y) arr1 arr2 arr3 >>= print + run (\x y z -> fnmsubDoubleX2# x z y) arr1 arr2 arr3 >>= print + runN (\x y z -> fmaddDoubleX2# x y z) arr1 arr2 arr3 >>= print + runN (\x y z -> fmaddDoubleX2# y x z) arr1 arr2 arr3 >>= print + runN (\x y z -> fmaddDoubleX2# z y x) arr1 arr2 arr3 >>= print + runN (\x y z -> fmaddDoubleX2# y z x) arr1 arr2 arr3 >>= print + runN (\x y z -> fmaddDoubleX2# z x y) arr1 arr2 arr3 >>= print + runN (\x y z -> fmaddDoubleX2# x z y) arr1 arr2 arr3 >>= print + runN (\x y z -> fmsubDoubleX2# x y z) arr1 arr2 arr3 >>= print + runN (\x y z -> fmsubDoubleX2# y x z) arr1 arr2 arr3 >>= print + runN (\x y z -> fmsubDoubleX2# z y x) arr1 arr2 arr3 >>= print + runN (\x y z -> fmsubDoubleX2# y z x) arr1 arr2 arr3 >>= print + runN (\x y z -> fmsubDoubleX2# z x y) arr1 arr2 arr3 >>= print + runN (\x y z -> fmsubDoubleX2# x z y) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmaddDoubleX2# x y z) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmaddDoubleX2# y x z) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmaddDoubleX2# z y x) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmaddDoubleX2# y z x) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmaddDoubleX2# z x y) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmaddDoubleX2# x z y) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmsubDoubleX2# x y z) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmsubDoubleX2# y x z) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmsubDoubleX2# z y x) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmsubDoubleX2# y z x) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmsubDoubleX2# z x y) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmsubDoubleX2# x z y) arr1 arr2 arr3 >>= print + +{- +The values was generated by: +{- cabal: +build-depends: base, random >= 1.3.0 +-} +import System.Random.Stateful +import qualified Data.List as List +import Control.Monad + +main :: IO () +main = do + let xs, ys, zs :: [Double] + (xs, ys, zs) = runStateGen_ (mkStdGen 42) $ \g -> do + a <- replicateM 64 (uniformRM (-100.0, 100.0) g) + b <- replicateM 64 (uniformRM (-100.0, 100.0) g) + c <- replicateM 64 (uniformRM (-100.0, 100.0) g) + pure (a, b, c) + print xs + print ys + print zs +-} + +{- +The code was generated by: +:m + Data.List +putStr $ unlines ([" run (\\x y z -> " ++ intercalate " " [f,a,b,c] ++ ") arr1 arr2 arr3 >>= print" | f <- ["fmaddDoubleX2#","fmsubDoubleX2#","fnmaddDoubleX2#","fnmsubDoubleX2#"], [a,b,c] <- permutations ["x", "y", "z"]]) +putStr $ unlines ([" runN (\\x y z -> " ++ intercalate " " [f,a,b,c] ++ ") arr1 arr2 arr3 >>= print" | f <- ["fmaddDoubleX2#","fmsubDoubleX2#","fnmaddDoubleX2#","fnmsubDoubleX2#"], [a,b,c] <- permutations ["x", "y", "z"]]) +-} diff --git a/testsuite/tests/simd/should_run/doublex2_fma.stdout b/testsuite/tests/simd/should_run/doublex2_fma.stdout new file mode 100644 index 00000000000..cf1d76d7e89 --- /dev/null +++ b/testsuite/tests/simd/should_run/doublex2_fma.stdout @@ -0,0 +1,48 @@ +[-242.9773776052145,694.4489686948278,0.0,0.0,-4058.0147594953255,-6960.18284543788,0.0,0.0,212.63373194854447,122.64132094193778,0.0,0.0,962.1259473824667,-2835.169387417661,0.0,0.0,-863.0586985613148,4811.90542208703,0.0,0.0,717.865578712553,145.4660011109934,0.0,0.0,3578.0833580286435,838.7503510006749,0.0,0.0,3031.73178692944,-1360.4285627773618,0.0,0.0,-1964.9012579124887,-6382.3159856404,0.0,0.0,-826.0052184059148,881.4986019572478,0.0,0.0,-568.021824988378,-2315.7633151692253,0.0,0.0,2690.905084207261,5040.852707979644,0.0,0.0,-7121.19634291726,762.8687394106812,0.0,0.0,-2590.4820460031665,-324.4333944663524,0.0,0.0,-5356.63181092298,1855.7781003484831,0.0,0.0,-7325.3456496049375,-5831.988466110285,0.0,0.0] +[-242.9773776052145,694.4489686948278,0.0,0.0,-4058.0147594953255,-6960.18284543788,0.0,0.0,212.63373194854447,122.64132094193778,0.0,0.0,962.1259473824667,-2835.169387417661,0.0,0.0,-863.0586985613148,4811.90542208703,0.0,0.0,717.865578712553,145.4660011109934,0.0,0.0,3578.0833580286435,838.7503510006749,0.0,0.0,3031.73178692944,-1360.4285627773618,0.0,0.0,-1964.9012579124887,-6382.3159856404,0.0,0.0,-826.0052184059148,881.4986019572478,0.0,0.0,-568.021824988378,-2315.7633151692253,0.0,0.0,2690.905084207261,5040.852707979644,0.0,0.0,-7121.19634291726,762.8687394106812,0.0,0.0,-2590.4820460031665,-324.4333944663524,0.0,0.0,-5356.63181092298,1855.7781003484831,0.0,0.0,-7325.3456496049375,-5831.988466110285,0.0,0.0] +[213.08173590858,-586.8942747933278,0.0,0.0,-5078.671807587537,-1663.7934392058762,0.0,0.0,755.9071285400033,-121.85477405184503,0.0,0.0,-448.86735017171674,-1146.790903718138,0.0,0.0,-3214.9585190661032,-5009.079008050515,0.0,0.0,127.47985774467396,573.4088786036091,0.0,0.0,5156.857217814713,8290.326031125627,0.0,0.0,-305.56591952281343,-5012.404002904572,0.0,0.0,2872.139504880543,983.6413755121445,0.0,0.0,593.1378422381306,1311.7561650958212,0.0,0.0,-317.69132887050245,2416.7600270944463,0.0,0.0,-738.374853779897,-2285.3861518597514,0.0,0.0,-6674.581836137969,-1870.2441790751045,0.0,0.0,-1312.3746517921643,25.48197513487777,0.0,0.0,-6565.504206548638,1531.5167971614185,0.0,0.0,-4273.267842310841,-7412.701311009711,0.0,0.0] +[213.08173590858,-586.8942747933278,0.0,0.0,-5078.671807587537,-1663.7934392058762,0.0,0.0,755.9071285400033,-121.85477405184503,0.0,0.0,-448.86735017171674,-1146.790903718138,0.0,0.0,-3214.9585190661032,-5009.079008050515,0.0,0.0,127.47985774467396,573.4088786036091,0.0,0.0,5156.857217814713,8290.326031125627,0.0,0.0,-305.56591952281343,-5012.404002904572,0.0,0.0,2872.139504880543,983.6413755121445,0.0,0.0,593.1378422381306,1311.7561650958212,0.0,0.0,-317.69132887050245,2416.7600270944463,0.0,0.0,-738.374853779897,-2285.3861518597514,0.0,0.0,-6674.581836137969,-1870.2441790751045,0.0,0.0,-1312.3746517921643,25.48197513487777,0.0,0.0,-6565.504206548638,1531.5167971614185,0.0,0.0,-4273.267842310841,-7412.701311009711,0.0,0.0] +[-5142.562955270541,-6070.012909560645,0.0,0.0,3033.12052252391,1544.5973325003533,0.0,0.0,756.775056122202,-2358.112894570768,0.0,0.0,-3169.2272285706676,511.82327472534524,0.0,0.0,624.9959660557216,-8949.845908495417,0.0,0.0,437.74270399835217,3551.3444458798513,0.0,0.0,4300.45215594526,916.7773078114716,0.0,0.0,-335.03608184866806,2552.6367811769496,0.0,0.0,-672.4189146621505,-1416.5626257612846,0.0,0.0,-1509.7496582472338,741.8915308725561,0.0,0.0,834.8558541447237,-2350.8234234835113,0.0,0.0,-880.7700594049473,-2495.7530053851588,0.0,0.0,6112.723540105788,-3098.287160191058,0.0,0.0,1868.022181913277,-58.72525452972284,0.0,0.0,8029.051425836387,3916.967579103439,0.0,0.0,4854.520066596946,5380.8578925409065,0.0,0.0] +[-5142.562955270541,-6070.012909560645,0.0,0.0,3033.12052252391,1544.5973325003533,0.0,0.0,756.775056122202,-2358.112894570768,0.0,0.0,-3169.2272285706676,511.82327472534524,0.0,0.0,624.9959660557216,-8949.845908495417,0.0,0.0,437.74270399835217,3551.3444458798513,0.0,0.0,4300.45215594526,916.7773078114716,0.0,0.0,-335.03608184866806,2552.6367811769496,0.0,0.0,-672.4189146621505,-1416.5626257612846,0.0,0.0,-1509.7496582472338,741.8915308725561,0.0,0.0,834.8558541447237,-2350.8234234835113,0.0,0.0,-880.7700594049473,-2495.7530053851588,0.0,0.0,6112.723540105788,-3098.287160191058,0.0,0.0,1868.022181913277,-58.72525452972284,0.0,0.0,8029.051425836387,3916.967579103439,0.0,0.0,4854.520066596946,5380.8578925409065,0.0,0.0] +[-123.66887478076143,555.1619830159207,0.0,0.0,-4182.561469585512,-6923.708340712654,0.0,0.0,92.08351105410034,-75.57021307780622,0.0,0.0,1043.8824920561099,-2809.2380260345767,0.0,0.0,-769.6063928711168,4619.25729263002,0.0,0.0,708.0174861680714,335.5761158661952,0.0,0.0,3735.861853573838,646.229533561876,0.0,0.0,3022.1168808564976,-1550.4077143812126,0.0,0.0,-2031.255095494704,-6413.941614843767,0.0,0.0,-761.892533407431,949.0180436291555,0.0,0.0,-613.2610750653602,-2415.774088954482,0.0,0.0,2661.7669190859074,4975.365891939763,0.0,0.0,-7273.784325025064,579.2924969909868,0.0,0.0,-2530.7378695903135,-323.73647805895814,0.0,0.0,-5158.408417204491,1743.3181549550636,0.0,0.0,-7220.548951232056,-5998.321414303247,0.0,0.0] +[-123.66887478076143,555.1619830159207,0.0,0.0,-4182.561469585512,-6923.708340712654,0.0,0.0,92.08351105410034,-75.57021307780622,0.0,0.0,1043.8824920561099,-2809.2380260345767,0.0,0.0,-769.6063928711168,4619.25729263002,0.0,0.0,708.0174861680714,335.5761158661952,0.0,0.0,3735.861853573838,646.229533561876,0.0,0.0,3022.1168808564976,-1550.4077143812126,0.0,0.0,-2031.255095494704,-6413.941614843767,0.0,0.0,-761.892533407431,949.0180436291555,0.0,0.0,-613.2610750653602,-2415.774088954482,0.0,0.0,2661.7669190859074,4975.365891939763,0.0,0.0,-7273.784325025064,579.2924969909868,0.0,0.0,-2530.7378695903135,-323.73647805895814,0.0,0.0,-5158.408417204491,1743.3181549550636,0.0,0.0,-7220.548951232056,-5998.321414303247,0.0,0.0] +[40.740774899926365,-412.78365647157773,0.0,0.0,-5178.72995895363,-1503.9283738498798,0.0,0.0,731.2057549166843,-74.28694004647016,0.0,0.0,-604.5545605194322,-1081.0930618679754,0.0,0.0,-3191.141169253008,-4824.311002961707,0.0,0.0,-46.99878455927278,648.2659285525247,0.0,0.0,5267.55727419402,8273.065705112165,0.0,0.0,-187.5189186542316,-5067.26672820033,0.0,0.0,2917.935168080773,1171.4265037479258,0.0,0.0,500.00811145730006,1358.0499617274847,0.0,0.0,-392.8971022630476,2512.754215107766,0.0,0.0,-623.883309619741,-2137.0679910204467,0.0,0.0,-6837.144414147259,-1803.1706444106508,0.0,0.0,-1190.1109866648455,14.057412202570207,0.0,0.0,-6404.804331679618,1393.1222242324873,0.0,0.0,-4091.021427844189,-7544.263452895227,0.0,0.0] +[40.740774899926365,-412.78365647157773,0.0,0.0,-5178.72995895363,-1503.9283738498798,0.0,0.0,731.2057549166843,-74.28694004647016,0.0,0.0,-604.5545605194322,-1081.0930618679754,0.0,0.0,-3191.141169253008,-4824.311002961707,0.0,0.0,-46.99878455927278,648.2659285525247,0.0,0.0,5267.55727419402,8273.065705112165,0.0,0.0,-187.5189186542316,-5067.26672820033,0.0,0.0,2917.935168080773,1171.4265037479258,0.0,0.0,500.00811145730006,1358.0499617274847,0.0,0.0,-392.8971022630476,2512.754215107766,0.0,0.0,-623.883309619741,-2137.0679910204467,0.0,0.0,-6837.144414147259,-1803.1706444106508,0.0,0.0,-1190.1109866648455,14.057412202570207,0.0,0.0,-6404.804331679618,1393.1222242324873,0.0,0.0,-4091.021427844189,-7544.263452895227,0.0,0.0] +[-5138.308061364413,-6055.658690802987,0.0,0.0,3197.8362626524713,1370.9022083625925,0.0,0.0,732.102967221447,-2356.1337795301793,0.0,0.0,-3194.9969553832725,339.99396482729856,0.0,0.0,487.8971616761733,-8847.759373435583,0.0,0.0,421.39820422402795,3564.1967321322604,0.0,0.0,4432.592020202271,744.7087288745139,0.0,0.0,-232.46933092332253,2658.7502220046385,0.0,0.0,-846.9400843167969,-1552.8487919843872,0.0,0.0,-1475.648888525258,820.9741198488246,0.0,0.0,866.2705407243802,-2449.4030875662406,0.0,0.0,-787.2666999637364,-2360.6890517433458,0.0,0.0,6289.824332234216,-3058.266569562696,0.0,0.0,1784.2488072109809,54.74427185230591,0.0,0.0,7898.185857500408,3864.955478063151,0.0,0.0,4694.891196603471,5560.701572658371,0.0,0.0] +[-5138.308061364413,-6055.658690802987,0.0,0.0,3197.8362626524713,1370.9022083625925,0.0,0.0,732.102967221447,-2356.1337795301793,0.0,0.0,-3194.9969553832725,339.99396482729856,0.0,0.0,487.8971616761733,-8847.759373435583,0.0,0.0,421.39820422402795,3564.1967321322604,0.0,0.0,4432.592020202271,744.7087288745139,0.0,0.0,-232.46933092332253,2658.7502220046385,0.0,0.0,-846.9400843167969,-1552.8487919843872,0.0,0.0,-1475.648888525258,820.9741198488246,0.0,0.0,866.2705407243802,-2449.4030875662406,0.0,0.0,-787.2666999637364,-2360.6890517433458,0.0,0.0,6289.824332234216,-3058.266569562696,0.0,0.0,1784.2488072109809,54.74427185230591,0.0,0.0,7898.185857500408,3864.955478063151,0.0,0.0,4694.891196603471,5560.701572658371,0.0,0.0] +[123.66887478076143,-555.1619830159207,0.0,0.0,4182.561469585512,6923.708340712654,0.0,0.0,-92.08351105410034,75.57021307780622,0.0,0.0,-1043.8824920561099,2809.2380260345767,0.0,0.0,769.6063928711168,-4619.25729263002,0.0,0.0,-708.0174861680714,-335.5761158661952,0.0,0.0,-3735.861853573838,-646.229533561876,0.0,0.0,-3022.1168808564976,1550.4077143812126,0.0,0.0,2031.255095494704,6413.941614843767,0.0,0.0,761.892533407431,-949.0180436291555,0.0,0.0,613.2610750653602,2415.774088954482,0.0,0.0,-2661.7669190859074,-4975.365891939763,0.0,0.0,7273.784325025064,-579.2924969909868,0.0,0.0,2530.7378695903135,323.73647805895814,0.0,0.0,5158.408417204491,-1743.3181549550636,0.0,0.0,7220.548951232056,5998.321414303247,0.0,0.0] +[123.66887478076143,-555.1619830159207,0.0,0.0,4182.561469585512,6923.708340712654,0.0,0.0,-92.08351105410034,75.57021307780622,0.0,0.0,-1043.8824920561099,2809.2380260345767,0.0,0.0,769.6063928711168,-4619.25729263002,0.0,0.0,-708.0174861680714,-335.5761158661952,0.0,0.0,-3735.861853573838,-646.229533561876,0.0,0.0,-3022.1168808564976,1550.4077143812126,0.0,0.0,2031.255095494704,6413.941614843767,0.0,0.0,761.892533407431,-949.0180436291555,0.0,0.0,613.2610750653602,2415.774088954482,0.0,0.0,-2661.7669190859074,-4975.365891939763,0.0,0.0,7273.784325025064,-579.2924969909868,0.0,0.0,2530.7378695903135,323.73647805895814,0.0,0.0,5158.408417204491,-1743.3181549550636,0.0,0.0,7220.548951232056,5998.321414303247,0.0,0.0] +[-40.740774899926365,412.78365647157773,0.0,0.0,5178.72995895363,1503.9283738498798,0.0,0.0,-731.2057549166843,74.28694004647016,0.0,0.0,604.5545605194322,1081.0930618679754,0.0,0.0,3191.141169253008,4824.311002961707,0.0,0.0,46.99878455927278,-648.2659285525247,0.0,0.0,-5267.55727419402,-8273.065705112165,0.0,0.0,187.5189186542316,5067.26672820033,0.0,0.0,-2917.935168080773,-1171.4265037479258,0.0,0.0,-500.00811145730006,-1358.0499617274847,0.0,0.0,392.8971022630476,-2512.754215107766,0.0,0.0,623.883309619741,2137.0679910204467,0.0,0.0,6837.144414147259,1803.1706444106508,0.0,0.0,1190.1109866648455,-14.057412202570207,0.0,0.0,6404.804331679618,-1393.1222242324873,0.0,0.0,4091.021427844189,7544.263452895227,0.0,0.0] +[-40.740774899926365,412.78365647157773,0.0,0.0,5178.72995895363,1503.9283738498798,0.0,0.0,-731.2057549166843,74.28694004647016,0.0,0.0,604.5545605194322,1081.0930618679754,0.0,0.0,3191.141169253008,4824.311002961707,0.0,0.0,46.99878455927278,-648.2659285525247,0.0,0.0,-5267.55727419402,-8273.065705112165,0.0,0.0,187.5189186542316,5067.26672820033,0.0,0.0,-2917.935168080773,-1171.4265037479258,0.0,0.0,-500.00811145730006,-1358.0499617274847,0.0,0.0,392.8971022630476,-2512.754215107766,0.0,0.0,623.883309619741,2137.0679910204467,0.0,0.0,6837.144414147259,1803.1706444106508,0.0,0.0,1190.1109866648455,-14.057412202570207,0.0,0.0,6404.804331679618,-1393.1222242324873,0.0,0.0,4091.021427844189,7544.263452895227,0.0,0.0] +[5138.308061364413,6055.658690802987,0.0,0.0,-3197.8362626524713,-1370.9022083625925,0.0,0.0,-732.102967221447,2356.1337795301793,0.0,0.0,3194.9969553832725,-339.99396482729856,0.0,0.0,-487.8971616761733,8847.759373435583,0.0,0.0,-421.39820422402795,-3564.1967321322604,0.0,0.0,-4432.592020202271,-744.7087288745139,0.0,0.0,232.46933092332253,-2658.7502220046385,0.0,0.0,846.9400843167969,1552.8487919843872,0.0,0.0,1475.648888525258,-820.9741198488246,0.0,0.0,-866.2705407243802,2449.4030875662406,0.0,0.0,787.2666999637364,2360.6890517433458,0.0,0.0,-6289.824332234216,3058.266569562696,0.0,0.0,-1784.2488072109809,-54.74427185230591,0.0,0.0,-7898.185857500408,-3864.955478063151,0.0,0.0,-4694.891196603471,-5560.701572658371,0.0,0.0] +[5138.308061364413,6055.658690802987,0.0,0.0,-3197.8362626524713,-1370.9022083625925,0.0,0.0,-732.102967221447,2356.1337795301793,0.0,0.0,3194.9969553832725,-339.99396482729856,0.0,0.0,-487.8971616761733,8847.759373435583,0.0,0.0,-421.39820422402795,-3564.1967321322604,0.0,0.0,-4432.592020202271,-744.7087288745139,0.0,0.0,232.46933092332253,-2658.7502220046385,0.0,0.0,846.9400843167969,1552.8487919843872,0.0,0.0,1475.648888525258,-820.9741198488246,0.0,0.0,-866.2705407243802,2449.4030875662406,0.0,0.0,787.2666999637364,2360.6890517433458,0.0,0.0,-6289.824332234216,3058.266569562696,0.0,0.0,-1784.2488072109809,-54.74427185230591,0.0,0.0,-7898.185857500408,-3864.955478063151,0.0,0.0,-4694.891196603471,-5560.701572658371,0.0,0.0] +[242.9773776052145,-694.4489686948278,0.0,0.0,4058.0147594953255,6960.18284543788,0.0,0.0,-212.63373194854447,-122.64132094193778,0.0,0.0,-962.1259473824667,2835.169387417661,0.0,0.0,863.0586985613148,-4811.90542208703,0.0,0.0,-717.865578712553,-145.4660011109934,0.0,0.0,-3578.0833580286435,-838.7503510006749,0.0,0.0,-3031.73178692944,1360.4285627773618,0.0,0.0,1964.9012579124887,6382.3159856404,0.0,0.0,826.0052184059148,-881.4986019572478,0.0,0.0,568.021824988378,2315.7633151692253,0.0,0.0,-2690.905084207261,-5040.852707979644,0.0,0.0,7121.19634291726,-762.8687394106812,0.0,0.0,2590.4820460031665,324.4333944663524,0.0,0.0,5356.63181092298,-1855.7781003484831,0.0,0.0,7325.3456496049375,5831.988466110285,0.0,0.0] +[242.9773776052145,-694.4489686948278,0.0,0.0,4058.0147594953255,6960.18284543788,0.0,0.0,-212.63373194854447,-122.64132094193778,0.0,0.0,-962.1259473824667,2835.169387417661,0.0,0.0,863.0586985613148,-4811.90542208703,0.0,0.0,-717.865578712553,-145.4660011109934,0.0,0.0,-3578.0833580286435,-838.7503510006749,0.0,0.0,-3031.73178692944,1360.4285627773618,0.0,0.0,1964.9012579124887,6382.3159856404,0.0,0.0,826.0052184059148,-881.4986019572478,0.0,0.0,568.021824988378,2315.7633151692253,0.0,0.0,-2690.905084207261,-5040.852707979644,0.0,0.0,7121.19634291726,-762.8687394106812,0.0,0.0,2590.4820460031665,324.4333944663524,0.0,0.0,5356.63181092298,-1855.7781003484831,0.0,0.0,7325.3456496049375,5831.988466110285,0.0,0.0] +[-213.08173590858,586.8942747933278,0.0,0.0,5078.671807587537,1663.7934392058762,0.0,0.0,-755.9071285400033,121.85477405184503,0.0,0.0,448.86735017171674,1146.790903718138,0.0,0.0,3214.9585190661032,5009.079008050515,0.0,0.0,-127.47985774467396,-573.4088786036091,0.0,0.0,-5156.857217814713,-8290.326031125627,0.0,0.0,305.56591952281343,5012.404002904572,0.0,0.0,-2872.139504880543,-983.6413755121445,0.0,0.0,-593.1378422381306,-1311.7561650958212,0.0,0.0,317.69132887050245,-2416.7600270944463,0.0,0.0,738.374853779897,2285.3861518597514,0.0,0.0,6674.581836137969,1870.2441790751045,0.0,0.0,1312.3746517921643,-25.48197513487777,0.0,0.0,6565.504206548638,-1531.5167971614185,0.0,0.0,4273.267842310841,7412.701311009711,0.0,0.0] +[-213.08173590858,586.8942747933278,0.0,0.0,5078.671807587537,1663.7934392058762,0.0,0.0,-755.9071285400033,121.85477405184503,0.0,0.0,448.86735017171674,1146.790903718138,0.0,0.0,3214.9585190661032,5009.079008050515,0.0,0.0,-127.47985774467396,-573.4088786036091,0.0,0.0,-5156.857217814713,-8290.326031125627,0.0,0.0,305.56591952281343,5012.404002904572,0.0,0.0,-2872.139504880543,-983.6413755121445,0.0,0.0,-593.1378422381306,-1311.7561650958212,0.0,0.0,317.69132887050245,-2416.7600270944463,0.0,0.0,738.374853779897,2285.3861518597514,0.0,0.0,6674.581836137969,1870.2441790751045,0.0,0.0,1312.3746517921643,-25.48197513487777,0.0,0.0,6565.504206548638,-1531.5167971614185,0.0,0.0,4273.267842310841,7412.701311009711,0.0,0.0] +[5142.562955270541,6070.012909560645,0.0,0.0,-3033.12052252391,-1544.5973325003533,0.0,0.0,-756.775056122202,2358.112894570768,0.0,0.0,3169.2272285706676,-511.82327472534524,0.0,0.0,-624.9959660557216,8949.845908495417,0.0,0.0,-437.74270399835217,-3551.3444458798513,0.0,0.0,-4300.45215594526,-916.7773078114716,0.0,0.0,335.03608184866806,-2552.6367811769496,0.0,0.0,672.4189146621505,1416.5626257612846,0.0,0.0,1509.7496582472338,-741.8915308725561,0.0,0.0,-834.8558541447237,2350.8234234835113,0.0,0.0,880.7700594049473,2495.7530053851588,0.0,0.0,-6112.723540105788,3098.287160191058,0.0,0.0,-1868.022181913277,58.72525452972284,0.0,0.0,-8029.051425836387,-3916.967579103439,0.0,0.0,-4854.520066596946,-5380.8578925409065,0.0,0.0] +[5142.562955270541,6070.012909560645,0.0,0.0,-3033.12052252391,-1544.5973325003533,0.0,0.0,-756.775056122202,2358.112894570768,0.0,0.0,3169.2272285706676,-511.82327472534524,0.0,0.0,-624.9959660557216,8949.845908495417,0.0,0.0,-437.74270399835217,-3551.3444458798513,0.0,0.0,-4300.45215594526,-916.7773078114716,0.0,0.0,335.03608184866806,-2552.6367811769496,0.0,0.0,672.4189146621505,1416.5626257612846,0.0,0.0,1509.7496582472338,-741.8915308725561,0.0,0.0,-834.8558541447237,2350.8234234835113,0.0,0.0,880.7700594049473,2495.7530053851588,0.0,0.0,-6112.723540105788,3098.287160191058,0.0,0.0,-1868.022181913277,58.72525452972284,0.0,0.0,-8029.051425836387,-3916.967579103439,0.0,0.0,-4854.520066596946,-5380.8578925409065,0.0,0.0] +[-242.9773776052145,694.4489686948278,0.0,0.0,-4058.0147594953255,-6960.18284543788,0.0,0.0,212.63373194854447,122.64132094193778,0.0,0.0,962.1259473824667,-2835.169387417661,0.0,0.0,-863.0586985613148,4811.90542208703,0.0,0.0,717.865578712553,145.4660011109934,0.0,0.0,3578.0833580286435,838.7503510006749,0.0,0.0,3031.73178692944,-1360.4285627773618,0.0,0.0,-1964.9012579124887,-6382.3159856404,0.0,0.0,-826.0052184059148,881.4986019572478,0.0,0.0,-568.021824988378,-2315.7633151692253,0.0,0.0,2690.905084207261,5040.852707979644,0.0,0.0,-7121.19634291726,762.8687394106812,0.0,0.0,-2590.4820460031665,-324.4333944663524,0.0,0.0,-5356.63181092298,1855.7781003484831,0.0,0.0,-7325.3456496049375,-5831.988466110285,0.0,0.0] +[-242.9773776052145,694.4489686948278,0.0,0.0,-4058.0147594953255,-6960.18284543788,0.0,0.0,212.63373194854447,122.64132094193778,0.0,0.0,962.1259473824667,-2835.169387417661,0.0,0.0,-863.0586985613148,4811.90542208703,0.0,0.0,717.865578712553,145.4660011109934,0.0,0.0,3578.0833580286435,838.7503510006749,0.0,0.0,3031.73178692944,-1360.4285627773618,0.0,0.0,-1964.9012579124887,-6382.3159856404,0.0,0.0,-826.0052184059148,881.4986019572478,0.0,0.0,-568.021824988378,-2315.7633151692253,0.0,0.0,2690.905084207261,5040.852707979644,0.0,0.0,-7121.19634291726,762.8687394106812,0.0,0.0,-2590.4820460031665,-324.4333944663524,0.0,0.0,-5356.63181092298,1855.7781003484831,0.0,0.0,-7325.3456496049375,-5831.988466110285,0.0,0.0] +[213.08173590858,-586.8942747933278,0.0,0.0,-5078.671807587537,-1663.7934392058762,0.0,0.0,755.9071285400033,-121.85477405184503,0.0,0.0,-448.86735017171674,-1146.790903718138,0.0,0.0,-3214.9585190661032,-5009.079008050515,0.0,0.0,127.47985774467396,573.4088786036091,0.0,0.0,5156.857217814713,8290.326031125627,0.0,0.0,-305.56591952281343,-5012.404002904572,0.0,0.0,2872.139504880543,983.6413755121445,0.0,0.0,593.1378422381306,1311.7561650958212,0.0,0.0,-317.69132887050245,2416.7600270944463,0.0,0.0,-738.374853779897,-2285.3861518597514,0.0,0.0,-6674.581836137969,-1870.2441790751045,0.0,0.0,-1312.3746517921643,25.48197513487777,0.0,0.0,-6565.504206548638,1531.5167971614185,0.0,0.0,-4273.267842310841,-7412.701311009711,0.0,0.0] +[213.08173590858,-586.8942747933278,0.0,0.0,-5078.671807587537,-1663.7934392058762,0.0,0.0,755.9071285400033,-121.85477405184503,0.0,0.0,-448.86735017171674,-1146.790903718138,0.0,0.0,-3214.9585190661032,-5009.079008050515,0.0,0.0,127.47985774467396,573.4088786036091,0.0,0.0,5156.857217814713,8290.326031125627,0.0,0.0,-305.56591952281343,-5012.404002904572,0.0,0.0,2872.139504880543,983.6413755121445,0.0,0.0,593.1378422381306,1311.7561650958212,0.0,0.0,-317.69132887050245,2416.7600270944463,0.0,0.0,-738.374853779897,-2285.3861518597514,0.0,0.0,-6674.581836137969,-1870.2441790751045,0.0,0.0,-1312.3746517921643,25.48197513487777,0.0,0.0,-6565.504206548638,1531.5167971614185,0.0,0.0,-4273.267842310841,-7412.701311009711,0.0,0.0] +[-5142.562955270541,-6070.012909560645,0.0,0.0,3033.12052252391,1544.5973325003533,0.0,0.0,756.775056122202,-2358.112894570768,0.0,0.0,-3169.2272285706676,511.82327472534524,0.0,0.0,624.9959660557216,-8949.845908495417,0.0,0.0,437.74270399835217,3551.3444458798513,0.0,0.0,4300.45215594526,916.7773078114716,0.0,0.0,-335.03608184866806,2552.6367811769496,0.0,0.0,-672.4189146621505,-1416.5626257612846,0.0,0.0,-1509.7496582472338,741.8915308725561,0.0,0.0,834.8558541447237,-2350.8234234835113,0.0,0.0,-880.7700594049473,-2495.7530053851588,0.0,0.0,6112.723540105788,-3098.287160191058,0.0,0.0,1868.022181913277,-58.72525452972284,0.0,0.0,8029.051425836387,3916.967579103439,0.0,0.0,4854.520066596946,5380.8578925409065,0.0,0.0] +[-5142.562955270541,-6070.012909560645,0.0,0.0,3033.12052252391,1544.5973325003533,0.0,0.0,756.775056122202,-2358.112894570768,0.0,0.0,-3169.2272285706676,511.82327472534524,0.0,0.0,624.9959660557216,-8949.845908495417,0.0,0.0,437.74270399835217,3551.3444458798513,0.0,0.0,4300.45215594526,916.7773078114716,0.0,0.0,-335.03608184866806,2552.6367811769496,0.0,0.0,-672.4189146621505,-1416.5626257612846,0.0,0.0,-1509.7496582472338,741.8915308725561,0.0,0.0,834.8558541447237,-2350.8234234835113,0.0,0.0,-880.7700594049473,-2495.7530053851588,0.0,0.0,6112.723540105788,-3098.287160191058,0.0,0.0,1868.022181913277,-58.72525452972284,0.0,0.0,8029.051425836387,3916.967579103439,0.0,0.0,4854.520066596946,5380.8578925409065,0.0,0.0] +[-123.66887478076143,555.1619830159207,0.0,0.0,-4182.561469585512,-6923.708340712654,0.0,0.0,92.08351105410034,-75.57021307780622,0.0,0.0,1043.8824920561099,-2809.2380260345767,0.0,0.0,-769.6063928711168,4619.25729263002,0.0,0.0,708.0174861680714,335.5761158661952,0.0,0.0,3735.861853573838,646.229533561876,0.0,0.0,3022.1168808564976,-1550.4077143812126,0.0,0.0,-2031.255095494704,-6413.941614843767,0.0,0.0,-761.892533407431,949.0180436291555,0.0,0.0,-613.2610750653602,-2415.774088954482,0.0,0.0,2661.7669190859074,4975.365891939763,0.0,0.0,-7273.784325025064,579.2924969909868,0.0,0.0,-2530.7378695903135,-323.73647805895814,0.0,0.0,-5158.408417204491,1743.3181549550636,0.0,0.0,-7220.548951232056,-5998.321414303247,0.0,0.0] +[-123.66887478076143,555.1619830159207,0.0,0.0,-4182.561469585512,-6923.708340712654,0.0,0.0,92.08351105410034,-75.57021307780622,0.0,0.0,1043.8824920561099,-2809.2380260345767,0.0,0.0,-769.6063928711168,4619.25729263002,0.0,0.0,708.0174861680714,335.5761158661952,0.0,0.0,3735.861853573838,646.229533561876,0.0,0.0,3022.1168808564976,-1550.4077143812126,0.0,0.0,-2031.255095494704,-6413.941614843767,0.0,0.0,-761.892533407431,949.0180436291555,0.0,0.0,-613.2610750653602,-2415.774088954482,0.0,0.0,2661.7669190859074,4975.365891939763,0.0,0.0,-7273.784325025064,579.2924969909868,0.0,0.0,-2530.7378695903135,-323.73647805895814,0.0,0.0,-5158.408417204491,1743.3181549550636,0.0,0.0,-7220.548951232056,-5998.321414303247,0.0,0.0] +[40.740774899926365,-412.78365647157773,0.0,0.0,-5178.72995895363,-1503.9283738498798,0.0,0.0,731.2057549166843,-74.28694004647016,0.0,0.0,-604.5545605194322,-1081.0930618679754,0.0,0.0,-3191.141169253008,-4824.311002961707,0.0,0.0,-46.99878455927278,648.2659285525247,0.0,0.0,5267.55727419402,8273.065705112165,0.0,0.0,-187.5189186542316,-5067.26672820033,0.0,0.0,2917.935168080773,1171.4265037479258,0.0,0.0,500.00811145730006,1358.0499617274847,0.0,0.0,-392.8971022630476,2512.754215107766,0.0,0.0,-623.883309619741,-2137.0679910204467,0.0,0.0,-6837.144414147259,-1803.1706444106508,0.0,0.0,-1190.1109866648455,14.057412202570207,0.0,0.0,-6404.804331679618,1393.1222242324873,0.0,0.0,-4091.021427844189,-7544.263452895227,0.0,0.0] +[40.740774899926365,-412.78365647157773,0.0,0.0,-5178.72995895363,-1503.9283738498798,0.0,0.0,731.2057549166843,-74.28694004647016,0.0,0.0,-604.5545605194322,-1081.0930618679754,0.0,0.0,-3191.141169253008,-4824.311002961707,0.0,0.0,-46.99878455927278,648.2659285525247,0.0,0.0,5267.55727419402,8273.065705112165,0.0,0.0,-187.5189186542316,-5067.26672820033,0.0,0.0,2917.935168080773,1171.4265037479258,0.0,0.0,500.00811145730006,1358.0499617274847,0.0,0.0,-392.8971022630476,2512.754215107766,0.0,0.0,-623.883309619741,-2137.0679910204467,0.0,0.0,-6837.144414147259,-1803.1706444106508,0.0,0.0,-1190.1109866648455,14.057412202570207,0.0,0.0,-6404.804331679618,1393.1222242324873,0.0,0.0,-4091.021427844189,-7544.263452895227,0.0,0.0] +[-5138.308061364413,-6055.658690802987,0.0,0.0,3197.8362626524713,1370.9022083625925,0.0,0.0,732.102967221447,-2356.1337795301793,0.0,0.0,-3194.9969553832725,339.99396482729856,0.0,0.0,487.8971616761733,-8847.759373435583,0.0,0.0,421.39820422402795,3564.1967321322604,0.0,0.0,4432.592020202271,744.7087288745139,0.0,0.0,-232.46933092332253,2658.7502220046385,0.0,0.0,-846.9400843167969,-1552.8487919843872,0.0,0.0,-1475.648888525258,820.9741198488246,0.0,0.0,866.2705407243802,-2449.4030875662406,0.0,0.0,-787.2666999637364,-2360.6890517433458,0.0,0.0,6289.824332234216,-3058.266569562696,0.0,0.0,1784.2488072109809,54.74427185230591,0.0,0.0,7898.185857500408,3864.955478063151,0.0,0.0,4694.891196603471,5560.701572658371,0.0,0.0] +[-5138.308061364413,-6055.658690802987,0.0,0.0,3197.8362626524713,1370.9022083625925,0.0,0.0,732.102967221447,-2356.1337795301793,0.0,0.0,-3194.9969553832725,339.99396482729856,0.0,0.0,487.8971616761733,-8847.759373435583,0.0,0.0,421.39820422402795,3564.1967321322604,0.0,0.0,4432.592020202271,744.7087288745139,0.0,0.0,-232.46933092332253,2658.7502220046385,0.0,0.0,-846.9400843167969,-1552.8487919843872,0.0,0.0,-1475.648888525258,820.9741198488246,0.0,0.0,866.2705407243802,-2449.4030875662406,0.0,0.0,-787.2666999637364,-2360.6890517433458,0.0,0.0,6289.824332234216,-3058.266569562696,0.0,0.0,1784.2488072109809,54.74427185230591,0.0,0.0,7898.185857500408,3864.955478063151,0.0,0.0,4694.891196603471,5560.701572658371,0.0,0.0] +[123.66887478076143,-555.1619830159207,0.0,0.0,4182.561469585512,6923.708340712654,0.0,0.0,-92.08351105410034,75.57021307780622,0.0,0.0,-1043.8824920561099,2809.2380260345767,0.0,0.0,769.6063928711168,-4619.25729263002,0.0,0.0,-708.0174861680714,-335.5761158661952,0.0,0.0,-3735.861853573838,-646.229533561876,0.0,0.0,-3022.1168808564976,1550.4077143812126,0.0,0.0,2031.255095494704,6413.941614843767,0.0,0.0,761.892533407431,-949.0180436291555,0.0,0.0,613.2610750653602,2415.774088954482,0.0,0.0,-2661.7669190859074,-4975.365891939763,0.0,0.0,7273.784325025064,-579.2924969909868,0.0,0.0,2530.7378695903135,323.73647805895814,0.0,0.0,5158.408417204491,-1743.3181549550636,0.0,0.0,7220.548951232056,5998.321414303247,0.0,0.0] +[123.66887478076143,-555.1619830159207,0.0,0.0,4182.561469585512,6923.708340712654,0.0,0.0,-92.08351105410034,75.57021307780622,0.0,0.0,-1043.8824920561099,2809.2380260345767,0.0,0.0,769.6063928711168,-4619.25729263002,0.0,0.0,-708.0174861680714,-335.5761158661952,0.0,0.0,-3735.861853573838,-646.229533561876,0.0,0.0,-3022.1168808564976,1550.4077143812126,0.0,0.0,2031.255095494704,6413.941614843767,0.0,0.0,761.892533407431,-949.0180436291555,0.0,0.0,613.2610750653602,2415.774088954482,0.0,0.0,-2661.7669190859074,-4975.365891939763,0.0,0.0,7273.784325025064,-579.2924969909868,0.0,0.0,2530.7378695903135,323.73647805895814,0.0,0.0,5158.408417204491,-1743.3181549550636,0.0,0.0,7220.548951232056,5998.321414303247,0.0,0.0] +[-40.740774899926365,412.78365647157773,0.0,0.0,5178.72995895363,1503.9283738498798,0.0,0.0,-731.2057549166843,74.28694004647016,0.0,0.0,604.5545605194322,1081.0930618679754,0.0,0.0,3191.141169253008,4824.311002961707,0.0,0.0,46.99878455927278,-648.2659285525247,0.0,0.0,-5267.55727419402,-8273.065705112165,0.0,0.0,187.5189186542316,5067.26672820033,0.0,0.0,-2917.935168080773,-1171.4265037479258,0.0,0.0,-500.00811145730006,-1358.0499617274847,0.0,0.0,392.8971022630476,-2512.754215107766,0.0,0.0,623.883309619741,2137.0679910204467,0.0,0.0,6837.144414147259,1803.1706444106508,0.0,0.0,1190.1109866648455,-14.057412202570207,0.0,0.0,6404.804331679618,-1393.1222242324873,0.0,0.0,4091.021427844189,7544.263452895227,0.0,0.0] +[-40.740774899926365,412.78365647157773,0.0,0.0,5178.72995895363,1503.9283738498798,0.0,0.0,-731.2057549166843,74.28694004647016,0.0,0.0,604.5545605194322,1081.0930618679754,0.0,0.0,3191.141169253008,4824.311002961707,0.0,0.0,46.99878455927278,-648.2659285525247,0.0,0.0,-5267.55727419402,-8273.065705112165,0.0,0.0,187.5189186542316,5067.26672820033,0.0,0.0,-2917.935168080773,-1171.4265037479258,0.0,0.0,-500.00811145730006,-1358.0499617274847,0.0,0.0,392.8971022630476,-2512.754215107766,0.0,0.0,623.883309619741,2137.0679910204467,0.0,0.0,6837.144414147259,1803.1706444106508,0.0,0.0,1190.1109866648455,-14.057412202570207,0.0,0.0,6404.804331679618,-1393.1222242324873,0.0,0.0,4091.021427844189,7544.263452895227,0.0,0.0] +[5138.308061364413,6055.658690802987,0.0,0.0,-3197.8362626524713,-1370.9022083625925,0.0,0.0,-732.102967221447,2356.1337795301793,0.0,0.0,3194.9969553832725,-339.99396482729856,0.0,0.0,-487.8971616761733,8847.759373435583,0.0,0.0,-421.39820422402795,-3564.1967321322604,0.0,0.0,-4432.592020202271,-744.7087288745139,0.0,0.0,232.46933092332253,-2658.7502220046385,0.0,0.0,846.9400843167969,1552.8487919843872,0.0,0.0,1475.648888525258,-820.9741198488246,0.0,0.0,-866.2705407243802,2449.4030875662406,0.0,0.0,787.2666999637364,2360.6890517433458,0.0,0.0,-6289.824332234216,3058.266569562696,0.0,0.0,-1784.2488072109809,-54.74427185230591,0.0,0.0,-7898.185857500408,-3864.955478063151,0.0,0.0,-4694.891196603471,-5560.701572658371,0.0,0.0] +[5138.308061364413,6055.658690802987,0.0,0.0,-3197.8362626524713,-1370.9022083625925,0.0,0.0,-732.102967221447,2356.1337795301793,0.0,0.0,3194.9969553832725,-339.99396482729856,0.0,0.0,-487.8971616761733,8847.759373435583,0.0,0.0,-421.39820422402795,-3564.1967321322604,0.0,0.0,-4432.592020202271,-744.7087288745139,0.0,0.0,232.46933092332253,-2658.7502220046385,0.0,0.0,846.9400843167969,1552.8487919843872,0.0,0.0,1475.648888525258,-820.9741198488246,0.0,0.0,-866.2705407243802,2449.4030875662406,0.0,0.0,787.2666999637364,2360.6890517433458,0.0,0.0,-6289.824332234216,3058.266569562696,0.0,0.0,-1784.2488072109809,-54.74427185230591,0.0,0.0,-7898.185857500408,-3864.955478063151,0.0,0.0,-4694.891196603471,-5560.701572658371,0.0,0.0] +[242.9773776052145,-694.4489686948278,0.0,0.0,4058.0147594953255,6960.18284543788,0.0,0.0,-212.63373194854447,-122.64132094193778,0.0,0.0,-962.1259473824667,2835.169387417661,0.0,0.0,863.0586985613148,-4811.90542208703,0.0,0.0,-717.865578712553,-145.4660011109934,0.0,0.0,-3578.0833580286435,-838.7503510006749,0.0,0.0,-3031.73178692944,1360.4285627773618,0.0,0.0,1964.9012579124887,6382.3159856404,0.0,0.0,826.0052184059148,-881.4986019572478,0.0,0.0,568.021824988378,2315.7633151692253,0.0,0.0,-2690.905084207261,-5040.852707979644,0.0,0.0,7121.19634291726,-762.8687394106812,0.0,0.0,2590.4820460031665,324.4333944663524,0.0,0.0,5356.63181092298,-1855.7781003484831,0.0,0.0,7325.3456496049375,5831.988466110285,0.0,0.0] +[242.9773776052145,-694.4489686948278,0.0,0.0,4058.0147594953255,6960.18284543788,0.0,0.0,-212.63373194854447,-122.64132094193778,0.0,0.0,-962.1259473824667,2835.169387417661,0.0,0.0,863.0586985613148,-4811.90542208703,0.0,0.0,-717.865578712553,-145.4660011109934,0.0,0.0,-3578.0833580286435,-838.7503510006749,0.0,0.0,-3031.73178692944,1360.4285627773618,0.0,0.0,1964.9012579124887,6382.3159856404,0.0,0.0,826.0052184059148,-881.4986019572478,0.0,0.0,568.021824988378,2315.7633151692253,0.0,0.0,-2690.905084207261,-5040.852707979644,0.0,0.0,7121.19634291726,-762.8687394106812,0.0,0.0,2590.4820460031665,324.4333944663524,0.0,0.0,5356.63181092298,-1855.7781003484831,0.0,0.0,7325.3456496049375,5831.988466110285,0.0,0.0] +[-213.08173590858,586.8942747933278,0.0,0.0,5078.671807587537,1663.7934392058762,0.0,0.0,-755.9071285400033,121.85477405184503,0.0,0.0,448.86735017171674,1146.790903718138,0.0,0.0,3214.9585190661032,5009.079008050515,0.0,0.0,-127.47985774467396,-573.4088786036091,0.0,0.0,-5156.857217814713,-8290.326031125627,0.0,0.0,305.56591952281343,5012.404002904572,0.0,0.0,-2872.139504880543,-983.6413755121445,0.0,0.0,-593.1378422381306,-1311.7561650958212,0.0,0.0,317.69132887050245,-2416.7600270944463,0.0,0.0,738.374853779897,2285.3861518597514,0.0,0.0,6674.581836137969,1870.2441790751045,0.0,0.0,1312.3746517921643,-25.48197513487777,0.0,0.0,6565.504206548638,-1531.5167971614185,0.0,0.0,4273.267842310841,7412.701311009711,0.0,0.0] +[-213.08173590858,586.8942747933278,0.0,0.0,5078.671807587537,1663.7934392058762,0.0,0.0,-755.9071285400033,121.85477405184503,0.0,0.0,448.86735017171674,1146.790903718138,0.0,0.0,3214.9585190661032,5009.079008050515,0.0,0.0,-127.47985774467396,-573.4088786036091,0.0,0.0,-5156.857217814713,-8290.326031125627,0.0,0.0,305.56591952281343,5012.404002904572,0.0,0.0,-2872.139504880543,-983.6413755121445,0.0,0.0,-593.1378422381306,-1311.7561650958212,0.0,0.0,317.69132887050245,-2416.7600270944463,0.0,0.0,738.374853779897,2285.3861518597514,0.0,0.0,6674.581836137969,1870.2441790751045,0.0,0.0,1312.3746517921643,-25.48197513487777,0.0,0.0,6565.504206548638,-1531.5167971614185,0.0,0.0,4273.267842310841,7412.701311009711,0.0,0.0] +[5142.562955270541,6070.012909560645,0.0,0.0,-3033.12052252391,-1544.5973325003533,0.0,0.0,-756.775056122202,2358.112894570768,0.0,0.0,3169.2272285706676,-511.82327472534524,0.0,0.0,-624.9959660557216,8949.845908495417,0.0,0.0,-437.74270399835217,-3551.3444458798513,0.0,0.0,-4300.45215594526,-916.7773078114716,0.0,0.0,335.03608184866806,-2552.6367811769496,0.0,0.0,672.4189146621505,1416.5626257612846,0.0,0.0,1509.7496582472338,-741.8915308725561,0.0,0.0,-834.8558541447237,2350.8234234835113,0.0,0.0,880.7700594049473,2495.7530053851588,0.0,0.0,-6112.723540105788,3098.287160191058,0.0,0.0,-1868.022181913277,58.72525452972284,0.0,0.0,-8029.051425836387,-3916.967579103439,0.0,0.0,-4854.520066596946,-5380.8578925409065,0.0,0.0] +[5142.562955270541,6070.012909560645,0.0,0.0,-3033.12052252391,-1544.5973325003533,0.0,0.0,-756.775056122202,2358.112894570768,0.0,0.0,3169.2272285706676,-511.82327472534524,0.0,0.0,-624.9959660557216,8949.845908495417,0.0,0.0,-437.74270399835217,-3551.3444458798513,0.0,0.0,-4300.45215594526,-916.7773078114716,0.0,0.0,335.03608184866806,-2552.6367811769496,0.0,0.0,672.4189146621505,1416.5626257612846,0.0,0.0,1509.7496582472338,-741.8915308725561,0.0,0.0,-834.8558541447237,2350.8234234835113,0.0,0.0,880.7700594049473,2495.7530053851588,0.0,0.0,-6112.723540105788,3098.287160191058,0.0,0.0,-1868.022181913277,58.72525452972284,0.0,0.0,-8029.051425836387,-3916.967579103439,0.0,0.0,-4854.520066596946,-5380.8578925409065,0.0,0.0] diff --git a/testsuite/tests/simd/should_run/floatx4_arith.hs b/testsuite/tests/simd/should_run/floatx4_arith.hs new file mode 100644 index 00000000000..5f57c4e1fd2 --- /dev/null +++ b/testsuite/tests/simd/should_run/floatx4_arith.hs @@ -0,0 +1,95 @@ +{-# LANGUAGE MagicHash, UnboxedTuples #-} +import Control.Monad +import Data.Array.Base +import Foreign.Marshal.Array +import GHC.Int +import GHC.IO +import GHC.Prim +import GHC.Ptr + +data FloatX4 = FloatX4 FloatX4# + +indexAsFloatX4 :: UArray Int Float -> Int -> FloatX4# +indexAsFloatX4 (UArray l _ _ ba) i = case i - l of + I# i# -> indexFloatArrayAsFloatX4# ba i# + +readAsFloatX4 :: Ptr Float -> Int -> IO FloatX4 +readAsFloatX4 (Ptr addr) (I# i) = IO $ \s -> + case readFloatOffAddrAsFloatX4# addr i s of + (# s', v #) -> (# s', FloatX4 v #) + +writeAsFloatX4 :: Ptr Float -> Int -> FloatX4# -> IO () +writeAsFloatX4 (Ptr addr) (I# i) v = IO $ \s -> + (# writeFloatOffAddrAsFloatX4# addr i v s, () #) + +arr1 :: UArray Int Float +arr1 = listArray (0,63) [-46.6892,89.12732,-77.78206,25.62262,7.794174,38.453793,-39.720543,47.347664,39.21601,-97.32084,-91.673874,-93.06639,-24.45533,-82.11456,-50.65983,47.034466,-62.318623,-1.7945938,66.2823,0.43374634,-72.966705,2.8155289,-98.03614,57.937504,7.237129,-73.059814,39.52617,34.392334,-60.721226,-57.35563,93.037544,48.76241,-71.80935,-23.923409,-69.97397,54.472355,94.4757,-70.334885,12.157753,21.06411,95.6841,-61.641663,13.519524,-48.503525,18.204895,3.8409805,76.24074,81.23582,-51.674843,5.475235,-3.6810303,40.684856,-5.465164,-82.67741,-81.206024,25.460907,16.86615,36.823112,-31.761482,-86.52606,73.76491,94.99991,22.627441,-45.88064] + +input2 :: [Float] +input2 = [-87.38458,-61.88547,0.7465515,-88.43077,-94.30282,-23.171593,85.92421,49.86781,-76.373604,87.17505,-75.796295,-17.862892,43.495815,-53.17978,7.1279907,-8.282211,65.43089,21.971985,-4.4562683,-57.797848,-0.100914,66.46458,0.43808746,87.80351,40.871555,-1.7138519,-88.45551,87.25368,-40.668373,-10.477974,-3.1042175,34.199455,-63.186687,-12.722816,63.30073,-9.216278,62.15632,-68.041595,-15.712379,10.544235,36.857437,-42.99411,69.461914,-73.757645,-33.06685,-80.0233,-14.392632,72.19195,43.64637,57.709164,-41.887623,7.433571,10.958084,-51.711353,-89.607704,98.22998,-87.74089,-82.14257,56.985752,-33.83731,-59.704292,-48.397453,-90.9834,-72.2701] + +run :: (FloatX4# -> FloatX4# -> FloatX4#) -> UArray Int Float -> Ptr Float -> IO [Float] +run f a b = allocaArray 64 $ \result -> do + forM_ [0,4..63] $ \i -> do + let v = indexAsFloatX4 a i + FloatX4 w <- readAsFloatX4 b i + writeAsFloatX4 result i (f v w) + peekArray 64 result +{-# INLINE run #-} + +runN :: (FloatX4# -> FloatX4# -> FloatX4#) -> UArray Int Float -> Ptr Float -> IO [Float] +runN f a b = allocaArray 64 $ \result -> do + forM_ [0,4..63] $ \i -> do + let v = indexAsFloatX4 a i + FloatX4 w <- readAsFloatX4 b i + writeAsFloatX4 result i (f v w) + peekArray 64 result +{-# NOINLINE runN #-} + +main :: IO () +main = do + withArray input2 $ \arr2 -> do + run (\x _ -> negateFloatX4# x) arr1 arr2 >>= print + run plusFloatX4# arr1 arr2 >>= print + run minusFloatX4# arr1 arr2 >>= print + run timesFloatX4# arr1 arr2 >>= print + run divideFloatX4# arr1 arr2 >>= print + -- minFloatX4# and maxFloatX4# are not well-defined if the arguments are signed zeros or NaNs. + -- This test case doesn't contain such cases. + run minFloatX4# arr1 arr2 >>= print + run maxFloatX4# arr1 arr2 >>= print + runN (\x _ -> negateFloatX4# x) arr1 arr2 >>= print + runN plusFloatX4# arr1 arr2 >>= print + runN minusFloatX4# arr1 arr2 >>= print + runN timesFloatX4# arr1 arr2 >>= print + runN divideFloatX4# arr1 arr2 >>= print + runN minFloatX4# arr1 arr2 >>= print + runN maxFloatX4# arr1 arr2 >>= print + runN (\_ y -> negateFloatX4# y) arr1 arr2 >>= print + runN (\x y -> plusFloatX4# y x) arr1 arr2 >>= print + runN (\x y -> minusFloatX4# y x) arr1 arr2 >>= print + runN (\x y -> timesFloatX4# y x) arr1 arr2 >>= print + runN (\x y -> divideFloatX4# y x) arr1 arr2 >>= print + runN (\x y -> minFloatX4# y x) arr1 arr2 >>= print + runN (\x y -> maxFloatX4# y x) arr1 arr2 >>= print + +{- +The values was generated by: +{- cabal: +build-depends: base, random >= 1.3.0 +-} +import System.Random.Stateful +import qualified Data.List as List +import Control.Monad + +main :: IO () +main = do + let xs, ys :: [Float] + (xs, ys) = runStateGen_ (mkStdGen 42) $ \g -> do + a <- replicateM 64 (uniformRM (-100.0, 100.0) g) + b <- replicateM 64 (uniformRM (-100.0, 100.0) g) + pure (a, b) + print $ or $ zipWith (\x y -> isNaN x || isNaN y || (x == 0 && y == 0 && isNegativeZero x /= isNegativeZero y)) xs ys -- should be False + print xs + print ys +-} diff --git a/testsuite/tests/simd/should_run/floatx4_arith.stdout b/testsuite/tests/simd/should_run/floatx4_arith.stdout new file mode 100644 index 00000000000..9043c04b6db --- /dev/null +++ b/testsuite/tests/simd/should_run/floatx4_arith.stdout @@ -0,0 +1,21 @@ +[46.6892,-89.12732,77.78206,-25.62262,-7.794174,-38.453793,39.720543,-47.347664,-39.21601,97.32084,91.673874,93.06639,24.45533,82.11456,50.65983,-47.034466,62.318623,1.7945938,-66.2823,-0.43374634,72.966705,-2.8155289,98.03614,-57.937504,-7.237129,73.059814,-39.52617,-34.392334,60.721226,57.35563,-93.037544,-48.76241,71.80935,23.923409,69.97397,-54.472355,-94.4757,70.334885,-12.157753,-21.06411,-95.6841,61.641663,-13.519524,48.503525,-18.204895,-3.8409805,-76.24074,-81.23582,51.674843,-5.475235,3.6810303,-40.684856,5.465164,82.67741,81.206024,-25.460907,-16.86615,-36.823112,31.761482,86.52606,-73.76491,-94.99991,-22.627441,45.88064] +[-134.07379,27.241848,-77.03551,-62.80815,-86.508644,15.2822,46.203667,97.21547,-37.157593,-10.14579,-167.47017,-110.92928,19.040485,-135.29434,-43.531837,38.752254,3.1122704,20.177391,61.826035,-57.3641,-73.06762,69.280106,-97.59805,145.74101,48.108685,-74.77367,-48.929344,121.64601,-101.3896,-67.8336,89.93333,82.96187,-134.99603,-36.646225,-6.673237,45.256077,156.63202,-138.37648,-3.5546265,31.608345,132.54153,-104.63577,82.98144,-122.26117,-14.861954,-76.18232,61.848106,153.42776,-8.028473,63.1844,-45.568653,48.118427,5.49292,-134.38876,-170.81372,123.69089,-70.87474,-45.319458,25.22427,-120.36337,14.060616,46.602455,-68.35596,-118.15074] +[40.69538,151.01279,-78.52861,114.05339,102.09699,61.625385,-125.64475,-2.5201454,115.589615,-184.49588,-15.877579,-75.2035,-67.95114,-28.934784,-57.78782,55.316677,-127.74951,-23.766579,70.73857,58.231594,-72.86579,-63.649048,-98.47423,-29.866009,-33.634426,-71.34596,127.98168,-52.861343,-20.052853,-46.877655,96.14176,14.562954,-8.622662,-11.200592,-133.2747,63.688633,32.31938,-2.2932892,27.870132,10.519875,58.82666,-18.647552,-55.94239,25.25412,51.271744,83.86428,90.63337,9.043869,-95.32121,-52.23393,38.206593,33.251286,-16.423248,-30.966053,8.40168,-72.76907,104.60704,118.96568,-88.74724,-52.68875,133.46921,143.39737,113.61084,26.389465] +[4079.9163,-5515.686,-58.068314,-2265.8281,-735.0126,-891.03564,-3412.9563,2361.1243,-2995.068,-8483.949,6948.54,1662.4349,-1063.7045,4366.8345,-361.10278,-389.54938,-4077.5632,-39.43079,-295.37173,-25.069605,7.3633623,187.13293,-42.948402,5087.116,295.79272,125.21371,-3496.3076,3000.8577,2469.4333,600.97076,-288.80878,1667.6478,4537.395,304.37314,-4429.4033,-502.03238,5872.2617,4785.6978,-191.02722,222.10493,3526.6707,2650.2285,939.092,3577.5059,-601.9785,-307.36795,-1097.3048,5864.572,-2255.4192,315.97122,154.1896,302.43378,-59.88773,4275.3604,7276.6855,2501.0244,-1479.851,-3024.745,-1809.9519,2927.8093,-4404.0815,-4597.7534,-2058.7214,3315.7986] +[0.5342956,-1.4401978,-104.18847,-0.28974777,-8.265049e-2,-1.659523,-0.46227416,0.9494635,-0.51347595,-1.1163841,1.209477,5.2100406,-0.5622456,1.5440937,-7.107168,-5.678974,-0.95243424,-8.167645e-2,-14.873948,-7.5045414e-3,723.0583,4.2361345e-2,-223.78212,0.65985405,0.17707007,42.629013,-0.446848,0.39416486,1.4930823,5.4739237,-29.971334,1.4258242,1.1364633,1.8803548,-1.1054212,-5.9104505,1.5199693,1.0337043,-0.7737691,1.9976897,2.5960593,1.4337234,0.19463217,0.6576067,-0.55054826,-4.7998276e-2,-5.2972064,1.1252754,-1.1839436,9.487636e-2,8.787871e-2,5.473124,-0.49873355,1.598825,0.90623933,0.2591969,-0.1922268,-0.44828293,-0.5573583,2.5571198,-1.2355043,-1.9629114,-0.24869858,0.6348495] +[-87.38458,-61.88547,-77.78206,-88.43077,-94.30282,-23.171593,-39.720543,47.347664,-76.373604,-97.32084,-91.673874,-93.06639,-24.45533,-82.11456,-50.65983,-8.282211,-62.318623,-1.7945938,-4.4562683,-57.797848,-72.966705,2.8155289,-98.03614,57.937504,7.237129,-73.059814,-88.45551,34.392334,-60.721226,-57.35563,-3.1042175,34.199455,-71.80935,-23.923409,-69.97397,-9.216278,62.15632,-70.334885,-15.712379,10.544235,36.857437,-61.641663,13.519524,-73.757645,-33.06685,-80.0233,-14.392632,72.19195,-51.674843,5.475235,-41.887623,7.433571,-5.465164,-82.67741,-89.607704,25.460907,-87.74089,-82.14257,-31.761482,-86.52606,-59.704292,-48.397453,-90.9834,-72.2701] +[-46.6892,89.12732,0.7465515,25.62262,7.794174,38.453793,85.92421,49.86781,39.21601,87.17505,-75.796295,-17.862892,43.495815,-53.17978,7.1279907,47.034466,65.43089,21.971985,66.2823,0.43374634,-0.100914,66.46458,0.43808746,87.80351,40.871555,-1.7138519,39.52617,87.25368,-40.668373,-10.477974,93.037544,48.76241,-63.186687,-12.722816,63.30073,54.472355,94.4757,-68.041595,12.157753,21.06411,95.6841,-42.99411,69.461914,-48.503525,18.204895,3.8409805,76.24074,81.23582,43.64637,57.709164,-3.6810303,40.684856,10.958084,-51.711353,-81.206024,98.22998,16.86615,36.823112,56.985752,-33.83731,73.76491,94.99991,22.627441,-45.88064] +[46.6892,-89.12732,77.78206,-25.62262,-7.794174,-38.453793,39.720543,-47.347664,-39.21601,97.32084,91.673874,93.06639,24.45533,82.11456,50.65983,-47.034466,62.318623,1.7945938,-66.2823,-0.43374634,72.966705,-2.8155289,98.03614,-57.937504,-7.237129,73.059814,-39.52617,-34.392334,60.721226,57.35563,-93.037544,-48.76241,71.80935,23.923409,69.97397,-54.472355,-94.4757,70.334885,-12.157753,-21.06411,-95.6841,61.641663,-13.519524,48.503525,-18.204895,-3.8409805,-76.24074,-81.23582,51.674843,-5.475235,3.6810303,-40.684856,5.465164,82.67741,81.206024,-25.460907,-16.86615,-36.823112,31.761482,86.52606,-73.76491,-94.99991,-22.627441,45.88064] +[-134.07379,27.241848,-77.03551,-62.80815,-86.508644,15.2822,46.203667,97.21547,-37.157593,-10.14579,-167.47017,-110.92928,19.040485,-135.29434,-43.531837,38.752254,3.1122704,20.177391,61.826035,-57.3641,-73.06762,69.280106,-97.59805,145.74101,48.108685,-74.77367,-48.929344,121.64601,-101.3896,-67.8336,89.93333,82.96187,-134.99603,-36.646225,-6.673237,45.256077,156.63202,-138.37648,-3.5546265,31.608345,132.54153,-104.63577,82.98144,-122.26117,-14.861954,-76.18232,61.848106,153.42776,-8.028473,63.1844,-45.568653,48.118427,5.49292,-134.38876,-170.81372,123.69089,-70.87474,-45.319458,25.22427,-120.36337,14.060616,46.602455,-68.35596,-118.15074] +[40.69538,151.01279,-78.52861,114.05339,102.09699,61.625385,-125.64475,-2.5201454,115.589615,-184.49588,-15.877579,-75.2035,-67.95114,-28.934784,-57.78782,55.316677,-127.74951,-23.766579,70.73857,58.231594,-72.86579,-63.649048,-98.47423,-29.866009,-33.634426,-71.34596,127.98168,-52.861343,-20.052853,-46.877655,96.14176,14.562954,-8.622662,-11.200592,-133.2747,63.688633,32.31938,-2.2932892,27.870132,10.519875,58.82666,-18.647552,-55.94239,25.25412,51.271744,83.86428,90.63337,9.043869,-95.32121,-52.23393,38.206593,33.251286,-16.423248,-30.966053,8.40168,-72.76907,104.60704,118.96568,-88.74724,-52.68875,133.46921,143.39737,113.61084,26.389465] +[4079.9163,-5515.686,-58.068314,-2265.8281,-735.0126,-891.03564,-3412.9563,2361.1243,-2995.068,-8483.949,6948.54,1662.4349,-1063.7045,4366.8345,-361.10278,-389.54938,-4077.5632,-39.43079,-295.37173,-25.069605,7.3633623,187.13293,-42.948402,5087.116,295.79272,125.21371,-3496.3076,3000.8577,2469.4333,600.97076,-288.80878,1667.6478,4537.395,304.37314,-4429.4033,-502.03238,5872.2617,4785.6978,-191.02722,222.10493,3526.6707,2650.2285,939.092,3577.5059,-601.9785,-307.36795,-1097.3048,5864.572,-2255.4192,315.97122,154.1896,302.43378,-59.88773,4275.3604,7276.6855,2501.0244,-1479.851,-3024.745,-1809.9519,2927.8093,-4404.0815,-4597.7534,-2058.7214,3315.7986] +[0.5342956,-1.4401978,-104.18847,-0.28974777,-8.265049e-2,-1.659523,-0.46227416,0.9494635,-0.51347595,-1.1163841,1.209477,5.2100406,-0.5622456,1.5440937,-7.107168,-5.678974,-0.95243424,-8.167645e-2,-14.873948,-7.5045414e-3,723.0583,4.2361345e-2,-223.78212,0.65985405,0.17707007,42.629013,-0.446848,0.39416486,1.4930823,5.4739237,-29.971334,1.4258242,1.1364633,1.8803548,-1.1054212,-5.9104505,1.5199693,1.0337043,-0.7737691,1.9976897,2.5960593,1.4337234,0.19463217,0.6576067,-0.55054826,-4.7998276e-2,-5.2972064,1.1252754,-1.1839436,9.487636e-2,8.787871e-2,5.473124,-0.49873355,1.598825,0.90623933,0.2591969,-0.1922268,-0.44828293,-0.5573583,2.5571198,-1.2355043,-1.9629114,-0.24869858,0.6348495] +[-87.38458,-61.88547,-77.78206,-88.43077,-94.30282,-23.171593,-39.720543,47.347664,-76.373604,-97.32084,-91.673874,-93.06639,-24.45533,-82.11456,-50.65983,-8.282211,-62.318623,-1.7945938,-4.4562683,-57.797848,-72.966705,2.8155289,-98.03614,57.937504,7.237129,-73.059814,-88.45551,34.392334,-60.721226,-57.35563,-3.1042175,34.199455,-71.80935,-23.923409,-69.97397,-9.216278,62.15632,-70.334885,-15.712379,10.544235,36.857437,-61.641663,13.519524,-73.757645,-33.06685,-80.0233,-14.392632,72.19195,-51.674843,5.475235,-41.887623,7.433571,-5.465164,-82.67741,-89.607704,25.460907,-87.74089,-82.14257,-31.761482,-86.52606,-59.704292,-48.397453,-90.9834,-72.2701] +[-46.6892,89.12732,0.7465515,25.62262,7.794174,38.453793,85.92421,49.86781,39.21601,87.17505,-75.796295,-17.862892,43.495815,-53.17978,7.1279907,47.034466,65.43089,21.971985,66.2823,0.43374634,-0.100914,66.46458,0.43808746,87.80351,40.871555,-1.7138519,39.52617,87.25368,-40.668373,-10.477974,93.037544,48.76241,-63.186687,-12.722816,63.30073,54.472355,94.4757,-68.041595,12.157753,21.06411,95.6841,-42.99411,69.461914,-48.503525,18.204895,3.8409805,76.24074,81.23582,43.64637,57.709164,-3.6810303,40.684856,10.958084,-51.711353,-81.206024,98.22998,16.86615,36.823112,56.985752,-33.83731,73.76491,94.99991,22.627441,-45.88064] +[87.38458,61.88547,-0.7465515,88.43077,94.30282,23.171593,-85.92421,-49.86781,76.373604,-87.17505,75.796295,17.862892,-43.495815,53.17978,-7.1279907,8.282211,-65.43089,-21.971985,4.4562683,57.797848,0.100914,-66.46458,-0.43808746,-87.80351,-40.871555,1.7138519,88.45551,-87.25368,40.668373,10.477974,3.1042175,-34.199455,63.186687,12.722816,-63.30073,9.216278,-62.15632,68.041595,15.712379,-10.544235,-36.857437,42.99411,-69.461914,73.757645,33.06685,80.0233,14.392632,-72.19195,-43.64637,-57.709164,41.887623,-7.433571,-10.958084,51.711353,89.607704,-98.22998,87.74089,82.14257,-56.985752,33.83731,59.704292,48.397453,90.9834,72.2701] +[-134.07379,27.241848,-77.03551,-62.80815,-86.508644,15.2822,46.203667,97.21547,-37.157593,-10.14579,-167.47017,-110.92928,19.040485,-135.29434,-43.531837,38.752254,3.1122704,20.177391,61.826035,-57.3641,-73.06762,69.280106,-97.59805,145.74101,48.108685,-74.77367,-48.929344,121.64601,-101.3896,-67.8336,89.93333,82.96187,-134.99603,-36.646225,-6.673237,45.256077,156.63202,-138.37648,-3.5546265,31.608345,132.54153,-104.63577,82.98144,-122.26117,-14.861954,-76.18232,61.848106,153.42776,-8.028473,63.1844,-45.568653,48.118427,5.49292,-134.38876,-170.81372,123.69089,-70.87474,-45.319458,25.22427,-120.36337,14.060616,46.602455,-68.35596,-118.15074] +[-40.69538,-151.01279,78.52861,-114.05339,-102.09699,-61.625385,125.64475,2.5201454,-115.589615,184.49588,15.877579,75.2035,67.95114,28.934784,57.78782,-55.316677,127.74951,23.766579,-70.73857,-58.231594,72.86579,63.649048,98.47423,29.866009,33.634426,71.34596,-127.98168,52.861343,20.052853,46.877655,-96.14176,-14.562954,8.622662,11.200592,133.2747,-63.688633,-32.31938,2.2932892,-27.870132,-10.519875,-58.82666,18.647552,55.94239,-25.25412,-51.271744,-83.86428,-90.63337,-9.043869,95.32121,52.23393,-38.206593,-33.251286,16.423248,30.966053,-8.40168,72.76907,-104.60704,-118.96568,88.74724,52.68875,-133.46921,-143.39737,-113.61084,-26.389465] +[4079.9163,-5515.686,-58.068314,-2265.8281,-735.0126,-891.03564,-3412.9563,2361.1243,-2995.068,-8483.949,6948.54,1662.4349,-1063.7045,4366.8345,-361.10278,-389.54938,-4077.5632,-39.43079,-295.37173,-25.069605,7.3633623,187.13293,-42.948402,5087.116,295.79272,125.21371,-3496.3076,3000.8577,2469.4333,600.97076,-288.80878,1667.6478,4537.395,304.37314,-4429.4033,-502.03238,5872.2617,4785.6978,-191.02722,222.10493,3526.6707,2650.2285,939.092,3577.5059,-601.9785,-307.36795,-1097.3048,5864.572,-2255.4192,315.97122,154.1896,302.43378,-59.88773,4275.3604,7276.6855,2501.0244,-1479.851,-3024.745,-1809.9519,2927.8093,-4404.0815,-4597.7534,-2058.7214,3315.7986] +[1.871623,-0.69434905,-9.597992e-3,-3.4512775,-12.099142,-0.60258275,-2.1632185,1.0532264,-1.9475107,-0.89574903,0.8268037,0.19193709,-1.7785822,0.6476291,-0.14070302,-0.17608814,-1.0499413,-12.243431,-6.723165e-2,-133.25264,1.3830144e-3,23.606426,-4.4686324e-3,1.5154866,5.647482,2.3458203e-2,-2.2378974,2.5370095,0.66975546,0.18268432,-3.3365212e-2,0.7013488,0.87992287,0.5318145,-0.90463257,-0.16919184,0.657908,0.9673947,-1.2923753,0.5005782,0.3851992,0.6974846,5.1378965,1.5206656,-1.8163713,-20.834082,-0.18877876,0.8886714,-0.8446348,10.540034,11.37932,0.182711,-2.0050786,0.6254593,1.1034613,3.8580709,-5.2021885,-2.230734,-1.794178,0.39106497,-0.80938613,-0.5094474,-4.0209317,1.5751765] +[-87.38458,-61.88547,-77.78206,-88.43077,-94.30282,-23.171593,-39.720543,47.347664,-76.373604,-97.32084,-91.673874,-93.06639,-24.45533,-82.11456,-50.65983,-8.282211,-62.318623,-1.7945938,-4.4562683,-57.797848,-72.966705,2.8155289,-98.03614,57.937504,7.237129,-73.059814,-88.45551,34.392334,-60.721226,-57.35563,-3.1042175,34.199455,-71.80935,-23.923409,-69.97397,-9.216278,62.15632,-70.334885,-15.712379,10.544235,36.857437,-61.641663,13.519524,-73.757645,-33.06685,-80.0233,-14.392632,72.19195,-51.674843,5.475235,-41.887623,7.433571,-5.465164,-82.67741,-89.607704,25.460907,-87.74089,-82.14257,-31.761482,-86.52606,-59.704292,-48.397453,-90.9834,-72.2701] +[-46.6892,89.12732,0.7465515,25.62262,7.794174,38.453793,85.92421,49.86781,39.21601,87.17505,-75.796295,-17.862892,43.495815,-53.17978,7.1279907,47.034466,65.43089,21.971985,66.2823,0.43374634,-0.100914,66.46458,0.43808746,87.80351,40.871555,-1.7138519,39.52617,87.25368,-40.668373,-10.477974,93.037544,48.76241,-63.186687,-12.722816,63.30073,54.472355,94.4757,-68.041595,12.157753,21.06411,95.6841,-42.99411,69.461914,-48.503525,18.204895,3.8409805,76.24074,81.23582,43.64637,57.709164,-3.6810303,40.684856,10.958084,-51.711353,-81.206024,98.22998,16.86615,36.823112,56.985752,-33.83731,73.76491,94.99991,22.627441,-45.88064] diff --git a/testsuite/tests/simd/should_run/floatx4_arith_baseline.hs b/testsuite/tests/simd/should_run/floatx4_arith_baseline.hs new file mode 100644 index 00000000000..5f57c4e1fd2 --- /dev/null +++ b/testsuite/tests/simd/should_run/floatx4_arith_baseline.hs @@ -0,0 +1,95 @@ +{-# LANGUAGE MagicHash, UnboxedTuples #-} +import Control.Monad +import Data.Array.Base +import Foreign.Marshal.Array +import GHC.Int +import GHC.IO +import GHC.Prim +import GHC.Ptr + +data FloatX4 = FloatX4 FloatX4# + +indexAsFloatX4 :: UArray Int Float -> Int -> FloatX4# +indexAsFloatX4 (UArray l _ _ ba) i = case i - l of + I# i# -> indexFloatArrayAsFloatX4# ba i# + +readAsFloatX4 :: Ptr Float -> Int -> IO FloatX4 +readAsFloatX4 (Ptr addr) (I# i) = IO $ \s -> + case readFloatOffAddrAsFloatX4# addr i s of + (# s', v #) -> (# s', FloatX4 v #) + +writeAsFloatX4 :: Ptr Float -> Int -> FloatX4# -> IO () +writeAsFloatX4 (Ptr addr) (I# i) v = IO $ \s -> + (# writeFloatOffAddrAsFloatX4# addr i v s, () #) + +arr1 :: UArray Int Float +arr1 = listArray (0,63) [-46.6892,89.12732,-77.78206,25.62262,7.794174,38.453793,-39.720543,47.347664,39.21601,-97.32084,-91.673874,-93.06639,-24.45533,-82.11456,-50.65983,47.034466,-62.318623,-1.7945938,66.2823,0.43374634,-72.966705,2.8155289,-98.03614,57.937504,7.237129,-73.059814,39.52617,34.392334,-60.721226,-57.35563,93.037544,48.76241,-71.80935,-23.923409,-69.97397,54.472355,94.4757,-70.334885,12.157753,21.06411,95.6841,-61.641663,13.519524,-48.503525,18.204895,3.8409805,76.24074,81.23582,-51.674843,5.475235,-3.6810303,40.684856,-5.465164,-82.67741,-81.206024,25.460907,16.86615,36.823112,-31.761482,-86.52606,73.76491,94.99991,22.627441,-45.88064] + +input2 :: [Float] +input2 = [-87.38458,-61.88547,0.7465515,-88.43077,-94.30282,-23.171593,85.92421,49.86781,-76.373604,87.17505,-75.796295,-17.862892,43.495815,-53.17978,7.1279907,-8.282211,65.43089,21.971985,-4.4562683,-57.797848,-0.100914,66.46458,0.43808746,87.80351,40.871555,-1.7138519,-88.45551,87.25368,-40.668373,-10.477974,-3.1042175,34.199455,-63.186687,-12.722816,63.30073,-9.216278,62.15632,-68.041595,-15.712379,10.544235,36.857437,-42.99411,69.461914,-73.757645,-33.06685,-80.0233,-14.392632,72.19195,43.64637,57.709164,-41.887623,7.433571,10.958084,-51.711353,-89.607704,98.22998,-87.74089,-82.14257,56.985752,-33.83731,-59.704292,-48.397453,-90.9834,-72.2701] + +run :: (FloatX4# -> FloatX4# -> FloatX4#) -> UArray Int Float -> Ptr Float -> IO [Float] +run f a b = allocaArray 64 $ \result -> do + forM_ [0,4..63] $ \i -> do + let v = indexAsFloatX4 a i + FloatX4 w <- readAsFloatX4 b i + writeAsFloatX4 result i (f v w) + peekArray 64 result +{-# INLINE run #-} + +runN :: (FloatX4# -> FloatX4# -> FloatX4#) -> UArray Int Float -> Ptr Float -> IO [Float] +runN f a b = allocaArray 64 $ \result -> do + forM_ [0,4..63] $ \i -> do + let v = indexAsFloatX4 a i + FloatX4 w <- readAsFloatX4 b i + writeAsFloatX4 result i (f v w) + peekArray 64 result +{-# NOINLINE runN #-} + +main :: IO () +main = do + withArray input2 $ \arr2 -> do + run (\x _ -> negateFloatX4# x) arr1 arr2 >>= print + run plusFloatX4# arr1 arr2 >>= print + run minusFloatX4# arr1 arr2 >>= print + run timesFloatX4# arr1 arr2 >>= print + run divideFloatX4# arr1 arr2 >>= print + -- minFloatX4# and maxFloatX4# are not well-defined if the arguments are signed zeros or NaNs. + -- This test case doesn't contain such cases. + run minFloatX4# arr1 arr2 >>= print + run maxFloatX4# arr1 arr2 >>= print + runN (\x _ -> negateFloatX4# x) arr1 arr2 >>= print + runN plusFloatX4# arr1 arr2 >>= print + runN minusFloatX4# arr1 arr2 >>= print + runN timesFloatX4# arr1 arr2 >>= print + runN divideFloatX4# arr1 arr2 >>= print + runN minFloatX4# arr1 arr2 >>= print + runN maxFloatX4# arr1 arr2 >>= print + runN (\_ y -> negateFloatX4# y) arr1 arr2 >>= print + runN (\x y -> plusFloatX4# y x) arr1 arr2 >>= print + runN (\x y -> minusFloatX4# y x) arr1 arr2 >>= print + runN (\x y -> timesFloatX4# y x) arr1 arr2 >>= print + runN (\x y -> divideFloatX4# y x) arr1 arr2 >>= print + runN (\x y -> minFloatX4# y x) arr1 arr2 >>= print + runN (\x y -> maxFloatX4# y x) arr1 arr2 >>= print + +{- +The values was generated by: +{- cabal: +build-depends: base, random >= 1.3.0 +-} +import System.Random.Stateful +import qualified Data.List as List +import Control.Monad + +main :: IO () +main = do + let xs, ys :: [Float] + (xs, ys) = runStateGen_ (mkStdGen 42) $ \g -> do + a <- replicateM 64 (uniformRM (-100.0, 100.0) g) + b <- replicateM 64 (uniformRM (-100.0, 100.0) g) + pure (a, b) + print $ or $ zipWith (\x y -> isNaN x || isNaN y || (x == 0 && y == 0 && isNegativeZero x /= isNegativeZero y)) xs ys -- should be False + print xs + print ys +-} diff --git a/testsuite/tests/simd/should_run/floatx4_arith_baseline.stdout b/testsuite/tests/simd/should_run/floatx4_arith_baseline.stdout new file mode 100644 index 00000000000..9043c04b6db --- /dev/null +++ b/testsuite/tests/simd/should_run/floatx4_arith_baseline.stdout @@ -0,0 +1,21 @@ +[46.6892,-89.12732,77.78206,-25.62262,-7.794174,-38.453793,39.720543,-47.347664,-39.21601,97.32084,91.673874,93.06639,24.45533,82.11456,50.65983,-47.034466,62.318623,1.7945938,-66.2823,-0.43374634,72.966705,-2.8155289,98.03614,-57.937504,-7.237129,73.059814,-39.52617,-34.392334,60.721226,57.35563,-93.037544,-48.76241,71.80935,23.923409,69.97397,-54.472355,-94.4757,70.334885,-12.157753,-21.06411,-95.6841,61.641663,-13.519524,48.503525,-18.204895,-3.8409805,-76.24074,-81.23582,51.674843,-5.475235,3.6810303,-40.684856,5.465164,82.67741,81.206024,-25.460907,-16.86615,-36.823112,31.761482,86.52606,-73.76491,-94.99991,-22.627441,45.88064] +[-134.07379,27.241848,-77.03551,-62.80815,-86.508644,15.2822,46.203667,97.21547,-37.157593,-10.14579,-167.47017,-110.92928,19.040485,-135.29434,-43.531837,38.752254,3.1122704,20.177391,61.826035,-57.3641,-73.06762,69.280106,-97.59805,145.74101,48.108685,-74.77367,-48.929344,121.64601,-101.3896,-67.8336,89.93333,82.96187,-134.99603,-36.646225,-6.673237,45.256077,156.63202,-138.37648,-3.5546265,31.608345,132.54153,-104.63577,82.98144,-122.26117,-14.861954,-76.18232,61.848106,153.42776,-8.028473,63.1844,-45.568653,48.118427,5.49292,-134.38876,-170.81372,123.69089,-70.87474,-45.319458,25.22427,-120.36337,14.060616,46.602455,-68.35596,-118.15074] +[40.69538,151.01279,-78.52861,114.05339,102.09699,61.625385,-125.64475,-2.5201454,115.589615,-184.49588,-15.877579,-75.2035,-67.95114,-28.934784,-57.78782,55.316677,-127.74951,-23.766579,70.73857,58.231594,-72.86579,-63.649048,-98.47423,-29.866009,-33.634426,-71.34596,127.98168,-52.861343,-20.052853,-46.877655,96.14176,14.562954,-8.622662,-11.200592,-133.2747,63.688633,32.31938,-2.2932892,27.870132,10.519875,58.82666,-18.647552,-55.94239,25.25412,51.271744,83.86428,90.63337,9.043869,-95.32121,-52.23393,38.206593,33.251286,-16.423248,-30.966053,8.40168,-72.76907,104.60704,118.96568,-88.74724,-52.68875,133.46921,143.39737,113.61084,26.389465] +[4079.9163,-5515.686,-58.068314,-2265.8281,-735.0126,-891.03564,-3412.9563,2361.1243,-2995.068,-8483.949,6948.54,1662.4349,-1063.7045,4366.8345,-361.10278,-389.54938,-4077.5632,-39.43079,-295.37173,-25.069605,7.3633623,187.13293,-42.948402,5087.116,295.79272,125.21371,-3496.3076,3000.8577,2469.4333,600.97076,-288.80878,1667.6478,4537.395,304.37314,-4429.4033,-502.03238,5872.2617,4785.6978,-191.02722,222.10493,3526.6707,2650.2285,939.092,3577.5059,-601.9785,-307.36795,-1097.3048,5864.572,-2255.4192,315.97122,154.1896,302.43378,-59.88773,4275.3604,7276.6855,2501.0244,-1479.851,-3024.745,-1809.9519,2927.8093,-4404.0815,-4597.7534,-2058.7214,3315.7986] +[0.5342956,-1.4401978,-104.18847,-0.28974777,-8.265049e-2,-1.659523,-0.46227416,0.9494635,-0.51347595,-1.1163841,1.209477,5.2100406,-0.5622456,1.5440937,-7.107168,-5.678974,-0.95243424,-8.167645e-2,-14.873948,-7.5045414e-3,723.0583,4.2361345e-2,-223.78212,0.65985405,0.17707007,42.629013,-0.446848,0.39416486,1.4930823,5.4739237,-29.971334,1.4258242,1.1364633,1.8803548,-1.1054212,-5.9104505,1.5199693,1.0337043,-0.7737691,1.9976897,2.5960593,1.4337234,0.19463217,0.6576067,-0.55054826,-4.7998276e-2,-5.2972064,1.1252754,-1.1839436,9.487636e-2,8.787871e-2,5.473124,-0.49873355,1.598825,0.90623933,0.2591969,-0.1922268,-0.44828293,-0.5573583,2.5571198,-1.2355043,-1.9629114,-0.24869858,0.6348495] +[-87.38458,-61.88547,-77.78206,-88.43077,-94.30282,-23.171593,-39.720543,47.347664,-76.373604,-97.32084,-91.673874,-93.06639,-24.45533,-82.11456,-50.65983,-8.282211,-62.318623,-1.7945938,-4.4562683,-57.797848,-72.966705,2.8155289,-98.03614,57.937504,7.237129,-73.059814,-88.45551,34.392334,-60.721226,-57.35563,-3.1042175,34.199455,-71.80935,-23.923409,-69.97397,-9.216278,62.15632,-70.334885,-15.712379,10.544235,36.857437,-61.641663,13.519524,-73.757645,-33.06685,-80.0233,-14.392632,72.19195,-51.674843,5.475235,-41.887623,7.433571,-5.465164,-82.67741,-89.607704,25.460907,-87.74089,-82.14257,-31.761482,-86.52606,-59.704292,-48.397453,-90.9834,-72.2701] +[-46.6892,89.12732,0.7465515,25.62262,7.794174,38.453793,85.92421,49.86781,39.21601,87.17505,-75.796295,-17.862892,43.495815,-53.17978,7.1279907,47.034466,65.43089,21.971985,66.2823,0.43374634,-0.100914,66.46458,0.43808746,87.80351,40.871555,-1.7138519,39.52617,87.25368,-40.668373,-10.477974,93.037544,48.76241,-63.186687,-12.722816,63.30073,54.472355,94.4757,-68.041595,12.157753,21.06411,95.6841,-42.99411,69.461914,-48.503525,18.204895,3.8409805,76.24074,81.23582,43.64637,57.709164,-3.6810303,40.684856,10.958084,-51.711353,-81.206024,98.22998,16.86615,36.823112,56.985752,-33.83731,73.76491,94.99991,22.627441,-45.88064] +[46.6892,-89.12732,77.78206,-25.62262,-7.794174,-38.453793,39.720543,-47.347664,-39.21601,97.32084,91.673874,93.06639,24.45533,82.11456,50.65983,-47.034466,62.318623,1.7945938,-66.2823,-0.43374634,72.966705,-2.8155289,98.03614,-57.937504,-7.237129,73.059814,-39.52617,-34.392334,60.721226,57.35563,-93.037544,-48.76241,71.80935,23.923409,69.97397,-54.472355,-94.4757,70.334885,-12.157753,-21.06411,-95.6841,61.641663,-13.519524,48.503525,-18.204895,-3.8409805,-76.24074,-81.23582,51.674843,-5.475235,3.6810303,-40.684856,5.465164,82.67741,81.206024,-25.460907,-16.86615,-36.823112,31.761482,86.52606,-73.76491,-94.99991,-22.627441,45.88064] +[-134.07379,27.241848,-77.03551,-62.80815,-86.508644,15.2822,46.203667,97.21547,-37.157593,-10.14579,-167.47017,-110.92928,19.040485,-135.29434,-43.531837,38.752254,3.1122704,20.177391,61.826035,-57.3641,-73.06762,69.280106,-97.59805,145.74101,48.108685,-74.77367,-48.929344,121.64601,-101.3896,-67.8336,89.93333,82.96187,-134.99603,-36.646225,-6.673237,45.256077,156.63202,-138.37648,-3.5546265,31.608345,132.54153,-104.63577,82.98144,-122.26117,-14.861954,-76.18232,61.848106,153.42776,-8.028473,63.1844,-45.568653,48.118427,5.49292,-134.38876,-170.81372,123.69089,-70.87474,-45.319458,25.22427,-120.36337,14.060616,46.602455,-68.35596,-118.15074] +[40.69538,151.01279,-78.52861,114.05339,102.09699,61.625385,-125.64475,-2.5201454,115.589615,-184.49588,-15.877579,-75.2035,-67.95114,-28.934784,-57.78782,55.316677,-127.74951,-23.766579,70.73857,58.231594,-72.86579,-63.649048,-98.47423,-29.866009,-33.634426,-71.34596,127.98168,-52.861343,-20.052853,-46.877655,96.14176,14.562954,-8.622662,-11.200592,-133.2747,63.688633,32.31938,-2.2932892,27.870132,10.519875,58.82666,-18.647552,-55.94239,25.25412,51.271744,83.86428,90.63337,9.043869,-95.32121,-52.23393,38.206593,33.251286,-16.423248,-30.966053,8.40168,-72.76907,104.60704,118.96568,-88.74724,-52.68875,133.46921,143.39737,113.61084,26.389465] +[4079.9163,-5515.686,-58.068314,-2265.8281,-735.0126,-891.03564,-3412.9563,2361.1243,-2995.068,-8483.949,6948.54,1662.4349,-1063.7045,4366.8345,-361.10278,-389.54938,-4077.5632,-39.43079,-295.37173,-25.069605,7.3633623,187.13293,-42.948402,5087.116,295.79272,125.21371,-3496.3076,3000.8577,2469.4333,600.97076,-288.80878,1667.6478,4537.395,304.37314,-4429.4033,-502.03238,5872.2617,4785.6978,-191.02722,222.10493,3526.6707,2650.2285,939.092,3577.5059,-601.9785,-307.36795,-1097.3048,5864.572,-2255.4192,315.97122,154.1896,302.43378,-59.88773,4275.3604,7276.6855,2501.0244,-1479.851,-3024.745,-1809.9519,2927.8093,-4404.0815,-4597.7534,-2058.7214,3315.7986] +[0.5342956,-1.4401978,-104.18847,-0.28974777,-8.265049e-2,-1.659523,-0.46227416,0.9494635,-0.51347595,-1.1163841,1.209477,5.2100406,-0.5622456,1.5440937,-7.107168,-5.678974,-0.95243424,-8.167645e-2,-14.873948,-7.5045414e-3,723.0583,4.2361345e-2,-223.78212,0.65985405,0.17707007,42.629013,-0.446848,0.39416486,1.4930823,5.4739237,-29.971334,1.4258242,1.1364633,1.8803548,-1.1054212,-5.9104505,1.5199693,1.0337043,-0.7737691,1.9976897,2.5960593,1.4337234,0.19463217,0.6576067,-0.55054826,-4.7998276e-2,-5.2972064,1.1252754,-1.1839436,9.487636e-2,8.787871e-2,5.473124,-0.49873355,1.598825,0.90623933,0.2591969,-0.1922268,-0.44828293,-0.5573583,2.5571198,-1.2355043,-1.9629114,-0.24869858,0.6348495] +[-87.38458,-61.88547,-77.78206,-88.43077,-94.30282,-23.171593,-39.720543,47.347664,-76.373604,-97.32084,-91.673874,-93.06639,-24.45533,-82.11456,-50.65983,-8.282211,-62.318623,-1.7945938,-4.4562683,-57.797848,-72.966705,2.8155289,-98.03614,57.937504,7.237129,-73.059814,-88.45551,34.392334,-60.721226,-57.35563,-3.1042175,34.199455,-71.80935,-23.923409,-69.97397,-9.216278,62.15632,-70.334885,-15.712379,10.544235,36.857437,-61.641663,13.519524,-73.757645,-33.06685,-80.0233,-14.392632,72.19195,-51.674843,5.475235,-41.887623,7.433571,-5.465164,-82.67741,-89.607704,25.460907,-87.74089,-82.14257,-31.761482,-86.52606,-59.704292,-48.397453,-90.9834,-72.2701] +[-46.6892,89.12732,0.7465515,25.62262,7.794174,38.453793,85.92421,49.86781,39.21601,87.17505,-75.796295,-17.862892,43.495815,-53.17978,7.1279907,47.034466,65.43089,21.971985,66.2823,0.43374634,-0.100914,66.46458,0.43808746,87.80351,40.871555,-1.7138519,39.52617,87.25368,-40.668373,-10.477974,93.037544,48.76241,-63.186687,-12.722816,63.30073,54.472355,94.4757,-68.041595,12.157753,21.06411,95.6841,-42.99411,69.461914,-48.503525,18.204895,3.8409805,76.24074,81.23582,43.64637,57.709164,-3.6810303,40.684856,10.958084,-51.711353,-81.206024,98.22998,16.86615,36.823112,56.985752,-33.83731,73.76491,94.99991,22.627441,-45.88064] +[87.38458,61.88547,-0.7465515,88.43077,94.30282,23.171593,-85.92421,-49.86781,76.373604,-87.17505,75.796295,17.862892,-43.495815,53.17978,-7.1279907,8.282211,-65.43089,-21.971985,4.4562683,57.797848,0.100914,-66.46458,-0.43808746,-87.80351,-40.871555,1.7138519,88.45551,-87.25368,40.668373,10.477974,3.1042175,-34.199455,63.186687,12.722816,-63.30073,9.216278,-62.15632,68.041595,15.712379,-10.544235,-36.857437,42.99411,-69.461914,73.757645,33.06685,80.0233,14.392632,-72.19195,-43.64637,-57.709164,41.887623,-7.433571,-10.958084,51.711353,89.607704,-98.22998,87.74089,82.14257,-56.985752,33.83731,59.704292,48.397453,90.9834,72.2701] +[-134.07379,27.241848,-77.03551,-62.80815,-86.508644,15.2822,46.203667,97.21547,-37.157593,-10.14579,-167.47017,-110.92928,19.040485,-135.29434,-43.531837,38.752254,3.1122704,20.177391,61.826035,-57.3641,-73.06762,69.280106,-97.59805,145.74101,48.108685,-74.77367,-48.929344,121.64601,-101.3896,-67.8336,89.93333,82.96187,-134.99603,-36.646225,-6.673237,45.256077,156.63202,-138.37648,-3.5546265,31.608345,132.54153,-104.63577,82.98144,-122.26117,-14.861954,-76.18232,61.848106,153.42776,-8.028473,63.1844,-45.568653,48.118427,5.49292,-134.38876,-170.81372,123.69089,-70.87474,-45.319458,25.22427,-120.36337,14.060616,46.602455,-68.35596,-118.15074] +[-40.69538,-151.01279,78.52861,-114.05339,-102.09699,-61.625385,125.64475,2.5201454,-115.589615,184.49588,15.877579,75.2035,67.95114,28.934784,57.78782,-55.316677,127.74951,23.766579,-70.73857,-58.231594,72.86579,63.649048,98.47423,29.866009,33.634426,71.34596,-127.98168,52.861343,20.052853,46.877655,-96.14176,-14.562954,8.622662,11.200592,133.2747,-63.688633,-32.31938,2.2932892,-27.870132,-10.519875,-58.82666,18.647552,55.94239,-25.25412,-51.271744,-83.86428,-90.63337,-9.043869,95.32121,52.23393,-38.206593,-33.251286,16.423248,30.966053,-8.40168,72.76907,-104.60704,-118.96568,88.74724,52.68875,-133.46921,-143.39737,-113.61084,-26.389465] +[4079.9163,-5515.686,-58.068314,-2265.8281,-735.0126,-891.03564,-3412.9563,2361.1243,-2995.068,-8483.949,6948.54,1662.4349,-1063.7045,4366.8345,-361.10278,-389.54938,-4077.5632,-39.43079,-295.37173,-25.069605,7.3633623,187.13293,-42.948402,5087.116,295.79272,125.21371,-3496.3076,3000.8577,2469.4333,600.97076,-288.80878,1667.6478,4537.395,304.37314,-4429.4033,-502.03238,5872.2617,4785.6978,-191.02722,222.10493,3526.6707,2650.2285,939.092,3577.5059,-601.9785,-307.36795,-1097.3048,5864.572,-2255.4192,315.97122,154.1896,302.43378,-59.88773,4275.3604,7276.6855,2501.0244,-1479.851,-3024.745,-1809.9519,2927.8093,-4404.0815,-4597.7534,-2058.7214,3315.7986] +[1.871623,-0.69434905,-9.597992e-3,-3.4512775,-12.099142,-0.60258275,-2.1632185,1.0532264,-1.9475107,-0.89574903,0.8268037,0.19193709,-1.7785822,0.6476291,-0.14070302,-0.17608814,-1.0499413,-12.243431,-6.723165e-2,-133.25264,1.3830144e-3,23.606426,-4.4686324e-3,1.5154866,5.647482,2.3458203e-2,-2.2378974,2.5370095,0.66975546,0.18268432,-3.3365212e-2,0.7013488,0.87992287,0.5318145,-0.90463257,-0.16919184,0.657908,0.9673947,-1.2923753,0.5005782,0.3851992,0.6974846,5.1378965,1.5206656,-1.8163713,-20.834082,-0.18877876,0.8886714,-0.8446348,10.540034,11.37932,0.182711,-2.0050786,0.6254593,1.1034613,3.8580709,-5.2021885,-2.230734,-1.794178,0.39106497,-0.80938613,-0.5094474,-4.0209317,1.5751765] +[-87.38458,-61.88547,-77.78206,-88.43077,-94.30282,-23.171593,-39.720543,47.347664,-76.373604,-97.32084,-91.673874,-93.06639,-24.45533,-82.11456,-50.65983,-8.282211,-62.318623,-1.7945938,-4.4562683,-57.797848,-72.966705,2.8155289,-98.03614,57.937504,7.237129,-73.059814,-88.45551,34.392334,-60.721226,-57.35563,-3.1042175,34.199455,-71.80935,-23.923409,-69.97397,-9.216278,62.15632,-70.334885,-15.712379,10.544235,36.857437,-61.641663,13.519524,-73.757645,-33.06685,-80.0233,-14.392632,72.19195,-51.674843,5.475235,-41.887623,7.433571,-5.465164,-82.67741,-89.607704,25.460907,-87.74089,-82.14257,-31.761482,-86.52606,-59.704292,-48.397453,-90.9834,-72.2701] +[-46.6892,89.12732,0.7465515,25.62262,7.794174,38.453793,85.92421,49.86781,39.21601,87.17505,-75.796295,-17.862892,43.495815,-53.17978,7.1279907,47.034466,65.43089,21.971985,66.2823,0.43374634,-0.100914,66.46458,0.43808746,87.80351,40.871555,-1.7138519,39.52617,87.25368,-40.668373,-10.477974,93.037544,48.76241,-63.186687,-12.722816,63.30073,54.472355,94.4757,-68.041595,12.157753,21.06411,95.6841,-42.99411,69.461914,-48.503525,18.204895,3.8409805,76.24074,81.23582,43.64637,57.709164,-3.6810303,40.684856,10.958084,-51.711353,-81.206024,98.22998,16.86615,36.823112,56.985752,-33.83731,73.76491,94.99991,22.627441,-45.88064] diff --git a/testsuite/tests/simd/should_run/floatx4_fma.hs b/testsuite/tests/simd/should_run/floatx4_fma.hs new file mode 100644 index 00000000000..588569e5239 --- /dev/null +++ b/testsuite/tests/simd/should_run/floatx4_fma.hs @@ -0,0 +1,133 @@ +{-# LANGUAGE MagicHash, UnboxedTuples #-} +import Control.Monad +import Data.Array.Base +import Foreign.Marshal.Array +import GHC.Int +import GHC.IO +import GHC.Prim +import GHC.Ptr + +data FloatX4 = FloatX4 FloatX4# + +indexAsFloatX4 :: UArray Int Float -> Int -> FloatX4# +indexAsFloatX4 (UArray l _ _ ba) i = case i - l of + I# i# -> indexFloatArrayAsFloatX4# ba i# + +readAsFloatX4 :: Ptr Float -> Int -> IO FloatX4 +readAsFloatX4 (Ptr addr) (I# i) = IO $ \s -> + case readFloatOffAddrAsFloatX4# addr i s of + (# s', v #) -> (# s', FloatX4 v #) + +writeAsFloatX4 :: Ptr Float -> Int -> FloatX4# -> IO () +writeAsFloatX4 (Ptr addr) (I# i) v = IO $ \s -> + (# writeFloatOffAddrAsFloatX4# addr i v s, () #) + +arr1 :: UArray Int Float +arr1 = listArray (0,63) [-46.6892,89.12732,-77.78206,25.62262,7.794174,38.453793,-39.720543,47.347664,39.21601,-97.32084,-91.673874,-93.06639,-24.45533,-82.11456,-50.65983,47.034466,-62.318623,-1.7945938,66.2823,0.43374634,-72.966705,2.8155289,-98.03614,57.937504,7.237129,-73.059814,39.52617,34.392334,-60.721226,-57.35563,93.037544,48.76241,-71.80935,-23.923409,-69.97397,54.472355,94.4757,-70.334885,12.157753,21.06411,95.6841,-61.641663,13.519524,-48.503525,18.204895,3.8409805,76.24074,81.23582,-51.674843,5.475235,-3.6810303,40.684856,-5.465164,-82.67741,-81.206024,25.460907,16.86615,36.823112,-31.761482,-86.52606,73.76491,94.99991,22.627441,-45.88064] + +input2 :: [Float] +input2 = [-87.38458,-61.88547,0.7465515,-88.43077,-94.30282,-23.171593,85.92421,49.86781,-76.373604,87.17505,-75.796295,-17.862892,43.495815,-53.17978,7.1279907,-8.282211,65.43089,21.971985,-4.4562683,-57.797848,-0.100914,66.46458,0.43808746,87.80351,40.871555,-1.7138519,-88.45551,87.25368,-40.668373,-10.477974,-3.1042175,34.199455,-63.186687,-12.722816,63.30073,-9.216278,62.15632,-68.041595,-15.712379,10.544235,36.857437,-42.99411,69.461914,-73.757645,-33.06685,-80.0233,-14.392632,72.19195,43.64637,57.709164,-41.887623,7.433571,10.958084,-51.711353,-89.607704,98.22998,-87.74089,-82.14257,56.985752,-33.83731,-59.704292,-48.397453,-90.9834,-72.2701] + +arr3 :: UArray Int Float +arr3 = listArray (0,63) [-82.874825,24.663322,80.977585,-5.539955,30.870918,-66.322014,68.622406,-32.070335,33.606728,52.395947,-28.537193,87.26526,-3.6302185,40.552147,-72.941605,-46.680695,37.59773,-26.715553,-50.429577,57.255318,3.264801,56.19945,-37.02984,92.190384,89.34591,49.41381,-2.5357513,-86.19853,68.70002,30.182632,-74.67398,11.763702,89.85512,71.93959,37.59725,-26.887596,-63.618843,12.511604,-21.1969,18.45224,88.10219,27.665588,-76.59616,87.72276,30.83065,-5.2282104,-78.12404,-8.904892,-57.82519,57.57774,62.44629,79.00699,9.82901,88.902176,91.8949,-13.740692,-61.520546,87.340866,38.71158,-84.03725,20.15123,68.01758,-89.39148,85.45143] + +run :: (FloatX4# -> FloatX4# -> FloatX4# -> FloatX4#) -> UArray Int Float -> Ptr Float -> UArray Int Float -> IO [Float] +run f a b c = allocaArray 64 $ \result -> do + forM_ [0,4..63] $ \i -> do + let v = indexAsFloatX4 a i + FloatX4 w <- readAsFloatX4 b i + let x = indexAsFloatX4 c i + writeAsFloatX4 result i (f v w x) + peekArray 64 result +{-# INLINE run #-} + +runN :: (FloatX4# -> FloatX4# -> FloatX4# -> FloatX4#) -> UArray Int Float -> Ptr Float -> UArray Int Float -> IO [Float] +runN f a b c = allocaArray 64 $ \result -> do + forM_ [0,4..63] $ \i -> do + let v = indexAsFloatX4 a i + FloatX4 w <- readAsFloatX4 b i + let x = indexAsFloatX4 c i + writeAsFloatX4 result i (f v w x) + peekArray 64 result +{-# NOINLINE runN #-} + +main :: IO () +main = do + withArray input2 $ \arr2 -> do + run (\x y z -> fmaddFloatX4# x y z) arr1 arr2 arr3 >>= print + run (\x y z -> fmaddFloatX4# y x z) arr1 arr2 arr3 >>= print + run (\x y z -> fmaddFloatX4# z y x) arr1 arr2 arr3 >>= print + run (\x y z -> fmaddFloatX4# y z x) arr1 arr2 arr3 >>= print + run (\x y z -> fmaddFloatX4# z x y) arr1 arr2 arr3 >>= print + run (\x y z -> fmaddFloatX4# x z y) arr1 arr2 arr3 >>= print + run (\x y z -> fmsubFloatX4# x y z) arr1 arr2 arr3 >>= print + run (\x y z -> fmsubFloatX4# y x z) arr1 arr2 arr3 >>= print + run (\x y z -> fmsubFloatX4# z y x) arr1 arr2 arr3 >>= print + run (\x y z -> fmsubFloatX4# y z x) arr1 arr2 arr3 >>= print + run (\x y z -> fmsubFloatX4# z x y) arr1 arr2 arr3 >>= print + run (\x y z -> fmsubFloatX4# x z y) arr1 arr2 arr3 >>= print + run (\x y z -> fnmaddFloatX4# x y z) arr1 arr2 arr3 >>= print + run (\x y z -> fnmaddFloatX4# y x z) arr1 arr2 arr3 >>= print + run (\x y z -> fnmaddFloatX4# z y x) arr1 arr2 arr3 >>= print + run (\x y z -> fnmaddFloatX4# y z x) arr1 arr2 arr3 >>= print + run (\x y z -> fnmaddFloatX4# z x y) arr1 arr2 arr3 >>= print + run (\x y z -> fnmaddFloatX4# x z y) arr1 arr2 arr3 >>= print + run (\x y z -> fnmsubFloatX4# x y z) arr1 arr2 arr3 >>= print + run (\x y z -> fnmsubFloatX4# y x z) arr1 arr2 arr3 >>= print + run (\x y z -> fnmsubFloatX4# z y x) arr1 arr2 arr3 >>= print + run (\x y z -> fnmsubFloatX4# y z x) arr1 arr2 arr3 >>= print + run (\x y z -> fnmsubFloatX4# z x y) arr1 arr2 arr3 >>= print + run (\x y z -> fnmsubFloatX4# x z y) arr1 arr2 arr3 >>= print + runN (\x y z -> fmaddFloatX4# x y z) arr1 arr2 arr3 >>= print + runN (\x y z -> fmaddFloatX4# y x z) arr1 arr2 arr3 >>= print + runN (\x y z -> fmaddFloatX4# z y x) arr1 arr2 arr3 >>= print + runN (\x y z -> fmaddFloatX4# y z x) arr1 arr2 arr3 >>= print + runN (\x y z -> fmaddFloatX4# z x y) arr1 arr2 arr3 >>= print + runN (\x y z -> fmaddFloatX4# x z y) arr1 arr2 arr3 >>= print + runN (\x y z -> fmsubFloatX4# x y z) arr1 arr2 arr3 >>= print + runN (\x y z -> fmsubFloatX4# y x z) arr1 arr2 arr3 >>= print + runN (\x y z -> fmsubFloatX4# z y x) arr1 arr2 arr3 >>= print + runN (\x y z -> fmsubFloatX4# y z x) arr1 arr2 arr3 >>= print + runN (\x y z -> fmsubFloatX4# z x y) arr1 arr2 arr3 >>= print + runN (\x y z -> fmsubFloatX4# x z y) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmaddFloatX4# x y z) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmaddFloatX4# y x z) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmaddFloatX4# z y x) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmaddFloatX4# y z x) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmaddFloatX4# z x y) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmaddFloatX4# x z y) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmsubFloatX4# x y z) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmsubFloatX4# y x z) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmsubFloatX4# z y x) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmsubFloatX4# y z x) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmsubFloatX4# z x y) arr1 arr2 arr3 >>= print + runN (\x y z -> fnmsubFloatX4# x z y) arr1 arr2 arr3 >>= print + +{- +The values was generated by: +{- cabal: +build-depends: base, random >= 1.3.0 +-} +import System.Random.Stateful +import qualified Data.List as List +import Control.Monad + +main :: IO () +main = do + let xs, ys, zs :: [Float] + (xs, ys, zs) = runStateGen_ (mkStdGen 42) $ \g -> do + a <- replicateM 64 (uniformRM (-100.0, 100.0) g) + b <- replicateM 64 (uniformRM (-100.0, 100.0) g) + c <- replicateM 64 (uniformRM (-100.0, 100.0) g) + pure (a, b, c) + print xs + print ys + print zs +-} + +{- +The code was generated by: +:m + Data.List +putStr $ unlines ([" run (\\x y z -> " ++ intercalate " " [f,a,b,c] ++ ") arr1 arr2 arr3 >>= print" | f <- ["fmaddFloatX4#","fmsubFloatX4#","fnmaddFloatX4#","fnmsubFloatX4#"], [a,b,c] <- permutations ["x", "y", "z"]]) +putStr $ unlines ([" runN (\\x y z -> " ++ intercalate " " [f,a,b,c] ++ ") arr1 arr2 arr3 >>= print" | f <- ["fmaddFloatX4#","fmsubFloatX4#","fnmaddFloatX4#","fnmsubFloatX4#"], [a,b,c] <- permutations ["x", "y", "z"]]) +-} diff --git a/testsuite/tests/simd/should_run/floatx4_fma.stdout b/testsuite/tests/simd/should_run/floatx4_fma.stdout new file mode 100644 index 00000000000..529ec678ac4 --- /dev/null +++ b/testsuite/tests/simd/should_run/floatx4_fma.stdout @@ -0,0 +1,48 @@ +[3997.0415,-5491.023,22.909271,-2271.368,-704.14166,-957.3576,-3344.3337,2329.054,-2961.4614,-8431.553,6920.003,1749.7002,-1067.3347,4407.386,-434.0444,-436.23007,-4039.9653,-66.14634,-345.8013,32.185715,10.628163,243.33238,-79.97824,5179.3066,385.13864,174.62752,-3498.8433,2914.6592,2538.1335,631.15344,-363.48276,1679.4115,4627.25,376.3127,-4391.806,-528.92,5808.643,4798.2095,-212.22412,240.55717,3614.7727,2677.894,862.49585,3665.2285,-571.1479,-312.59616,-1175.4288,5855.667,-2313.2444,373.54898,216.6359,381.44077,-50.05872,4364.2627,7368.58,2487.2837,-1541.3716,-2937.4043,-1771.2404,2843.772,-4383.93,-4529.736,-2148.113,3401.25] +[3997.0415,-5491.023,22.909271,-2271.368,-704.14166,-957.3576,-3344.3337,2329.054,-2961.4614,-8431.553,6920.003,1749.7002,-1067.3347,4407.386,-434.0444,-436.23007,-4039.9653,-66.14634,-345.8013,32.185715,10.628163,243.33238,-79.97824,5179.3066,385.13864,174.62752,-3498.8433,2914.6592,2538.1335,631.15344,-363.48276,1679.4115,4627.25,376.3127,-4391.806,-528.92,5808.643,4798.2095,-212.22412,240.55717,3614.7727,2677.894,862.49585,3665.2285,-571.1479,-312.59616,-1175.4288,5855.667,-2313.2444,373.54898,216.6359,381.44077,-50.05872,4364.2627,7368.58,2487.2837,-1541.3716,-2937.4043,-1771.2404,2843.772,-4383.93,-4529.736,-2148.113,3401.25] +[7195.293,-1437.1741,-17.32812,515.52515,-2903.4204,1575.2405,5856.6055,-1551.9297,-2527.451,4470.2983,2071.3396,-1651.8763,-182.35464,-2238.6687,-570.5869,433.65384,2397.7344,-588.7883,291.01004,-3308.8003,-73.29617,3738.0884,-114.258446,8152.577,3658.9434,-157.74777,263.82736,-7486.7466,-2854.6392,-373.60846,324.84183,451.07462,-5749.4565,-939.19763,2309.9595,302.2759,-3859.8374,-921.6444,345.2115,215.62888,3342.905,-1251.099,-5306.9966,-6518.728,-1001.2676,422.21964,1200.6512,-561.6257,-2575.5344,3328.2385,-2619.4077,627.9889,102.24195,-4679.929,-8315.697,-1324.287,5414.7334,-7137.58,2174.2468,2757.0684,-1129.35,-3196.8777,8155.768,-6221.4644] +[7195.293,-1437.1741,-17.32812,515.52515,-2903.4204,1575.2405,5856.6055,-1551.9297,-2527.451,4470.2983,2071.3396,-1651.8763,-182.35464,-2238.6687,-570.5869,433.65384,2397.7344,-588.7883,291.01004,-3308.8003,-73.29617,3738.0884,-114.258446,8152.577,3658.9434,-157.74777,263.82736,-7486.7466,-2854.6392,-373.60846,324.84183,451.07462,-5749.4565,-939.19763,2309.9595,302.2759,-3859.8374,-921.6444,345.2115,215.62888,3342.905,-1251.099,-5306.9966,-6518.728,-1001.2676,422.21964,1200.6512,-561.6257,-2575.5344,3328.2385,-2619.4077,627.9889,102.24195,-4679.929,-8315.697,-1324.287,5414.7334,-7137.58,2174.2468,2757.0684,-1129.35,-3196.8777,8155.768,-6221.4644] +[3781.9749,2136.2903,-6297.857,-230.37894,146.3105,-2573.5046,-2639.795,-1468.5876,1241.5482,-5012.0425,2540.3188,-8139.3257,132.274,-3383.1016,3702.3372,-2203.8838,-2277.6077,69.91555,-3347.0447,-32.963562,-238.3227,224.69576,3630.7004,5429.0845,687.47943,-3611.8777,-188.68405,-2877.315,-4212.218,-1741.6218,-6950.588,607.8259,-6515.624,-1733.7631,-2567.528,-1473.8469,-5948.2783,-948.0438,-273.41904,399.22424,8466.836,-1748.3469,-966.08167,-4328.621,528.2019,-100.10475,-5970.627,-651.2042,3031.7542,372.96082,-271.7543,3221.8215,-42.759068,-7401.9126,-7552.027,-251.6205,-1125.3556,3134.02,-1172.5514,7237.5747,1426.7493,6413.266,-2113.6838,-3992.8362] +[3781.9749,2136.2903,-6297.857,-230.37894,146.3105,-2573.5046,-2639.795,-1468.5876,1241.5482,-5012.0425,2540.3188,-8139.3257,132.274,-3383.1016,3702.3372,-2203.8838,-2277.6077,69.91555,-3347.0447,-32.963562,-238.3227,224.69576,3630.7004,5429.0845,687.47943,-3611.8777,-188.68405,-2877.315,-4212.218,-1741.6218,-6950.588,607.8259,-6515.624,-1733.7631,-2567.528,-1473.8469,-5948.2783,-948.0438,-273.41904,399.22424,8466.836,-1748.3469,-966.08167,-4328.621,528.2019,-100.10475,-5970.627,-651.2042,3031.7542,372.96082,-271.7543,3221.8215,-42.759068,-7401.9126,-7552.027,-251.6205,-1125.3556,3134.02,-1172.5514,7237.5747,1426.7493,6413.266,-2113.6838,-3992.8362] +[4162.791,-5540.3496,-139.0459,-2260.288,-765.8835,-824.7136,-3481.5786,2393.1946,-3028.6748,-8536.345,6977.077,1575.1697,-1060.0743,4326.282,-288.1612,-342.86868,-4115.1606,-12.715235,-244.94215,-82.32492,4.0985613,130.93349,-5.9185658,4994.926,206.44682,75.7999,-3493.7717,3087.0562,2400.7334,570.78815,-214.1348,1655.8842,4447.5396,232.43355,-4467.0005,-475.14478,5935.8804,4773.186,-169.83032,203.6527,3438.5684,2622.5627,1015.6882,3489.783,-632.80914,-302.13974,-1019.1808,5873.4766,-2197.594,258.3935,91.74332,223.42677,-69.716736,4186.4585,7184.7905,2514.7651,-1418.3304,-3112.086,-1848.6636,3011.8464,-4424.233,-4665.771,-1969.3301,3230.347] +[4162.791,-5540.3496,-139.0459,-2260.288,-765.8835,-824.7136,-3481.5786,2393.1946,-3028.6748,-8536.345,6977.077,1575.1697,-1060.0743,4326.282,-288.1612,-342.86868,-4115.1606,-12.715235,-244.94215,-82.32492,4.0985613,130.93349,-5.9185658,4994.926,206.44682,75.7999,-3493.7717,3087.0562,2400.7334,570.78815,-214.1348,1655.8842,4447.5396,232.43355,-4467.0005,-475.14478,5935.8804,4773.186,-169.83032,203.6527,3438.5684,2622.5627,1015.6882,3489.783,-632.80914,-302.13974,-1019.1808,5873.4766,-2197.594,258.3935,91.74332,223.42677,-69.716736,4186.4585,7184.7905,2514.7651,-1418.3304,-3112.086,-1848.6636,3011.8464,-4424.233,-4665.771,-1969.3301,3230.347] +[7288.6714,-1615.4287,138.236,464.27988,-2919.0088,1498.3329,5936.0464,-1646.625,-2605.8828,4664.94,2254.6875,-1465.7435,-133.44398,-2074.4397,-469.26724,339.5849,2522.3716,-585.19916,158.44542,-3309.668,72.63724,3732.4573,81.813835,8036.702,3644.4692,-11.62814,184.77502,-7555.5313,-2733.1968,-258.89722,138.76674,353.5498,-5605.838,-891.35077,2449.9075,193.3312,-4048.7888,-780.9746,320.89597,173.50066,3151.5369,-1127.8157,-5334.0356,-6421.7207,-1037.6774,414.53766,1048.1698,-724.0973,-2472.1848,3317.288,-2612.0457,546.6192,113.17228,-4514.574,-8153.2847,-1375.2089,5381.0015,-7211.2266,2237.7698,2930.1206,-1276.8799,-3386.8774,8110.513,-6129.703] +[7288.6714,-1615.4287,138.236,464.27988,-2919.0088,1498.3329,5936.0464,-1646.625,-2605.8828,4664.94,2254.6875,-1465.7435,-133.44398,-2074.4397,-469.26724,339.5849,2522.3716,-585.19916,158.44542,-3309.668,72.63724,3732.4573,81.813835,8036.702,3644.4692,-11.62814,184.77502,-7555.5313,-2733.1968,-258.89722,138.76674,353.5498,-5605.838,-891.35077,2449.9075,193.3312,-4048.7888,-780.9746,320.89597,173.50066,3151.5369,-1127.8157,-5334.0356,-6421.7207,-1037.6774,414.53766,1048.1698,-724.0973,-2472.1848,3317.288,-2612.0457,546.6192,113.17228,-4514.574,-8153.2847,-1375.2089,5381.0015,-7211.2266,2237.7698,2930.1206,-1276.8799,-3386.8774,8110.513,-6129.703] +[3956.744,2260.0613,-6299.3496,-53.51739,334.91614,-2527.1614,-2811.6433,-1568.3232,1394.2954,-5186.3926,2691.9114,-8103.5996,45.282375,-3276.742,3688.081,-2187.3193,-2408.4695,25.971582,-3338.1323,82.63213,-238.12086,91.7666,3629.8245,5253.477,605.7363,-3608.45,-11.773023,-3051.8223,-4130.881,-1720.6659,-6944.3794,539.427,-6389.251,-1708.3174,-2694.1296,-1455.4144,-6072.5913,-811.96063,-241.9943,378.13577,8393.121,-1662.3588,-1105.0055,-4181.1055,594.3356,59.941845,-5941.842,-795.58813,2944.4614,257.54248,-187.97906,3206.9543,-64.67524,-7298.4897,-7372.8115,-448.08047,-949.87384,3298.3052,-1286.5228,7305.2495,1546.158,6510.061,-1931.717,-3848.2961] +[3956.744,2260.0613,-6299.3496,-53.51739,334.91614,-2527.1614,-2811.6433,-1568.3232,1394.2954,-5186.3926,2691.9114,-8103.5996,45.282375,-3276.742,3688.081,-2187.3193,-2408.4695,25.971582,-3338.1323,82.63213,-238.12086,91.7666,3629.8245,5253.477,605.7363,-3608.45,-11.773023,-3051.8223,-4130.881,-1720.6659,-6944.3794,539.427,-6389.251,-1708.3174,-2694.1296,-1455.4144,-6072.5913,-811.96063,-241.9943,378.13577,8393.121,-1662.3588,-1105.0055,-4181.1055,594.3356,59.941845,-5941.842,-795.58813,2944.4614,257.54248,-187.97906,3206.9543,-64.67524,-7298.4897,-7372.8115,-448.08047,-949.87384,3298.3052,-1286.5228,7305.2495,1546.158,6510.061,-1931.717,-3848.2961] +[-4162.791,5540.3496,139.0459,2260.288,765.8835,824.7136,3481.5786,-2393.1946,3028.6748,8536.345,-6977.077,-1575.1697,1060.0743,-4326.282,288.1612,342.86868,4115.1606,12.715235,244.94215,82.32492,-4.0985613,-130.93349,5.9185658,-4994.926,-206.44682,-75.7999,3493.7717,-3087.0562,-2400.7334,-570.78815,214.1348,-1655.8842,-4447.5396,-232.43355,4467.0005,475.14478,-5935.8804,-4773.186,169.83032,-203.6527,-3438.5684,-2622.5627,-1015.6882,-3489.783,632.80914,302.13974,1019.1808,-5873.4766,2197.594,-258.3935,-91.74332,-223.42677,69.716736,-4186.4585,-7184.7905,-2514.7651,1418.3304,3112.086,1848.6636,-3011.8464,4424.233,4665.771,1969.3301,-3230.347] +[-4162.791,5540.3496,139.0459,2260.288,765.8835,824.7136,3481.5786,-2393.1946,3028.6748,8536.345,-6977.077,-1575.1697,1060.0743,-4326.282,288.1612,342.86868,4115.1606,12.715235,244.94215,82.32492,-4.0985613,-130.93349,5.9185658,-4994.926,-206.44682,-75.7999,3493.7717,-3087.0562,-2400.7334,-570.78815,214.1348,-1655.8842,-4447.5396,-232.43355,4467.0005,475.14478,-5935.8804,-4773.186,169.83032,-203.6527,-3438.5684,-2622.5627,-1015.6882,-3489.783,632.80914,302.13974,1019.1808,-5873.4766,2197.594,-258.3935,-91.74332,-223.42677,69.716736,-4186.4585,-7184.7905,-2514.7651,1418.3304,3112.086,1848.6636,-3011.8464,4424.233,4665.771,1969.3301,-3230.347] +[-7288.6714,1615.4287,-138.236,-464.27988,2919.0088,-1498.3329,-5936.0464,1646.625,2605.8828,-4664.94,-2254.6875,1465.7435,133.44398,2074.4397,469.26724,-339.5849,-2522.3716,585.19916,-158.44542,3309.668,-72.63724,-3732.4573,-81.813835,-8036.702,-3644.4692,11.62814,-184.77502,7555.5313,2733.1968,258.89722,-138.76674,-353.5498,5605.838,891.35077,-2449.9075,-193.3312,4048.7888,780.9746,-320.89597,-173.50066,-3151.5369,1127.8157,5334.0356,6421.7207,1037.6774,-414.53766,-1048.1698,724.0973,2472.1848,-3317.288,2612.0457,-546.6192,-113.17228,4514.574,8153.2847,1375.2089,-5381.0015,7211.2266,-2237.7698,-2930.1206,1276.8799,3386.8774,-8110.513,6129.703] +[-7288.6714,1615.4287,-138.236,-464.27988,2919.0088,-1498.3329,-5936.0464,1646.625,2605.8828,-4664.94,-2254.6875,1465.7435,133.44398,2074.4397,469.26724,-339.5849,-2522.3716,585.19916,-158.44542,3309.668,-72.63724,-3732.4573,-81.813835,-8036.702,-3644.4692,11.62814,-184.77502,7555.5313,2733.1968,258.89722,-138.76674,-353.5498,5605.838,891.35077,-2449.9075,-193.3312,4048.7888,780.9746,-320.89597,-173.50066,-3151.5369,1127.8157,5334.0356,6421.7207,1037.6774,-414.53766,-1048.1698,724.0973,2472.1848,-3317.288,2612.0457,-546.6192,-113.17228,4514.574,8153.2847,1375.2089,-5381.0015,7211.2266,-2237.7698,-2930.1206,1276.8799,3386.8774,-8110.513,6129.703] +[-3956.744,-2260.0613,6299.3496,53.51739,-334.91614,2527.1614,2811.6433,1568.3232,-1394.2954,5186.3926,-2691.9114,8103.5996,-45.282375,3276.742,-3688.081,2187.3193,2408.4695,-25.971582,3338.1323,-82.63213,238.12086,-91.7666,-3629.8245,-5253.477,-605.7363,3608.45,11.773023,3051.8223,4130.881,1720.6659,6944.3794,-539.427,6389.251,1708.3174,2694.1296,1455.4144,6072.5913,811.96063,241.9943,-378.13577,-8393.121,1662.3588,1105.0055,4181.1055,-594.3356,-59.941845,5941.842,795.58813,-2944.4614,-257.54248,187.97906,-3206.9543,64.67524,7298.4897,7372.8115,448.08047,949.87384,-3298.3052,1286.5228,-7305.2495,-1546.158,-6510.061,1931.717,3848.2961] +[-3956.744,-2260.0613,6299.3496,53.51739,-334.91614,2527.1614,2811.6433,1568.3232,-1394.2954,5186.3926,-2691.9114,8103.5996,-45.282375,3276.742,-3688.081,2187.3193,2408.4695,-25.971582,3338.1323,-82.63213,238.12086,-91.7666,-3629.8245,-5253.477,-605.7363,3608.45,11.773023,3051.8223,4130.881,1720.6659,6944.3794,-539.427,6389.251,1708.3174,2694.1296,1455.4144,6072.5913,811.96063,241.9943,-378.13577,-8393.121,1662.3588,1105.0055,4181.1055,-594.3356,-59.941845,5941.842,795.58813,-2944.4614,-257.54248,187.97906,-3206.9543,64.67524,7298.4897,7372.8115,448.08047,949.87384,-3298.3052,1286.5228,-7305.2495,-1546.158,-6510.061,1931.717,3848.2961] +[-3997.0415,5491.023,-22.909271,2271.368,704.14166,957.3576,3344.3337,-2329.054,2961.4614,8431.553,-6920.003,-1749.7002,1067.3347,-4407.386,434.0444,436.23007,4039.9653,66.14634,345.8013,-32.185715,-10.628163,-243.33238,79.97824,-5179.3066,-385.13864,-174.62752,3498.8433,-2914.6592,-2538.1335,-631.15344,363.48276,-1679.4115,-4627.25,-376.3127,4391.806,528.92,-5808.643,-4798.2095,212.22412,-240.55717,-3614.7727,-2677.894,-862.49585,-3665.2285,571.1479,312.59616,1175.4288,-5855.667,2313.2444,-373.54898,-216.6359,-381.44077,50.05872,-4364.2627,-7368.58,-2487.2837,1541.3716,2937.4043,1771.2404,-2843.772,4383.93,4529.736,2148.113,-3401.25] +[-3997.0415,5491.023,-22.909271,2271.368,704.14166,957.3576,3344.3337,-2329.054,2961.4614,8431.553,-6920.003,-1749.7002,1067.3347,-4407.386,434.0444,436.23007,4039.9653,66.14634,345.8013,-32.185715,-10.628163,-243.33238,79.97824,-5179.3066,-385.13864,-174.62752,3498.8433,-2914.6592,-2538.1335,-631.15344,363.48276,-1679.4115,-4627.25,-376.3127,4391.806,528.92,-5808.643,-4798.2095,212.22412,-240.55717,-3614.7727,-2677.894,-862.49585,-3665.2285,571.1479,312.59616,1175.4288,-5855.667,2313.2444,-373.54898,-216.6359,-381.44077,50.05872,-4364.2627,-7368.58,-2487.2837,1541.3716,2937.4043,1771.2404,-2843.772,4383.93,4529.736,2148.113,-3401.25] +[-7195.293,1437.1741,17.32812,-515.52515,2903.4204,-1575.2405,-5856.6055,1551.9297,2527.451,-4470.2983,-2071.3396,1651.8763,182.35464,2238.6687,570.5869,-433.65384,-2397.7344,588.7883,-291.01004,3308.8003,73.29617,-3738.0884,114.258446,-8152.577,-3658.9434,157.74777,-263.82736,7486.7466,2854.6392,373.60846,-324.84183,-451.07462,5749.4565,939.19763,-2309.9595,-302.2759,3859.8374,921.6444,-345.2115,-215.62888,-3342.905,1251.099,5306.9966,6518.728,1001.2676,-422.21964,-1200.6512,561.6257,2575.5344,-3328.2385,2619.4077,-627.9889,-102.24195,4679.929,8315.697,1324.287,-5414.7334,7137.58,-2174.2468,-2757.0684,1129.35,3196.8777,-8155.768,6221.4644] +[-7195.293,1437.1741,17.32812,-515.52515,2903.4204,-1575.2405,-5856.6055,1551.9297,2527.451,-4470.2983,-2071.3396,1651.8763,182.35464,2238.6687,570.5869,-433.65384,-2397.7344,588.7883,-291.01004,3308.8003,73.29617,-3738.0884,114.258446,-8152.577,-3658.9434,157.74777,-263.82736,7486.7466,2854.6392,373.60846,-324.84183,-451.07462,5749.4565,939.19763,-2309.9595,-302.2759,3859.8374,921.6444,-345.2115,-215.62888,-3342.905,1251.099,5306.9966,6518.728,1001.2676,-422.21964,-1200.6512,561.6257,2575.5344,-3328.2385,2619.4077,-627.9889,-102.24195,4679.929,8315.697,1324.287,-5414.7334,7137.58,-2174.2468,-2757.0684,1129.35,3196.8777,-8155.768,6221.4644] +[-3781.9749,-2136.2903,6297.857,230.37894,-146.3105,2573.5046,2639.795,1468.5876,-1241.5482,5012.0425,-2540.3188,8139.3257,-132.274,3383.1016,-3702.3372,2203.8838,2277.6077,-69.91555,3347.0447,32.963562,238.3227,-224.69576,-3630.7004,-5429.0845,-687.47943,3611.8777,188.68405,2877.315,4212.218,1741.6218,6950.588,-607.8259,6515.624,1733.7631,2567.528,1473.8469,5948.2783,948.0438,273.41904,-399.22424,-8466.836,1748.3469,966.08167,4328.621,-528.2019,100.10475,5970.627,651.2042,-3031.7542,-372.96082,271.7543,-3221.8215,42.759068,7401.9126,7552.027,251.6205,1125.3556,-3134.02,1172.5514,-7237.5747,-1426.7493,-6413.266,2113.6838,3992.8362] +[-3781.9749,-2136.2903,6297.857,230.37894,-146.3105,2573.5046,2639.795,1468.5876,-1241.5482,5012.0425,-2540.3188,8139.3257,-132.274,3383.1016,-3702.3372,2203.8838,2277.6077,-69.91555,3347.0447,32.963562,238.3227,-224.69576,-3630.7004,-5429.0845,-687.47943,3611.8777,188.68405,2877.315,4212.218,1741.6218,6950.588,-607.8259,6515.624,1733.7631,2567.528,1473.8469,5948.2783,948.0438,273.41904,-399.22424,-8466.836,1748.3469,966.08167,4328.621,-528.2019,100.10475,5970.627,651.2042,-3031.7542,-372.96082,271.7543,-3221.8215,42.759068,7401.9126,7552.027,251.6205,1125.3556,-3134.02,1172.5514,-7237.5747,-1426.7493,-6413.266,2113.6838,3992.8362] +[3997.0415,-5491.023,22.909271,-2271.368,-704.14166,-957.3576,-3344.3337,2329.054,-2961.4614,-8431.553,6920.003,1749.7002,-1067.3347,4407.386,-434.0444,-436.23007,-4039.9653,-66.14634,-345.8013,32.185715,10.628163,243.33238,-79.97824,5179.3066,385.13864,174.62752,-3498.8433,2914.6592,2538.1335,631.15344,-363.48276,1679.4115,4627.25,376.3127,-4391.806,-528.92,5808.643,4798.2095,-212.22412,240.55717,3614.7727,2677.894,862.49585,3665.2285,-571.1479,-312.59616,-1175.4288,5855.667,-2313.2444,373.54898,216.6359,381.44077,-50.05872,4364.2627,7368.58,2487.2837,-1541.3716,-2937.4043,-1771.2404,2843.772,-4383.93,-4529.736,-2148.113,3401.25] +[3997.0415,-5491.023,22.909271,-2271.368,-704.14166,-957.3576,-3344.3337,2329.054,-2961.4614,-8431.553,6920.003,1749.7002,-1067.3347,4407.386,-434.0444,-436.23007,-4039.9653,-66.14634,-345.8013,32.185715,10.628163,243.33238,-79.97824,5179.3066,385.13864,174.62752,-3498.8433,2914.6592,2538.1335,631.15344,-363.48276,1679.4115,4627.25,376.3127,-4391.806,-528.92,5808.643,4798.2095,-212.22412,240.55717,3614.7727,2677.894,862.49585,3665.2285,-571.1479,-312.59616,-1175.4288,5855.667,-2313.2444,373.54898,216.6359,381.44077,-50.05872,4364.2627,7368.58,2487.2837,-1541.3716,-2937.4043,-1771.2404,2843.772,-4383.93,-4529.736,-2148.113,3401.25] +[7195.293,-1437.1741,-17.32812,515.52515,-2903.4204,1575.2405,5856.6055,-1551.9297,-2527.451,4470.2983,2071.3396,-1651.8763,-182.35464,-2238.6687,-570.5869,433.65384,2397.7344,-588.7883,291.01004,-3308.8003,-73.29617,3738.0884,-114.258446,8152.577,3658.9434,-157.74777,263.82736,-7486.7466,-2854.6392,-373.60846,324.84183,451.07462,-5749.4565,-939.19763,2309.9595,302.2759,-3859.8374,-921.6444,345.2115,215.62888,3342.905,-1251.099,-5306.9966,-6518.728,-1001.2676,422.21964,1200.6512,-561.6257,-2575.5344,3328.2385,-2619.4077,627.9889,102.24195,-4679.929,-8315.697,-1324.287,5414.7334,-7137.58,2174.2468,2757.0684,-1129.35,-3196.8777,8155.768,-6221.4644] +[7195.293,-1437.1741,-17.32812,515.52515,-2903.4204,1575.2405,5856.6055,-1551.9297,-2527.451,4470.2983,2071.3396,-1651.8763,-182.35464,-2238.6687,-570.5869,433.65384,2397.7344,-588.7883,291.01004,-3308.8003,-73.29617,3738.0884,-114.258446,8152.577,3658.9434,-157.74777,263.82736,-7486.7466,-2854.6392,-373.60846,324.84183,451.07462,-5749.4565,-939.19763,2309.9595,302.2759,-3859.8374,-921.6444,345.2115,215.62888,3342.905,-1251.099,-5306.9966,-6518.728,-1001.2676,422.21964,1200.6512,-561.6257,-2575.5344,3328.2385,-2619.4077,627.9889,102.24195,-4679.929,-8315.697,-1324.287,5414.7334,-7137.58,2174.2468,2757.0684,-1129.35,-3196.8777,8155.768,-6221.4644] +[3781.9749,2136.2903,-6297.857,-230.37894,146.3105,-2573.5046,-2639.795,-1468.5876,1241.5482,-5012.0425,2540.3188,-8139.3257,132.274,-3383.1016,3702.3372,-2203.8838,-2277.6077,69.91555,-3347.0447,-32.963562,-238.3227,224.69576,3630.7004,5429.0845,687.47943,-3611.8777,-188.68405,-2877.315,-4212.218,-1741.6218,-6950.588,607.8259,-6515.624,-1733.7631,-2567.528,-1473.8469,-5948.2783,-948.0438,-273.41904,399.22424,8466.836,-1748.3469,-966.08167,-4328.621,528.2019,-100.10475,-5970.627,-651.2042,3031.7542,372.96082,-271.7543,3221.8215,-42.759068,-7401.9126,-7552.027,-251.6205,-1125.3556,3134.02,-1172.5514,7237.5747,1426.7493,6413.266,-2113.6838,-3992.8362] +[3781.9749,2136.2903,-6297.857,-230.37894,146.3105,-2573.5046,-2639.795,-1468.5876,1241.5482,-5012.0425,2540.3188,-8139.3257,132.274,-3383.1016,3702.3372,-2203.8838,-2277.6077,69.91555,-3347.0447,-32.963562,-238.3227,224.69576,3630.7004,5429.0845,687.47943,-3611.8777,-188.68405,-2877.315,-4212.218,-1741.6218,-6950.588,607.8259,-6515.624,-1733.7631,-2567.528,-1473.8469,-5948.2783,-948.0438,-273.41904,399.22424,8466.836,-1748.3469,-966.08167,-4328.621,528.2019,-100.10475,-5970.627,-651.2042,3031.7542,372.96082,-271.7543,3221.8215,-42.759068,-7401.9126,-7552.027,-251.6205,-1125.3556,3134.02,-1172.5514,7237.5747,1426.7493,6413.266,-2113.6838,-3992.8362] +[4162.791,-5540.3496,-139.0459,-2260.288,-765.8835,-824.7136,-3481.5786,2393.1946,-3028.6748,-8536.345,6977.077,1575.1697,-1060.0743,4326.282,-288.1612,-342.86868,-4115.1606,-12.715235,-244.94215,-82.32492,4.0985613,130.93349,-5.9185658,4994.926,206.44682,75.7999,-3493.7717,3087.0562,2400.7334,570.78815,-214.1348,1655.8842,4447.5396,232.43355,-4467.0005,-475.14478,5935.8804,4773.186,-169.83032,203.6527,3438.5684,2622.5627,1015.6882,3489.783,-632.80914,-302.13974,-1019.1808,5873.4766,-2197.594,258.3935,91.74332,223.42677,-69.716736,4186.4585,7184.7905,2514.7651,-1418.3304,-3112.086,-1848.6636,3011.8464,-4424.233,-4665.771,-1969.3301,3230.347] +[4162.791,-5540.3496,-139.0459,-2260.288,-765.8835,-824.7136,-3481.5786,2393.1946,-3028.6748,-8536.345,6977.077,1575.1697,-1060.0743,4326.282,-288.1612,-342.86868,-4115.1606,-12.715235,-244.94215,-82.32492,4.0985613,130.93349,-5.9185658,4994.926,206.44682,75.7999,-3493.7717,3087.0562,2400.7334,570.78815,-214.1348,1655.8842,4447.5396,232.43355,-4467.0005,-475.14478,5935.8804,4773.186,-169.83032,203.6527,3438.5684,2622.5627,1015.6882,3489.783,-632.80914,-302.13974,-1019.1808,5873.4766,-2197.594,258.3935,91.74332,223.42677,-69.716736,4186.4585,7184.7905,2514.7651,-1418.3304,-3112.086,-1848.6636,3011.8464,-4424.233,-4665.771,-1969.3301,3230.347] +[7288.6714,-1615.4287,138.236,464.27988,-2919.0088,1498.3329,5936.0464,-1646.625,-2605.8828,4664.94,2254.6875,-1465.7435,-133.44398,-2074.4397,-469.26724,339.5849,2522.3716,-585.19916,158.44542,-3309.668,72.63724,3732.4573,81.813835,8036.702,3644.4692,-11.62814,184.77502,-7555.5313,-2733.1968,-258.89722,138.76674,353.5498,-5605.838,-891.35077,2449.9075,193.3312,-4048.7888,-780.9746,320.89597,173.50066,3151.5369,-1127.8157,-5334.0356,-6421.7207,-1037.6774,414.53766,1048.1698,-724.0973,-2472.1848,3317.288,-2612.0457,546.6192,113.17228,-4514.574,-8153.2847,-1375.2089,5381.0015,-7211.2266,2237.7698,2930.1206,-1276.8799,-3386.8774,8110.513,-6129.703] +[7288.6714,-1615.4287,138.236,464.27988,-2919.0088,1498.3329,5936.0464,-1646.625,-2605.8828,4664.94,2254.6875,-1465.7435,-133.44398,-2074.4397,-469.26724,339.5849,2522.3716,-585.19916,158.44542,-3309.668,72.63724,3732.4573,81.813835,8036.702,3644.4692,-11.62814,184.77502,-7555.5313,-2733.1968,-258.89722,138.76674,353.5498,-5605.838,-891.35077,2449.9075,193.3312,-4048.7888,-780.9746,320.89597,173.50066,3151.5369,-1127.8157,-5334.0356,-6421.7207,-1037.6774,414.53766,1048.1698,-724.0973,-2472.1848,3317.288,-2612.0457,546.6192,113.17228,-4514.574,-8153.2847,-1375.2089,5381.0015,-7211.2266,2237.7698,2930.1206,-1276.8799,-3386.8774,8110.513,-6129.703] +[3956.744,2260.0613,-6299.3496,-53.51739,334.91614,-2527.1614,-2811.6433,-1568.3232,1394.2954,-5186.3926,2691.9114,-8103.5996,45.282375,-3276.742,3688.081,-2187.3193,-2408.4695,25.971582,-3338.1323,82.63213,-238.12086,91.7666,3629.8245,5253.477,605.7363,-3608.45,-11.773023,-3051.8223,-4130.881,-1720.6659,-6944.3794,539.427,-6389.251,-1708.3174,-2694.1296,-1455.4144,-6072.5913,-811.96063,-241.9943,378.13577,8393.121,-1662.3588,-1105.0055,-4181.1055,594.3356,59.941845,-5941.842,-795.58813,2944.4614,257.54248,-187.97906,3206.9543,-64.67524,-7298.4897,-7372.8115,-448.08047,-949.87384,3298.3052,-1286.5228,7305.2495,1546.158,6510.061,-1931.717,-3848.2961] +[3956.744,2260.0613,-6299.3496,-53.51739,334.91614,-2527.1614,-2811.6433,-1568.3232,1394.2954,-5186.3926,2691.9114,-8103.5996,45.282375,-3276.742,3688.081,-2187.3193,-2408.4695,25.971582,-3338.1323,82.63213,-238.12086,91.7666,3629.8245,5253.477,605.7363,-3608.45,-11.773023,-3051.8223,-4130.881,-1720.6659,-6944.3794,539.427,-6389.251,-1708.3174,-2694.1296,-1455.4144,-6072.5913,-811.96063,-241.9943,378.13577,8393.121,-1662.3588,-1105.0055,-4181.1055,594.3356,59.941845,-5941.842,-795.58813,2944.4614,257.54248,-187.97906,3206.9543,-64.67524,-7298.4897,-7372.8115,-448.08047,-949.87384,3298.3052,-1286.5228,7305.2495,1546.158,6510.061,-1931.717,-3848.2961] +[-4162.791,5540.3496,139.0459,2260.288,765.8835,824.7136,3481.5786,-2393.1946,3028.6748,8536.345,-6977.077,-1575.1697,1060.0743,-4326.282,288.1612,342.86868,4115.1606,12.715235,244.94215,82.32492,-4.0985613,-130.93349,5.9185658,-4994.926,-206.44682,-75.7999,3493.7717,-3087.0562,-2400.7334,-570.78815,214.1348,-1655.8842,-4447.5396,-232.43355,4467.0005,475.14478,-5935.8804,-4773.186,169.83032,-203.6527,-3438.5684,-2622.5627,-1015.6882,-3489.783,632.80914,302.13974,1019.1808,-5873.4766,2197.594,-258.3935,-91.74332,-223.42677,69.716736,-4186.4585,-7184.7905,-2514.7651,1418.3304,3112.086,1848.6636,-3011.8464,4424.233,4665.771,1969.3301,-3230.347] +[-4162.791,5540.3496,139.0459,2260.288,765.8835,824.7136,3481.5786,-2393.1946,3028.6748,8536.345,-6977.077,-1575.1697,1060.0743,-4326.282,288.1612,342.86868,4115.1606,12.715235,244.94215,82.32492,-4.0985613,-130.93349,5.9185658,-4994.926,-206.44682,-75.7999,3493.7717,-3087.0562,-2400.7334,-570.78815,214.1348,-1655.8842,-4447.5396,-232.43355,4467.0005,475.14478,-5935.8804,-4773.186,169.83032,-203.6527,-3438.5684,-2622.5627,-1015.6882,-3489.783,632.80914,302.13974,1019.1808,-5873.4766,2197.594,-258.3935,-91.74332,-223.42677,69.716736,-4186.4585,-7184.7905,-2514.7651,1418.3304,3112.086,1848.6636,-3011.8464,4424.233,4665.771,1969.3301,-3230.347] +[-7288.6714,1615.4287,-138.236,-464.27988,2919.0088,-1498.3329,-5936.0464,1646.625,2605.8828,-4664.94,-2254.6875,1465.7435,133.44398,2074.4397,469.26724,-339.5849,-2522.3716,585.19916,-158.44542,3309.668,-72.63724,-3732.4573,-81.813835,-8036.702,-3644.4692,11.62814,-184.77502,7555.5313,2733.1968,258.89722,-138.76674,-353.5498,5605.838,891.35077,-2449.9075,-193.3312,4048.7888,780.9746,-320.89597,-173.50066,-3151.5369,1127.8157,5334.0356,6421.7207,1037.6774,-414.53766,-1048.1698,724.0973,2472.1848,-3317.288,2612.0457,-546.6192,-113.17228,4514.574,8153.2847,1375.2089,-5381.0015,7211.2266,-2237.7698,-2930.1206,1276.8799,3386.8774,-8110.513,6129.703] +[-7288.6714,1615.4287,-138.236,-464.27988,2919.0088,-1498.3329,-5936.0464,1646.625,2605.8828,-4664.94,-2254.6875,1465.7435,133.44398,2074.4397,469.26724,-339.5849,-2522.3716,585.19916,-158.44542,3309.668,-72.63724,-3732.4573,-81.813835,-8036.702,-3644.4692,11.62814,-184.77502,7555.5313,2733.1968,258.89722,-138.76674,-353.5498,5605.838,891.35077,-2449.9075,-193.3312,4048.7888,780.9746,-320.89597,-173.50066,-3151.5369,1127.8157,5334.0356,6421.7207,1037.6774,-414.53766,-1048.1698,724.0973,2472.1848,-3317.288,2612.0457,-546.6192,-113.17228,4514.574,8153.2847,1375.2089,-5381.0015,7211.2266,-2237.7698,-2930.1206,1276.8799,3386.8774,-8110.513,6129.703] +[-3956.744,-2260.0613,6299.3496,53.51739,-334.91614,2527.1614,2811.6433,1568.3232,-1394.2954,5186.3926,-2691.9114,8103.5996,-45.282375,3276.742,-3688.081,2187.3193,2408.4695,-25.971582,3338.1323,-82.63213,238.12086,-91.7666,-3629.8245,-5253.477,-605.7363,3608.45,11.773023,3051.8223,4130.881,1720.6659,6944.3794,-539.427,6389.251,1708.3174,2694.1296,1455.4144,6072.5913,811.96063,241.9943,-378.13577,-8393.121,1662.3588,1105.0055,4181.1055,-594.3356,-59.941845,5941.842,795.58813,-2944.4614,-257.54248,187.97906,-3206.9543,64.67524,7298.4897,7372.8115,448.08047,949.87384,-3298.3052,1286.5228,-7305.2495,-1546.158,-6510.061,1931.717,3848.2961] +[-3956.744,-2260.0613,6299.3496,53.51739,-334.91614,2527.1614,2811.6433,1568.3232,-1394.2954,5186.3926,-2691.9114,8103.5996,-45.282375,3276.742,-3688.081,2187.3193,2408.4695,-25.971582,3338.1323,-82.63213,238.12086,-91.7666,-3629.8245,-5253.477,-605.7363,3608.45,11.773023,3051.8223,4130.881,1720.6659,6944.3794,-539.427,6389.251,1708.3174,2694.1296,1455.4144,6072.5913,811.96063,241.9943,-378.13577,-8393.121,1662.3588,1105.0055,4181.1055,-594.3356,-59.941845,5941.842,795.58813,-2944.4614,-257.54248,187.97906,-3206.9543,64.67524,7298.4897,7372.8115,448.08047,949.87384,-3298.3052,1286.5228,-7305.2495,-1546.158,-6510.061,1931.717,3848.2961] +[-3997.0415,5491.023,-22.909271,2271.368,704.14166,957.3576,3344.3337,-2329.054,2961.4614,8431.553,-6920.003,-1749.7002,1067.3347,-4407.386,434.0444,436.23007,4039.9653,66.14634,345.8013,-32.185715,-10.628163,-243.33238,79.97824,-5179.3066,-385.13864,-174.62752,3498.8433,-2914.6592,-2538.1335,-631.15344,363.48276,-1679.4115,-4627.25,-376.3127,4391.806,528.92,-5808.643,-4798.2095,212.22412,-240.55717,-3614.7727,-2677.894,-862.49585,-3665.2285,571.1479,312.59616,1175.4288,-5855.667,2313.2444,-373.54898,-216.6359,-381.44077,50.05872,-4364.2627,-7368.58,-2487.2837,1541.3716,2937.4043,1771.2404,-2843.772,4383.93,4529.736,2148.113,-3401.25] +[-3997.0415,5491.023,-22.909271,2271.368,704.14166,957.3576,3344.3337,-2329.054,2961.4614,8431.553,-6920.003,-1749.7002,1067.3347,-4407.386,434.0444,436.23007,4039.9653,66.14634,345.8013,-32.185715,-10.628163,-243.33238,79.97824,-5179.3066,-385.13864,-174.62752,3498.8433,-2914.6592,-2538.1335,-631.15344,363.48276,-1679.4115,-4627.25,-376.3127,4391.806,528.92,-5808.643,-4798.2095,212.22412,-240.55717,-3614.7727,-2677.894,-862.49585,-3665.2285,571.1479,312.59616,1175.4288,-5855.667,2313.2444,-373.54898,-216.6359,-381.44077,50.05872,-4364.2627,-7368.58,-2487.2837,1541.3716,2937.4043,1771.2404,-2843.772,4383.93,4529.736,2148.113,-3401.25] +[-7195.293,1437.1741,17.32812,-515.52515,2903.4204,-1575.2405,-5856.6055,1551.9297,2527.451,-4470.2983,-2071.3396,1651.8763,182.35464,2238.6687,570.5869,-433.65384,-2397.7344,588.7883,-291.01004,3308.8003,73.29617,-3738.0884,114.258446,-8152.577,-3658.9434,157.74777,-263.82736,7486.7466,2854.6392,373.60846,-324.84183,-451.07462,5749.4565,939.19763,-2309.9595,-302.2759,3859.8374,921.6444,-345.2115,-215.62888,-3342.905,1251.099,5306.9966,6518.728,1001.2676,-422.21964,-1200.6512,561.6257,2575.5344,-3328.2385,2619.4077,-627.9889,-102.24195,4679.929,8315.697,1324.287,-5414.7334,7137.58,-2174.2468,-2757.0684,1129.35,3196.8777,-8155.768,6221.4644] +[-7195.293,1437.1741,17.32812,-515.52515,2903.4204,-1575.2405,-5856.6055,1551.9297,2527.451,-4470.2983,-2071.3396,1651.8763,182.35464,2238.6687,570.5869,-433.65384,-2397.7344,588.7883,-291.01004,3308.8003,73.29617,-3738.0884,114.258446,-8152.577,-3658.9434,157.74777,-263.82736,7486.7466,2854.6392,373.60846,-324.84183,-451.07462,5749.4565,939.19763,-2309.9595,-302.2759,3859.8374,921.6444,-345.2115,-215.62888,-3342.905,1251.099,5306.9966,6518.728,1001.2676,-422.21964,-1200.6512,561.6257,2575.5344,-3328.2385,2619.4077,-627.9889,-102.24195,4679.929,8315.697,1324.287,-5414.7334,7137.58,-2174.2468,-2757.0684,1129.35,3196.8777,-8155.768,6221.4644] +[-3781.9749,-2136.2903,6297.857,230.37894,-146.3105,2573.5046,2639.795,1468.5876,-1241.5482,5012.0425,-2540.3188,8139.3257,-132.274,3383.1016,-3702.3372,2203.8838,2277.6077,-69.91555,3347.0447,32.963562,238.3227,-224.69576,-3630.7004,-5429.0845,-687.47943,3611.8777,188.68405,2877.315,4212.218,1741.6218,6950.588,-607.8259,6515.624,1733.7631,2567.528,1473.8469,5948.2783,948.0438,273.41904,-399.22424,-8466.836,1748.3469,966.08167,4328.621,-528.2019,100.10475,5970.627,651.2042,-3031.7542,-372.96082,271.7543,-3221.8215,42.759068,7401.9126,7552.027,251.6205,1125.3556,-3134.02,1172.5514,-7237.5747,-1426.7493,-6413.266,2113.6838,3992.8362] +[-3781.9749,-2136.2903,6297.857,230.37894,-146.3105,2573.5046,2639.795,1468.5876,-1241.5482,5012.0425,-2540.3188,8139.3257,-132.274,3383.1016,-3702.3372,2203.8838,2277.6077,-69.91555,3347.0447,32.963562,238.3227,-224.69576,-3630.7004,-5429.0845,-687.47943,3611.8777,188.68405,2877.315,4212.218,1741.6218,6950.588,-607.8259,6515.624,1733.7631,2567.528,1473.8469,5948.2783,948.0438,273.41904,-399.22424,-8466.836,1748.3469,966.08167,4328.621,-528.2019,100.10475,5970.627,651.2042,-3031.7542,-372.96082,271.7543,-3221.8215,42.759068,7401.9126,7552.027,251.6205,1125.3556,-3134.02,1172.5514,-7237.5747,-1426.7493,-6413.266,2113.6838,3992.8362] -- GitLab