[commit: vector] simd: Add PackedVector and PackedMVector instances for vectors of 3-tuples. (a448468)

Geoffrey Mainland gmainlan at ghc.haskell.org
Fri Jul 19 14:25:00 CEST 2013


Repository : http://darcs.haskell.org/ghc.git/

On branch  : simd

http://hackage.haskell.org/trac/ghc/changeset/a44846851d8c9970639e87003c31c0b78c5ab5aa

>---------------------------------------------------------------

commit a44846851d8c9970639e87003c31c0b78c5ab5aa
Author: Geoffrey Mainland <mainland at apeiron.net>
Date:   Thu Mar 28 18:49:42 2013 +0000

    Add PackedVector and PackedMVector instances for vectors of 3-tuples.

>---------------------------------------------------------------

 Data/Vector/Unboxed/Base.hs |   28 ++++++++++++++++++++++++++++
 1 file changed, 28 insertions(+)

diff --git a/Data/Vector/Unboxed/Base.hs b/Data/Vector/Unboxed/Base.hs
index bf3e5f7..4405726 100644
--- a/Data/Vector/Unboxed/Base.hs
+++ b/Data/Vector/Unboxed/Base.hs
@@ -471,4 +471,32 @@ instance (Unbox a, G.PackedVector Vector a) => G.PackedVector Vector (a, a) wher
       do  v1' <- G.basicUnsafePrefetchDataM v1 j k
           v2' <- G.basicUnsafePrefetchDataM v2 j k
           return $! V_2 n v1' v2'
+
+instance (Unbox a, M.PackedMVector MVector a) => M.PackedMVector MVector (a, a, a) where
+  {-# INLINE basicUnsafeReadAsMulti #-}
+  {-# INLINE basicUnsafeWriteAsMulti #-}
+  basicUnsafeReadAsMulti (MV_3 _ v1 v2 v3) j =
+      do  x <- M.basicUnsafeReadAsMulti v1 j
+          y <- M.basicUnsafeReadAsMulti v2 j
+          z <- M.basicUnsafeReadAsMulti v3 j
+          return $ M_3 x y z
+
+  basicUnsafeWriteAsMulti (MV_3 _ v1 v2 v3) j (M_3 x y z) =
+      do  M.basicUnsafeWriteAsMulti v1 j x
+          M.basicUnsafeWriteAsMulti v2 j y
+          M.basicUnsafeWriteAsMulti v3 j z
+
+instance (Unbox a, G.PackedVector Vector a) => G.PackedVector Vector (a, a, a) where
+  {-# INLINE basicUnsafeIndexAsMultiM #-}
+  basicUnsafeIndexAsMultiM (V_3 _ v1 v2 v3) j =
+      do  x <- G.basicUnsafeIndexAsMultiM v1 j
+          y <- G.basicUnsafeIndexAsMultiM v2 j
+          z <- G.basicUnsafeIndexAsMultiM v3 j
+          return $! M_3 x y z
+
+  basicUnsafePrefetchDataM (V_3 n v1 v2 v3) j k =
+      do  v1' <- G.basicUnsafePrefetchDataM v1 j k
+          v2' <- G.basicUnsafePrefetchDataM v2 j k
+          v3' <- G.basicUnsafePrefetchDataM v3 j k
+          return $! V_3 n v1' v2' v3'
 #endif /* defined(__GLASGOW_HASKELL_LLVM__) */






More information about the ghc-commits mailing list