Use the pinned prefix over pinned suffix in array combinators

- Remove withNewArrayUnsafePinned (asPtrUnsafe can be used)
- Deprecate newPinned
This commit is contained in:
Adithya Kumar 2023-07-26 17:31:08 +05:30
parent d29030f3bf
commit 3a3436c393
11 changed files with 55 additions and 64 deletions

View File

@ -33,7 +33,7 @@ module Streamly.Data.MutArray
-- Uninitialized Arrays
, new
, newPinned
, pinnedNew
-- From containers
, fromListN
@ -84,11 +84,20 @@ module Streamly.Data.MutArray
-- * Pinning & Unpinning
, pin
, unpin
-- * Deprecated
, newPinned
)
where
import Prelude hiding (length, read)
import Streamly.Internal.Data.Array.Mut
import Streamly.Internal.Data.Unbox (Unbox (..))
import Control.Monad.IO.Class (MonadIO)
#include "DocTestDataMutArray.hs"
{-# DEPRECATED newPinned "Please use pinnedNew instead." #-}
{-# INLINE newPinned #-}
newPinned :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a)
newPinned = pinnedNew

View File

@ -597,7 +597,7 @@ writeNUnsafe n = Fold step initial return
writeN :: MonadIO m => Int -> Fold m a (MutArray a)
writeN n = FL.take n $ writeNUnsafe n
-- >>> f n = MutArray.writeAppendWith (* 2) (MutArray.newPinned n)
-- >>> f n = MutArray.writeAppendWith (* 2) (MutArray.pinnedNew n)
-- >>> writeWith n = Fold.rmapM MutArray.rightSize (f n)
-- >>> writeWith n = Fold.rmapM MutArray.fromArrayStreamK (MutArray.writeChunks n)
@ -610,7 +610,7 @@ writeN n = FL.take n $ writeNUnsafe n
-- /Pre-release/
{-# INLINE_NORMAL writeWith #-}
writeWith :: MonadIO m => Int -> Fold m a (MutArray a)
-- writeWith n = FL.rmapM rightSize $ writeAppendWith (* 2) (newPinned n)
-- writeWith n = FL.rmapM rightSize $ writeAppendWith (* 2) (pinnedNew n)
writeWith elemCount = FL.rmapM extract $ FL.foldlM' step initial
where

View File

@ -42,15 +42,12 @@ module Streamly.Internal.Data.Array.Mut.Type
, nil
-- *** Uninitialized Arrays
, newPinned
, newPinnedBytes
, newAlignedPinned
, pinnedNew
, pinnedNewBytes
, pinnedNewAligned
, new
, newArrayWith
-- *** Initialized Arrays
, withNewArrayUnsafePinned
-- *** From streams
, ArrayUnsafe (..)
, writeNWithUnsafe
@ -388,7 +385,7 @@ isPinned MutArray{..} = Unboxed.isPinned arrContents
-- files and arrays.
-- GHC always guarantees word-aligned memory, alignment is important only when
-- we need more than that. See stg_newAlignedPinnedByteArrayzh and
-- we need more than that. See stg_pinnedNewAlignedByteArrayzh and
-- allocatePinned in GHC source.
-- | @newArrayWith allocator alignment count@ allocates a new array of zero
@ -441,22 +438,22 @@ newBytesAs ps bytes = do
-- 'Unboxed' instance of the type.
--
-- /Pre-release/
{-# INLINE newPinnedBytes #-}
newPinnedBytes :: MonadIO m =>
{-# INLINE pinnedNewBytes #-}
pinnedNewBytes :: MonadIO m =>
#ifdef DEVBUILD
Unbox a =>
#endif
Int -> m (MutArray a)
newPinnedBytes = newBytesAs Pinned
pinnedNewBytes = newBytesAs Pinned
-- | Like 'newArrayWith' but using an allocator is a pinned memory allocator and
-- the alignment is dictated by the 'Unboxed' instance of the type.
--
-- /Internal/
{-# INLINE newAlignedPinned #-}
newAlignedPinned :: (MonadIO m, Unbox a) => Int -> Int -> m (MutArray a)
newAlignedPinned =
newArrayWith (\s a -> liftIO $ Unboxed.newAlignedPinnedBytes s a)
{-# INLINE pinnedNewAligned #-}
pinnedNewAligned :: (MonadIO m, Unbox a) => Int -> Int -> m (MutArray a)
pinnedNewAligned =
newArrayWith (\s a -> liftIO $ Unboxed.pinnedNewAlignedBytes s a)
{-# INLINE newAs #-}
newAs :: (MonadIO m, Unbox a) => PinnedState -> Int -> m (MutArray a)
@ -471,9 +468,9 @@ newAs ps =
-- the array is uninitialized and the allocation is aligned as per the 'Unboxed'
-- instance of the type.
--
{-# INLINE newPinned #-}
newPinned :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a)
newPinned = newAs Pinned
{-# INLINE pinnedNew #-}
pinnedNew :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a)
pinnedNew = newAs Pinned
-- | Allocates an empty unpinned array that can hold 'count' items. The memory
-- of the array is uninitialized.
@ -482,21 +479,6 @@ newPinned = newAs Pinned
new :: (MonadIO m, Unbox a) => Int -> m (MutArray a)
new = newAs Unpinned
-- XXX This should create a full length uninitialzed array so that the pointer
-- can be used.
-- | Allocate a pinned MutArray of the given size and run an IO action passing
-- the array start pointer.
--
-- /Internal/
{-# INLINE withNewArrayUnsafePinned #-}
withNewArrayUnsafePinned ::
(MonadIO m, Unbox a) => Int -> (Ptr a -> m ()) -> m (MutArray a)
withNewArrayUnsafePinned count f = do
arr <- newPinned count
asPtrUnsafe arr
$ \p -> f p >> return arr
-------------------------------------------------------------------------------
-- Random writes
-------------------------------------------------------------------------------
@ -755,7 +737,7 @@ reallocExplicit elemSize newCapacityInBytes MutArray{..} = do
let newCapMaxInBytes = roundUpLargeArray newCapacityInBytes
contents <-
if Unboxed.isPinned arrContents
then Unboxed.newPinnedBytes newCapMaxInBytes
then Unboxed.pinnedNewBytes newCapMaxInBytes
else Unboxed.newUnpinnedBytes newCapMaxInBytes
let !(MutableByteArray mbarrFrom#) = arrContents
!(MutableByteArray mbarrTo#) = contents
@ -1864,15 +1846,15 @@ writeRevN = writeRevNWith new
-- | @pinnedWriteNAligned align n@ folds a maximum of @n@ elements from the
-- input stream to a 'MutArray' aligned to the given size.
--
-- >>> pinnedWriteNAligned align = MutArray.writeNWith (MutArray.newAlignedPinned align)
-- >>> pinnedWriteNAligned align n = MutArray.writeAppendN n (MutArray.newAlignedPinned align n)
-- >>> pinnedWriteNAligned align = MutArray.writeNWith (MutArray.pinnedNewAligned align)
-- >>> pinnedWriteNAligned align n = MutArray.writeAppendN n (MutArray.pinnedNewAligned align n)
--
-- /Pre-release/
--
{-# INLINE_NORMAL pinnedWriteNAligned #-}
pinnedWriteNAligned :: forall m a. (MonadIO m, Unbox a)
=> Int -> Int -> Fold m a (MutArray a)
pinnedWriteNAligned align = writeNWith (newAlignedPinned align)
pinnedWriteNAligned align = writeNWith (pinnedNewAligned align)
-- XXX Buffer to a list instead?
--

View File

@ -2440,7 +2440,7 @@ bottomBy cmp n = Fold step initial extract
where
initial = do
arr <- MA.newPinned n
arr <- MA.pinnedNew n
if n <= 0
then return $ Done arr
else return $ Partial (arr, 0)

View File

@ -476,7 +476,7 @@ splitAtArrayListRev n ls
spliceArraysLenUnsafe :: (MonadIO m, Unbox a)
=> Int -> Stream m (MutArray a) -> m (MutArray a)
spliceArraysLenUnsafe len buffered = do
arr <- liftIO $ MA.newPinned len
arr <- liftIO $ MA.pinnedNew len
D.foldlM' MA.spliceUnsafe (return arr) buffered
{-# INLINE _spliceArrays #-}
@ -485,7 +485,7 @@ _spliceArrays :: (MonadIO m, Unbox a)
_spliceArrays s = do
buffered <- D.foldr K.cons K.nil s
len <- K.fold FL.sum (fmap Array.length buffered)
arr <- liftIO $ MA.newPinned len
arr <- liftIO $ MA.pinnedNew len
final <- D.foldlM' writeArr (return arr) (toStream buffered)
return $ A.unsafeFreeze final
@ -507,7 +507,7 @@ spliceArraysRealloced :: forall m a. (MonadIO m, Unbox a)
=> Stream m (Array a) -> m (Array a)
spliceArraysRealloced s = do
let n = allocBytesToElemCount (undefined :: a) (4 * 1024)
idst = liftIO $ MA.newPinned n
idst = liftIO $ MA.pinnedNew n
arr <- D.foldlM' MA.spliceExp idst (fmap A.unsafeThaw s)
liftIO $ A.unsafeFreeze <$> MA.rightSize arr

View File

@ -16,8 +16,8 @@ module Streamly.Internal.Data.Unbox
, unpin
, newBytes
, newUnpinnedBytes
, newPinnedBytes
, newAlignedPinnedBytes
, pinnedNewBytes
, pinnedNewAlignedBytes
, nil
-- * Type Parser and Builder
@ -117,21 +117,21 @@ newUnpinnedBytes (I# nbytes) = IO $ \s ->
let c = MutableByteArray mbarr#
in (# s', c #)
{-# INLINE newPinnedBytes #-}
newPinnedBytes :: Int -> IO MutableByteArray
newPinnedBytes nbytes | nbytes < 0 =
errorWithoutStackTrace "newPinnedBytes: size must be >= 0"
newPinnedBytes (I# nbytes) = IO $ \s ->
{-# INLINE pinnedNewBytes #-}
pinnedNewBytes :: Int -> IO MutableByteArray
pinnedNewBytes nbytes | nbytes < 0 =
errorWithoutStackTrace "pinnedNewBytes: size must be >= 0"
pinnedNewBytes (I# nbytes) = IO $ \s ->
case newPinnedByteArray# nbytes s of
(# s', mbarr# #) ->
let c = MutableByteArray mbarr#
in (# s', c #)
{-# INLINE newAlignedPinnedBytes #-}
newAlignedPinnedBytes :: Int -> Int -> IO MutableByteArray
newAlignedPinnedBytes nbytes _align | nbytes < 0 =
errorWithoutStackTrace "newAlignedPinnedBytes: size must be >= 0"
newAlignedPinnedBytes (I# nbytes) (I# align) = IO $ \s ->
{-# INLINE pinnedNewAlignedBytes #-}
pinnedNewAlignedBytes :: Int -> Int -> IO MutableByteArray
pinnedNewAlignedBytes nbytes _align | nbytes < 0 =
errorWithoutStackTrace "pinnedNewAlignedBytes: size must be >= 0"
pinnedNewAlignedBytes (I# nbytes) (I# align) = IO $ \s ->
case newAlignedPinnedByteArray# nbytes align s of
(# s', mbarr# #) ->
let c = MutableByteArray mbarr#
@ -140,7 +140,7 @@ newAlignedPinnedBytes (I# nbytes) (I# align) = IO $ \s ->
{-# INLINE newBytes #-}
newBytes :: PinnedState -> Int -> IO MutableByteArray
newBytes Unpinned = newUnpinnedBytes
newBytes Pinned = newPinnedBytes
newBytes Pinned = pinnedNewBytes
-------------------------------------------------------------------------------
-- Pinning & Unpinning

View File

@ -180,7 +180,7 @@ import qualified Streamly.Internal.Data.Stream.StreamK.Type as K (mkStream)
{-# INLINABLE getChunk #-}
getChunk :: MonadIO m => Int -> Handle -> m (Array Word8)
getChunk size h = liftIO $ do
arr <- MArray.newPinnedBytes size
arr <- MArray.pinnedNewBytes size
-- ptr <- mallocPlainForeignPtrAlignedBytes size (alignment (undefined :: Word8))
MArray.asPtrUnsafe arr $ \p -> do
n <- hGetBufSome h p size

View File

@ -146,7 +146,7 @@ import qualified Streamly.Internal.System.IOVec.Type as RawIO
import qualified Streamly.Data.Array as A
import qualified Streamly.Data.Fold as FL
import qualified Streamly.Internal.Data.Array.Mut as MArray
(MutArray(..), newPinnedBytes, asPtrUnsafe)
(MutArray(..), pinnedNewBytes, asPtrUnsafe)
import qualified Streamly.Internal.Data.Stream.Chunked as AS
import qualified Streamly.Internal.Data.Stream as S
import qualified Streamly.Internal.Data.Stream.StreamD.Type as D
@ -217,7 +217,7 @@ openFile path mode = Handle . fst <$> FD.openFile path mode True
{-# INLINABLE readArrayUpto #-}
readArrayUpto :: Int -> Handle -> IO (Array Word8)
readArrayUpto size (Handle fd) = do
arr <- MArray.newPinnedBytes size
arr <- MArray.pinnedNewBytes size
-- ptr <- mallocPlainForeignPtrAlignedBytes size (alignment (undefined :: Word8))
MArray.asPtrUnsafe arr $ \p -> do
-- n <- hGetBufSome h p size

View File

@ -101,7 +101,7 @@ import qualified Streamly.Internal.Data.Array.Type as A
, writeNAs
)
import qualified Streamly.Internal.Data.Array.Mut as MArray
(MutArray(..), newPinnedBytes, asPtrUnsafe)
(MutArray(..), pinnedNewBytes, asPtrUnsafe)
import qualified Streamly.Internal.Data.Stream as S
import qualified Streamly.Internal.Data.Stream.StreamD.Type as D
(Stream(..), Step(..))
@ -260,7 +260,7 @@ readArrayUptoWith
-> h
-> IO (Array Word8)
readArrayUptoWith f size h = do
arr <- MArray.newPinnedBytes size
arr <- MArray.pinnedNewBytes size
-- ptr <- mallocPlainForeignPtrAlignedBytes size (alignment (undefined :: Word8))
MArray.asPtrUnsafe arr $ \p -> do
n <- f h p size

View File

@ -150,7 +150,7 @@ testBubbleWith asc =
else MA.bubble (flip compare) arr
return arr
)
(MA.newPinned $ length ls)
(MA.pinnedNew $ length ls)
testBubbleAsc :: Property
testBubbleAsc = testBubbleWith True
@ -160,7 +160,7 @@ testBubbleDesc = testBubbleWith False
testByteLengthWithMA :: forall a. Unbox a => a -> IO ()
testByteLengthWithMA _ = do
arrA <- MA.newPinned 100 :: IO (MutArray a)
arrA <- MA.pinnedNew 100 :: IO (MutArray a)
let arrW8 = MA.castUnsafe arrA :: MutArray Word8
MA.byteLength arrA `shouldBe` MA.length arrW8

View File

@ -42,7 +42,7 @@ testAppend =
action ls = do
x <- Stream.fold
(MArray.writeAppend (MArray.newPinned 0))
(MArray.writeAppend (MArray.pinnedNew 0))
(Stream.fromList (ls::[Int]))
lst <- MArray.toList x
assert (ls == lst)