[commit: packages/primitive] ghc-head: Add setByteArray (1bf1e7d)
git at git.haskell.org
git at git.haskell.org
Thu Sep 26 11:44:34 CEST 2013
Repository : ssh://git@git.haskell.org/primitive
On branch : ghc-head
Link : http://git.haskell.org/packages/primitive.git/commitdiff/1bf1e7d4f8e001e86e16840d0846e02f57b6220f
>---------------------------------------------------------------
commit 1bf1e7d4f8e001e86e16840d0846e02f57b6220f
Author: Roman Leshchinskiy <rl at cse.unsw.edu.au>
Date: Thu Jan 26 15:37:37 2012 -0700
Add setByteArray
>---------------------------------------------------------------
1bf1e7d4f8e001e86e16840d0846e02f57b6220f
Data/Primitive/ByteArray.hs | 35 ++++++++++++++++++++++++++++-------
1 file changed, 28 insertions(+), 7 deletions(-)
diff --git a/Data/Primitive/ByteArray.hs b/Data/Primitive/ByteArray.hs
index a7ba137..4e49043 100644
--- a/Data/Primitive/ByteArray.hs
+++ b/Data/Primitive/ByteArray.hs
@@ -13,17 +13,28 @@
--
module Data.Primitive.ByteArray (
+ -- * Types
ByteArray(..), MutableByteArray(..), ByteArray#, MutableByteArray#,
+ -- * Allocation
newByteArray, newPinnedByteArray, newAlignedPinnedByteArray,
+
+ -- * Element access
readByteArray, writeByteArray, indexByteArray,
+
+ -- * Freezing and thawing
unsafeFreezeByteArray, unsafeThawByteArray,
+
+ -- * Block operations
+ copyByteArray, copyMutableByteArray, moveByteArray,
+ setByteArray, fillByteArray,
+
+ -- * Information
sizeofByteArray, sizeofMutableByteArray, sameMutableByteArray,
byteArrayContents, mutableByteArrayContents,
- copyByteArray, copyMutableByteArray, moveByteArray, fillByteArray,
-- * Deprecated operations
- memcpyByteArray, memcpyByteArray', memmoveByteArray, memsetByteArray
+ memcpyByteArray, memcpyByteArray', memmoveByteArray, memsetByteArray,
) where
import Control.Monad.Primitive
@@ -203,18 +214,28 @@ moveByteArray (MutableByteArray dst#) doff
$ memmove_mba dst# (fromIntegral doff) src# (fromIntegral soff)
(fromIntegral sz)
--- | Fill a slice of a mutable byte array with a value.
+-- | Fill a slice of a mutable byte array with a value. The offset and length
+-- are given in elements of type @a@ rather than in bytes.
+setByteArray
+ :: (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -- ^ array to fill
+ -> Int -- ^ offset into array
+ -> Int -- ^ number of values to fill
+ -> a -- ^ value to fill with
+ -> m ()
+{-# INLINE setByteArray #-}
+setByteArray (MutableByteArray dst#) (I# doff#) (I# sz#) x
+ = primitive_ (setByteArray# dst# doff# sz# x)
+
+-- | Fill a slice of a mutable byte array with a byte.
fillByteArray
:: PrimMonad m => MutableByteArray (PrimState m)
-- ^ array to fill
-> Int -- ^ offset into array
-> Int -- ^ number of bytes to fill
- -> Word8 -- ^ value to fill with
+ -> Word8 -- ^ byte to fill with
-> m ()
{-# INLINE fillByteArray #-}
-fillByteArray (MutableByteArray dst#) doff sz c
- = unsafePrimToPrim
- $ memset_mba dst# (fromIntegral doff) (fromIntegral c) (fromIntegral sz)
+fillByteArray = setByteArray
More information about the ghc-commits
mailing list