[commit: vector] : Improve basicSet for primitive vectors (84dae34)
Geoffrey Mainland
gmainlan at ghc.haskell.org
Fri Jul 19 14:23:45 CEST 2013
Repository : http://darcs.haskell.org/ghc.git/
On branch :
http://hackage.haskell.org/trac/ghc/changeset/84dae347965c1a53eaaac416c006324735380dec
>---------------------------------------------------------------
commit 84dae347965c1a53eaaac416c006324735380dec
Author: Roman Leshchinskiy <rl at cse.unsw.edu.au>
Date: Fri Jan 27 23:44:26 2012 +0000
Improve basicSet for primitive vectors
>---------------------------------------------------------------
Data/Vector/Primitive/Mutable.hs | 3 +++
1 file changed, 3 insertions(+)
diff --git a/Data/Vector/Primitive/Mutable.hs b/Data/Vector/Primitive/Mutable.hs
index 447e315..d496e7e 100644
--- a/Data/Vector/Primitive/Mutable.hs
+++ b/Data/Vector/Primitive/Mutable.hs
@@ -105,6 +105,9 @@ instance Prim a => G.MVector MVector a where
where
sz = sizeOf (undefined :: a)
+ {-# INLINE basicSet #-}
+ basicSet (MVector i n arr) x = setByteArray arr i n x
+
-- Length information
-- ------------------
More information about the ghc-commits
mailing list