Skip to content
Snippets Groups Projects
Commit a4484685 authored by gmainland's avatar gmainland
Browse files

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

parent 2f0d6d20
No related branches found
No related tags found
No related merge requests found
......@@ -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__) */
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment