Skip to content
Snippets Groups Projects
Commit 38b7d817 authored by Andrew Martin's avatar Andrew Martin
Browse files

Prepare changelog for 0.9.1.0

Also, add mutableByteArrayAsForeignPtr for symmetry with
byteArrayAsForeignPtr.
parent 4b2de727
No related branches found
No related tags found
No related merge requests found
......@@ -63,6 +63,7 @@ module Data.Primitive.ByteArray (
isByteArrayPinned, isMutableByteArrayPinned,
#endif
byteArrayAsForeignPtr,
mutableByteArrayAsForeignPtr,
byteArrayContents,
withByteArrayContents,
mutableByteArrayContents,
......@@ -130,11 +131,21 @@ newAlignedPinnedByteArray (I# n#) (I# k#)
-- | Create a foreign pointer that points to the array's data. This operation
-- is only safe on /pinned/ byte arrays. The array's data is not garbage
-- collected while references to the foreign pointer exist.
-- collected while references to the foreign pointer exist. Writing to the
-- array through the foreign pointer results in undefined behavior.
byteArrayAsForeignPtr :: ByteArray -> ForeignPtr Word8
{-# INLINE byteArrayAsForeignPtr #-}
byteArrayAsForeignPtr (ByteArray arr#) = ForeignPtr (byteArrayContents# arr#) (PlainPtr (unsafeCoerce# arr#))
-- | Variant of 'byteArrayAsForeignPtr' for mutable byte arrays. Similarly, this
-- is only safe on /pinned/ mutable byte arrays. This function differs from the
-- variant for immutable arrays in that it is safe to write to the array though
-- the foreign pointer.
mutableByteArrayAsForeignPtr :: MutableByteArray RealWorld -> ForeignPtr Word8
{-# INLINE mutableByteArrayAsForeignPtr #-}
mutableByteArrayAsForeignPtr (MutableByteArray arr#) = ForeignPtr (mutableByteArrayContents# arr#) (PlainPtr arr#)
-- | Yield a pointer to the array's data. This operation is only safe on
-- /pinned/ byte arrays. Byte arrays allocated by 'newPinnedByteArray' and
-- 'newAlignedPinnedByteArray' are guaranteed to be pinned. Byte arrays
......
## Changes in version 0.9.1.0
* Add `byteArrayAsForeignPtr`.
* Make fromListN functions good consumers for list fusion.
* Add functions to improve `MutVar`'s interoperability with `IORef` and `STRef`.
* Add `createPrimArray` and `createByteArray`.
* Add `byteArrayAsForeignPtr` and `mutableByteArrayAsForeignPtr`.
* Use `copyMutableByteArrayNonOverlapping#` in the implementation of `copyMutableByteArray`
on sufficiently new GHCs. This does not change the contract for `copyMutableByteArray`.
This function has always been documented as having undefined behavior when the slices
overlap. However, overlaps previously were handled gracefully (with the semantics
of C's `memmove`). Going forward, users who do not uphold `copyMutableByteArray`'s
precondition will be met with unpredictable results.
* Drop support for GHC 8.0.
## Changes in version 0.9.0.0
......
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