Skip to content

Commit

Permalink
Rearrange bulk ByteArray operations and deprecate old versions
Browse files Browse the repository at this point in the history
Ignore-this: 88185d4f050856df3ec72d0e310d0ac7

darcs-hash:20110817221716-b2b0a-f4b15ab2483089e01ea3bc4c4adc9fe4e55c38ce.gz
  • Loading branch information
Roman Leshchinskiy committed Aug 17, 2011
1 parent d0b7464 commit 267e4d2
Showing 1 changed file with 85 additions and 25 deletions.
110 changes: 85 additions & 25 deletions Data/Primitive/ByteArray.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,9 @@ module Data.Primitive.ByteArray (
unsafeFreezeByteArray, unsafeThawByteArray,
sizeofByteArray, sizeofMutableByteArray, sameMutableByteArray,
byteArrayContents, mutableByteArrayContents,
copyByteArray, copyMutableByteArray, moveByteArray, fillByteArray,

-- * Deprecated operations
memcpyByteArray, memcpyByteArray', memmoveByteArray, memsetByteArray
) where

Expand Down Expand Up @@ -141,13 +143,39 @@ i# :: Int -> Int#
i# (I# n#) = n#
#endif

memcpyByteArray
:: PrimMonad m => MutableByteArray (PrimState m) -> Int
-> MutableByteArray (PrimState m) -> Int
-> Int -> m ()
{-# INLINE memcpyByteArray #-}
memcpyByteArray (MutableByteArray dst#) doff
(MutableByteArray src#) soff sz
-- | Copy a slice of an immutable byte array to a mutable byte array.
copyByteArray
:: PrimMonad m => ByteArray -- ^ source array
-> Int -- ^ offset into source array
-> MutableByteArray (PrimState m)
-- ^ destination array
-> Int -- ^ offset into destination array
-> Int -- ^ number of bytes to copy
-> m ()
{-# INLINE copyByteArray #-}
copyByteArray (ByteArray src#) soff (MutableByteArray dst#) doff sz
#if __GLASGOW_HASKELL__ >= 702
= primitive_ (copyByteArray# src# (i# soff) dst# (i# doff) (i# sz))
#else
= unsafePrimToPrim
$ memcpy_ba dst# (fromIntegral doff) src# (fromIntegral soff)
(fromIntegral sz)
#endif

-- | Copy a slice of a mutable byte array into another array. The two slices
-- may not overlap.
copyMutableByteArray
:: PrimMonad m => MutableByteArray (PrimState m)
-- ^ source array
-> Int -- ^ offset into source array
-> MutableByteArray (PrimState m)
-- ^ destination array
-> Int -- ^ offset into destination array
-> Int -- ^ number of bytes to copy
-> m ()
{-# INLINE copyMutableByteArray #-}
copyMutableByteArray (MutableByteArray src#) soff
(MutableByteArray dst#) doff sz
#if __GLASGOW_HASKELL__ >= 702
= primitive_ (copyMutableByteArray# src# (i# soff) dst# (i# doff) (i# sz))
#else
Expand All @@ -156,40 +184,72 @@ memcpyByteArray (MutableByteArray dst#) doff
(fromIntegral sz)
#endif

-- | Copy a slice of a mutable byte array into another, potentially
-- overlapping array.
moveByteArray
:: PrimMonad m => MutableByteArray (PrimState m)
-- ^ source array
-> Int -- ^ offset into source array
-> MutableByteArray (PrimState m)
-- ^ destination array
-> Int -- ^ offset into destination array
-> Int -- ^ number of bytes to copy
-> m ()
{-# INLINE moveByteArray #-}
moveByteArray (MutableByteArray src#) soff
(MutableByteArray dst#) doff sz
= unsafePrimToPrim
$ memmove_mba dst# (fromIntegral doff) src# (fromIntegral soff)
(fromIntegral sz)

-- | Fill a slice of a mutable byte array with a value.
fillByteArray
:: PrimMonad m => MutableByteArray (PrimState m)
-- ^ array to fill
-> Int -- ^ offset into array
-> Int -- ^ number of bytes to fill
-> Word8 -- ^ value to fill with
-> m ()
{-# INLINE fillByteArray #-}
fillByteArray (MutableByteArray dst#) doff c sz
= unsafePrimToPrim
$ memset_mba dst# (fromIntegral doff) (fromIntegral c) (fromIntegral sz)



memcpyByteArray
:: PrimMonad m => MutableByteArray (PrimState m) -> Int
-> MutableByteArray (PrimState m) -> Int
-> Int -> m ()
{-# DEPRECATED memcpyByteArray "Use copyMutableByteArray instead (NOTE: arguments are flipped)" #-}
{-# INLINE memcpyByteArray #-}
memcpyByteArray dst doff src soff sz
= copyMutableByteArray src soff dst doff sz

memcpyByteArray'
:: PrimMonad m => MutableByteArray (PrimState m) -> Int
-> ByteArray -> Int
-> Int -> m ()
{-# DEPRECATED memcpyByteArray' "Use copyByteArray instead (NOTE: arguments are flipped)" #-}
{-# INLINE memcpyByteArray' #-}
memcpyByteArray' (MutableByteArray dst#) doff
(ByteArray src#) soff sz
#if __GLASGOW_HASKELL__ >= 702
= primitive_ (copyByteArray# src# (i# soff) dst# (i# doff) (i# sz))
#else
= unsafePrimToPrim
$ memcpy_ba dst# (fromIntegral doff) src# (fromIntegral soff)
(fromIntegral sz)
#endif
memcpyByteArray' dst doff src soff sz
= copyByteArray src soff dst doff sz

memmoveByteArray
:: PrimMonad m => MutableByteArray (PrimState m) -> Int
-> MutableByteArray (PrimState m) -> Int
-> Int -> m ()
{-# DEPRECATED memmoveByteArray "Use moveByteArray instead (NOTE: arguments are flipped)" #-}
{-# INLINE memmoveByteArray #-}
memmoveByteArray (MutableByteArray dst#) doff
(MutableByteArray src#) soff sz
= unsafePrimToPrim
$ memmove_mba dst# (fromIntegral doff) src# (fromIntegral soff)
(fromIntegral sz)
memmoveByteArray dst doff src soff sz
= moveByteArray src soff dst doff sz

memsetByteArray
:: PrimMonad m => MutableByteArray (PrimState m) -> Int -> Word8
-> Int -> m ()
{-# DEPRECATED memsetByteArray "Use fillByteArray instead (NOTE: arguments are flipped)" #-}
{-# INLINE memsetByteArray #-}
memsetByteArray (MutableByteArray dst#) doff c sz
= unsafePrimToPrim
$ memset_mba dst# (fromIntegral doff) (fromIntegral c) (fromIntegral sz)

memsetByteArray dst off x sz = fillByteArray dst off sz x


foreign import ccall unsafe "primitive-memops.h memcpy_off"
Expand Down

0 comments on commit 267e4d2

Please sign in to comment.