diff --git a/core/src/Streamly/Data/MutArray.hs b/core/src/Streamly/Data/MutArray.hs index 26b9e26f1b..7b9cab5bb7 100644 --- a/core/src/Streamly/Data/MutArray.hs +++ b/core/src/Streamly/Data/MutArray.hs @@ -110,4 +110,4 @@ import Control.Monad.IO.Class (MonadIO) {-# DEPRECATED newPinned "Please use pinnedEmptyOf instead." #-} {-# INLINE newPinned #-} newPinned :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) -newPinned = pinnedEmptyOf +newPinned = emptyOf' diff --git a/core/src/Streamly/Internal/Data/Array/Type.hs b/core/src/Streamly/Internal/Data/Array/Type.hs index b8460e4511..9fa5715515 100644 --- a/core/src/Streamly/Internal/Data/Array/Type.hs +++ b/core/src/Streamly/Internal/Data/Array/Type.hs @@ -47,18 +47,18 @@ module Streamly.Internal.Data.Array.Type -- *** Stream Folds , unsafeMakePure , createOf - , pinnedCreateOf + , createOf' , unsafeCreateOf - , unsafePinnedCreateOf + , unsafeCreateOf' , create - , pinnedCreate + , create' , createWith -- *** From containers , fromListN - , pinnedFromListN + , fromListN' , fromList - , pinnedFromList + , fromList' , fromListRevN , fromListRev , fromStreamN @@ -112,7 +112,7 @@ module Streamly.Internal.Data.Array.Type -- *** Chunk -- | Group a stream into arrays. , chunksOf - , pinnedChunksOf + , chunksOf' , buildChunks , chunksEndBy , chunksEndBy' @@ -164,6 +164,12 @@ module Streamly.Internal.Data.Array.Type , lCompactGE , lPinnedCompactGE , compactGE + , pinnedCreateOf + , unsafePinnedCreateOf + , pinnedCreate + , pinnedFromListN + , pinnedFromList + , pinnedChunksOf ) where @@ -412,10 +418,11 @@ fromListN :: Unbox a => Int -> [a] -> Array a fromListN n xs = unsafePerformIO $ unsafeFreeze <$> MA.fromListN n xs -- | Like 'fromListN' but creates a pinned array. -{-# INLINABLE pinnedFromListN #-} -pinnedFromListN :: Unbox a => Int -> [a] -> Array a -pinnedFromListN n xs = - unsafePerformIO $ unsafeFreeze <$> MA.pinnedFromListN n xs +{-# INLINABLE fromListN' #-} +pinnedFromListN, fromListN' :: Unbox a => Int -> [a] -> Array a +fromListN' n xs = + unsafePerformIO $ unsafeFreeze <$> MA.fromListN' n xs +RENAME_PRIME(pinnedFromListN,fromListN) -- | Create an 'Array' from the first N elements of a list in reverse order. -- The array is allocated to size N, if the list terminates before N elements @@ -433,9 +440,10 @@ fromList :: Unbox a => [a] -> Array a fromList xs = unsafePerformIO $ unsafeFreeze <$> MA.fromList xs -- | Like 'fromList' but creates a pinned array. -{-# INLINE pinnedFromList #-} -pinnedFromList :: Unbox a => [a] -> Array a -pinnedFromList xs = unsafePerformIO $ unsafeFreeze <$> MA.pinnedFromList xs +{-# INLINE fromList' #-} +pinnedFromList, fromList' :: Unbox a => [a] -> Array a +fromList' xs = unsafePerformIO $ unsafeFreeze <$> MA.fromList' xs +RENAME_PRIME(pinnedFromList,fromList) -- | Create an 'Array' from a list in reverse order. The list must be of finite -- size. @@ -513,10 +521,11 @@ chunksOf :: forall m a. (MonadIO m, Unbox a) chunksOf n str = D.map unsafeFreeze $ MA.chunksOf n str -- | Like 'chunksOf' but creates pinned arrays. -{-# INLINE_NORMAL pinnedChunksOf #-} -pinnedChunksOf :: forall m a. (MonadIO m, Unbox a) +{-# INLINE_NORMAL chunksOf' #-} +pinnedChunksOf, chunksOf' :: forall m a. (MonadIO m, Unbox a) => Int -> D.Stream m a -> D.Stream m (Array a) -pinnedChunksOf n str = D.map unsafeFreeze $ MA.pinnedChunksOf n str +chunksOf' n str = D.map unsafeFreeze $ MA.chunksOf' n str +RENAME_PRIME(pinnedChunksOf,chunksOf) -- | Create arrays from the input stream using a predicate to find the end of -- the chunk. When the predicate matches, the chunk ends, the matching element @@ -536,7 +545,7 @@ chunksEndBy p = D.foldMany (Fold.takeEndBy p create) {-# INLINE chunksEndBy' #-} chunksEndBy' :: forall m a. (MonadIO m, Unbox a) => (a -> Bool) -> D.Stream m a -> D.Stream m (Array a) -chunksEndBy' p = D.foldMany (Fold.takeEndBy p pinnedCreate) +chunksEndBy' p = D.foldMany (Fold.takeEndBy p create') -- | Create chunks using newline as the separator, including it. {-# INLINE chunksEndByLn #-} @@ -877,14 +886,15 @@ writeN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a) writeN = createOf -- | Like 'createOf' but creates a pinned array. -{-# INLINE_NORMAL pinnedCreateOf #-} -pinnedCreateOf :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a) -pinnedCreateOf = fmap unsafeFreeze . MA.pinnedCreateOf +{-# INLINE_NORMAL createOf' #-} +pinnedCreateOf, createOf' :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a) +createOf' = fmap unsafeFreeze . MA.createOf' +RENAME_PRIME(pinnedCreateOf,createOf) -{-# DEPRECATED pinnedWriteN "Please use pinnedCreateOf instead." #-} +{-# DEPRECATED pinnedWriteN "Please use createOf' instead." #-} {-# INLINE pinnedWriteN #-} pinnedWriteN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a) -pinnedWriteN = pinnedCreateOf +pinnedWriteN = createOf' -- | @pinnedWriteNAligned alignment n@ folds a maximum of @n@ elements from the input -- stream to an 'Array' aligned to the given size. @@ -914,16 +924,17 @@ writeNUnsafe :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a) writeNUnsafe = unsafeCreateOf -{-# INLINE_NORMAL unsafePinnedCreateOf #-} -unsafePinnedCreateOf :: forall m a. (MonadIO m, Unbox a) +{-# INLINE_NORMAL unsafeCreateOf' #-} +unsafePinnedCreateOf, unsafeCreateOf' :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a) -unsafePinnedCreateOf n = unsafeFreeze <$> MA.unsafePinnedCreateOf n +unsafeCreateOf' n = unsafeFreeze <$> MA.unsafeCreateOf' n +RENAME_PRIME(unsafePinnedCreateOf,unsafeCreateOf) -{-# DEPRECATED pinnedWriteNUnsafe "Please use unsafePinnedCreateOf instead." #-} +{-# DEPRECATED pinnedWriteNUnsafe "Please use unsafeCreateOf' instead." #-} {-# INLINE pinnedWriteNUnsafe #-} pinnedWriteNUnsafe :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (Array a) -pinnedWriteNUnsafe = unsafePinnedCreateOf +pinnedWriteNUnsafe = unsafeCreateOf' -- | A version of "create" that let's you pass in the initial capacity of the -- array in terms of the number of elements. @@ -960,14 +971,15 @@ write :: forall m a. (MonadIO m, Unbox a) => Fold m a (Array a) write = create -- | Like 'create' but creates a pinned array. -{-# INLINE pinnedCreate #-} -pinnedCreate :: forall m a. (MonadIO m, Unbox a) => Fold m a (Array a) -pinnedCreate = fmap unsafeFreeze MA.pinnedCreate +{-# INLINE create' #-} +pinnedCreate, create' :: forall m a. (MonadIO m, Unbox a) => Fold m a (Array a) +create' = fmap unsafeFreeze MA.create' +RENAME_PRIME(pinnedCreate,create) -{-# DEPRECATED pinnedWrite "Please use pinnedCreate instead." #-} +{-# DEPRECATED pinnedWrite "Please use create' instead." #-} {-# INLINE pinnedWrite #-} pinnedWrite :: forall m a. (MonadIO m, Unbox a) => Fold m a (Array a) -pinnedWrite = pinnedCreate +pinnedWrite = create' -- | Fold "step" has a dependency on "initial", and each step is dependent on -- the previous invocation of step due to state passing, finally extract diff --git a/core/src/Streamly/Internal/Data/Fold/Combinators.hs b/core/src/Streamly/Internal/Data/Fold/Combinators.hs index a99ba5ef21..fa7e0b849d 100644 --- a/core/src/Streamly/Internal/Data/Fold/Combinators.hs +++ b/core/src/Streamly/Internal/Data/Fold/Combinators.hs @@ -2321,7 +2321,7 @@ bottomBy cmp n = Fold step initial extract extract where initial = do - arr <- MA.pinnedEmptyOf n + arr <- MA.emptyOf' n if n <= 0 then return $ Done arr else return $ Partial (arr, 0) diff --git a/core/src/Streamly/Internal/Data/MutArray/Type.hs b/core/src/Streamly/Internal/Data/MutArray/Type.hs index 8b559a1ae1..eacd60be4a 100644 --- a/core/src/Streamly/Internal/Data/MutArray/Type.hs +++ b/core/src/Streamly/Internal/Data/MutArray/Type.hs @@ -56,13 +56,13 @@ module Streamly.Internal.Data.MutArray.Type -- extend the length without reallocating. , emptyOf , emptyWithAligned - , pinnedEmptyOf + , emptyOf' , pinnedNewAligned -- XXX not required -- , new -- uninitialized array of specified length -- *** Cloning , clone - , pinnedClone + , clone' -- *** Slicing -- | Get a subarray without copying @@ -75,22 +75,22 @@ module Streamly.Internal.Data.MutArray.Type , ArrayUnsafe (..) , unsafeCreateOfWith , unsafeCreateOf - , unsafePinnedCreateOf - , pinnedCreateOf + , unsafeCreateOf' + , createOf' , createWithOf , createOf , revCreateOf - , pinnedCreate + , create' , createWith , create -- , revCreate -- *** From containers , fromListN - , pinnedFromListN + , fromListN' , fromList - , pinnedFromList + , fromList' , fromListRevN , fromListRev , fromStreamN @@ -244,7 +244,7 @@ module Streamly.Internal.Data.MutArray.Type -- *** Chunk -- | Group a stream into arrays. , chunksOf - , pinnedChunksOf -- chunksOf' + , chunksOf' -- chunksOf' -- , timedChunksOf -- see the Streamly.Data.Stream.Prelude module , buildChunks , chunksEndBy @@ -354,6 +354,14 @@ module Streamly.Internal.Data.MutArray.Type , lPinnedCompactGE , lCompactGE , compactGE + , pinnedEmptyOf + , pinnedChunksOf + , pinnedCreateOf + , pinnedCreate + , pinnedFromListN + , pinnedFromList + , pinnedClone + , unsafePinnedCreateOf ) where @@ -518,7 +526,7 @@ pin :: MutArray a -> IO (MutArray a) pin arr@MutArray{..} = if Unboxed.isPinned arrContents then pure arr - else pinnedClone arr + else clone' arr -- | Return a copy of the array in unpinned memory if pinned, else return the -- original array. @@ -614,11 +622,11 @@ newBytesAs ps bytes = do -- The memory of the array is uninitialized and the allocation is aligned as -- per the 'Unboxed' instance of the type. -- --- > pinnedNewBytes = (unsafeCast :: Array Word8 -> a) . pinnedEmptyOf +-- > pinnedNewBytes = (unsafeCast :: Array Word8 -> a) . emptyOf' -- -- /Pre-release/ {-# INLINE pinnedNewBytes #-} -{-# DEPRECATED pinnedNewBytes "Please use pinnedEmptyOf to create a Word8 array and cast it accordingly." #-} +{-# DEPRECATED pinnedNewBytes "Please use emptyOf' to create a Word8 array and cast it accordingly." #-} pinnedNewBytes :: MonadIO m => #ifdef DEVBUILD Unbox a => @@ -630,7 +638,7 @@ pinnedNewBytes = newBytesAs Pinned -- the alignment is dictated by the 'Unboxed' instance of the type. -- -- /Internal/ -{-# DEPRECATED pinnedNewAligned "Please use pinnedEmptyOf to create a Word8 array and cast it accordingly." #-} +{-# DEPRECATED pinnedNewAligned "Please use emptyOf' to create a Word8 array and cast it accordingly." #-} {-# INLINE pinnedNewAligned #-} pinnedNewAligned :: (MonadIO m, Unbox a) => Int -> Int -> m (MutArray a) pinnedNewAligned = emptyWithAligned (\s _ -> liftIO $ Unboxed.pinnedNew s) @@ -646,14 +654,15 @@ newAs ps = -- | Allocates a pinned array of zero length but growable to the specified -- capacity without reallocation. -{-# INLINE pinnedEmptyOf #-} -pinnedEmptyOf :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) -pinnedEmptyOf = newAs Pinned +{-# INLINE emptyOf' #-} +pinnedEmptyOf, emptyOf' :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) +emptyOf' = newAs Pinned +RENAME_PRIME(pinnedEmptyOf,emptyOf) -{-# DEPRECATED pinnedNew "Please use pinnedEmptyOf instead." #-} +{-# DEPRECATED pinnedNew "Please use emptyOf' instead." #-} {-# INLINE pinnedNew #-} pinnedNew :: forall m a. (MonadIO m, Unbox a) => Int -> m (MutArray a) -pinnedNew = pinnedEmptyOf +pinnedNew = emptyOf' -- | Allocates an unpinned array of zero length but growable to the specified -- capacity without reallocation. @@ -926,7 +935,7 @@ reallocExplicitAs ps elemSize newCapacityInBytes MutArray{..} = do } -- XXX We may also need reallocAs to allocate as pinned/unpinned explicitly. In --- fact clone/pinnedClone can be implemented using reallocAs. +-- fact clone/clone' can be implemented using reallocAs. -- | @realloc newCapacity array@ reallocates the array to the specified -- capacity in bytes. @@ -1709,11 +1718,12 @@ chunksOf :: forall m a. (MonadIO m, Unbox a) chunksOf = chunksOfAs Unpinned -- | Like 'chunksOf' but creates pinned arrays. -{-# INLINE_NORMAL pinnedChunksOf #-} -pinnedChunksOf :: forall m a. (MonadIO m, Unbox a) +{-# INLINE_NORMAL chunksOf' #-} +pinnedChunksOf, chunksOf' :: forall m a. (MonadIO m, Unbox a) => Int -> D.Stream m a -> D.Stream m (MutArray a) --- pinnedChunksOf n = D.foldMany (pinnedCreateOf n) -pinnedChunksOf = chunksOfAs Pinned +-- chunksOf' n = D.foldMany (createOf' n) +chunksOf' = chunksOfAs Pinned +RENAME_PRIME(pinnedChunksOf,chunksOf) -- | Create arrays from the input stream using a predicate to find the end of -- the chunk. When the predicate matches, the chunk ends, the matching element @@ -1733,7 +1743,7 @@ chunksEndBy p = D.foldMany (FL.takeEndBy p create) {-# INLINE chunksEndBy' #-} chunksEndBy' :: forall m a. (MonadIO m, Unbox a) => (a -> Bool) -> D.Stream m a -> D.Stream m (MutArray a) -chunksEndBy' p = D.foldMany (FL.takeEndBy p pinnedCreate) +chunksEndBy' p = D.foldMany (FL.takeEndBy p create') -- | Create chunks using newline as the separator, including it. {-# INLINE chunksEndByLn #-} @@ -2239,16 +2249,17 @@ writeNUnsafe :: forall m a. (MonadIO m, Unbox a) writeNUnsafe = unsafeCreateOf -- | Like 'unsafeCreateOf' but creates a pinned array. -{-# INLINE_NORMAL unsafePinnedCreateOf #-} -unsafePinnedCreateOf :: forall m a. (MonadIO m, Unbox a) +{-# INLINE_NORMAL unsafeCreateOf' #-} +unsafePinnedCreateOf, unsafeCreateOf' :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) -unsafePinnedCreateOf = writeNUnsafeAs Pinned +unsafeCreateOf' = writeNUnsafeAs Pinned +RENAME_PRIME(unsafePinnedCreateOf,unsafeCreateOf) -{-# DEPRECATED pinnedWriteNUnsafe "Please use unsafePinnedCreateOf instead." #-} +{-# DEPRECATED pinnedWriteNUnsafe "Please use unsafeCreateOf' instead." #-} {-# INLINE pinnedWriteNUnsafe #-} pinnedWriteNUnsafe :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) -pinnedWriteNUnsafe = unsafePinnedCreateOf +pinnedWriteNUnsafe = unsafeCreateOf' -- | @createWithOf alloc n@ folds a maximum of @n@ elements into an array -- allocated using the @alloc@ function. @@ -2292,20 +2303,21 @@ writeN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) writeN = createOf -- | Like 'createOf' but creates a pinned array. -{-# INLINE_NORMAL pinnedCreateOf #-} -pinnedCreateOf :: +{-# INLINE_NORMAL createOf' #-} +pinnedCreateOf, createOf' :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) -pinnedCreateOf = writeNAs Pinned +createOf' = writeNAs Pinned +RENAME_PRIME(pinnedCreateOf,createOf) -{-# DEPRECATED pinnedWriteN "Please use pinnedCreateOf instead." #-} +{-# DEPRECATED pinnedWriteN "Please use createOf' instead." #-} {-# INLINE pinnedWriteN #-} pinnedWriteN :: forall m a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) -pinnedWriteN = pinnedCreateOf +pinnedWriteN = createOf' -- | Like unsafeCreateOfWith but writes the array in reverse order. -- @@ -2462,15 +2474,16 @@ write :: forall m a. (MonadIO m, Unbox a) => Fold m a (MutArray a) write = create -- | Like 'create' but creates a pinned array. -{-# INLINE pinnedCreate #-} -pinnedCreate :: forall m a. (MonadIO m, Unbox a) => Fold m a (MutArray a) -pinnedCreate = +{-# INLINE create' #-} +pinnedCreate, create' :: forall m a. (MonadIO m, Unbox a) => Fold m a (MutArray a) +create' = writeWithAs Pinned (allocBytesToElemCount (undefined :: a) arrayChunkBytes) +RENAME_PRIME(pinnedCreate,create) -{-# DEPRECATED pinnedWrite "Please use pinnedCreate instead." #-} +{-# DEPRECATED pinnedWrite "Please use create' instead." #-} {-# INLINE pinnedWrite #-} pinnedWrite :: forall m a. (MonadIO m, Unbox a) => Fold m a (MutArray a) -pinnedWrite = pinnedCreate +pinnedWrite = create' ------------------------------------------------------------------------------- -- construct from streams, known size @@ -2515,9 +2528,10 @@ fromListN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a) fromListN n xs = fromStreamDN n $ D.fromList xs -- | Like 'fromListN' but creates a pinned array. -{-# INLINABLE pinnedFromListN #-} -pinnedFromListN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a) -pinnedFromListN n xs = fromStreamDNAs Pinned n $ D.fromList xs +{-# INLINABLE fromListN' #-} +pinnedFromListN, fromListN' :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a) +fromListN' n xs = fromStreamDNAs Pinned n $ D.fromList xs +RENAME_PRIME(pinnedFromListN,fromListN) -- | Like fromListN but writes the array in reverse order. -- @@ -2711,9 +2725,10 @@ fromList :: (MonadIO m, Unbox a) => [a] -> m (MutArray a) fromList xs = fromStreamD $ D.fromList xs -- | Like 'fromList' but creates a pinned array. -{-# INLINE pinnedFromList #-} -pinnedFromList :: (MonadIO m, Unbox a) => [a] -> m (MutArray a) -pinnedFromList xs = fromStreamDAs Pinned $ D.fromList xs +{-# INLINE fromList' #-} +pinnedFromList, fromList' :: (MonadIO m, Unbox a) => [a] -> m (MutArray a) +fromList' xs = fromStreamDAs Pinned $ D.fromList xs +RENAME_PRIME(pinnedFromList,fromList) -- XXX We are materializing the whole list first for getting the length. Check -- if the 'fromList' like chunked implementation would fare better. @@ -2752,7 +2767,7 @@ cloneAs ps src = -- To clone a slice of "MutArray" you can create a slice with "unsafeGetSlice" -- and then use "clone". -- --- The new "MutArray" is unpinned in nature. Use "pinnedClone" to clone the +-- The new "MutArray" is unpinned in nature. Use "clone'" to clone the -- MutArray in pinned memory. {-# INLINE clone #-} clone :: @@ -2765,15 +2780,16 @@ clone :: clone = cloneAs Unpinned -- Similar to "clone" but uses pinned memory. -{-# INLINE pinnedClone #-} -pinnedClone :: +{-# INLINE clone' #-} +pinnedClone, clone' :: ( MonadIO m #ifdef DEVBUILD , Unbox a #endif ) => MutArray a -> m (MutArray a) -pinnedClone = cloneAs Pinned +clone' = cloneAs Pinned +RENAME_PRIME(pinnedClone,clone) ------------------------------------------------------------------------------- -- Combining @@ -3043,7 +3059,7 @@ unsafeAsPtr arr f = unsafePinnedCreateUsingPtr :: MonadIO m => Int -> (Ptr Word8 -> m Int) -> m (MutArray Word8) unsafePinnedCreateUsingPtr cap pop = do - (arr :: MutArray Word8) <- pinnedEmptyOf cap + (arr :: MutArray Word8) <- emptyOf' cap len <- Unboxed.unsafeAsPtr (arrContents arr) pop when (len > cap) (error (errMsg len)) -- arrStart == 0 diff --git a/core/src/Streamly/Internal/Data/Scanl/Combinators.hs b/core/src/Streamly/Internal/Data/Scanl/Combinators.hs index 680e00f965..ee700e561d 100644 --- a/core/src/Streamly/Internal/Data/Scanl/Combinators.hs +++ b/core/src/Streamly/Internal/Data/Scanl/Combinators.hs @@ -2220,7 +2220,7 @@ bottomBy cmp n = Scanl step initial extract extract where initial = do - arr <- MA.pinnedEmptyOf n + arr <- MA.emptyOf' n if n <= 0 then return $ Done arr else return $ Partial (arr, 0) diff --git a/core/src/Streamly/Internal/FileSystem/File.hs b/core/src/Streamly/Internal/FileSystem/File.hs index 791577c649..7cb7981b7a 100644 --- a/core/src/Streamly/Internal/FileSystem/File.hs +++ b/core/src/Streamly/Internal/FileSystem/File.hs @@ -113,7 +113,7 @@ import Streamly.Internal.System.IO (defaultChunkSize) import qualified Streamly.Internal.Data.Array as A import qualified Streamly.Data.Stream as S import qualified Streamly.Data.Unfold as UF -import qualified Streamly.Internal.Data.Array.Type as IA (pinnedChunksOf) +import qualified Streamly.Internal.Data.Array.Type as IA (chunksOf') import qualified Streamly.Internal.Data.Unfold as UF (bracketIO) import qualified Streamly.Internal.Data.Fold.Type as FL (Step(..), snoc, reduce) @@ -400,7 +400,7 @@ fromChunks = fromChunksMode WriteMode {-# INLINE fromBytesWith #-} fromBytesWith :: (MonadIO m, MonadCatch m) => Int -> FilePath -> Stream m Word8 -> m () -fromBytesWith n file xs = fromChunks file $ IA.pinnedChunksOf n xs +fromBytesWith n file xs = fromChunks file $ IA.chunksOf' n xs {-# DEPRECATED fromBytesWithBufferOf "Please use 'fromBytesWith' instead" #-} {-# INLINE fromBytesWithBufferOf #-} @@ -462,7 +462,7 @@ writeChunks path = Fold step initial extract final writeWith :: (MonadIO m, MonadCatch m) => Int -> FilePath -> Fold m Word8 () writeWith n path = - groupsOf n (A.unsafePinnedCreateOf n) (writeChunks path) + groupsOf n (A.unsafeCreateOf' n) (writeChunks path) {-# DEPRECATED writeWithBufferOf "Please use 'writeWith' instead" #-} {-# INLINE writeWithBufferOf #-} @@ -501,7 +501,7 @@ writeAppendChunks = fromChunksMode AppendMode writeAppendWith :: (MonadIO m, MonadCatch m) => Int -> FilePath -> Stream m Word8 -> m () writeAppendWith n file xs = - writeAppendChunks file $ IA.pinnedChunksOf n xs + writeAppendChunks file $ IA.chunksOf' n xs -- | Append a byte stream to a file. Combines the bytes in chunks of size up to -- 'A.defaultChunkSize' before writing. If the file exists then the new data diff --git a/core/src/Streamly/Internal/FileSystem/Handle.hs b/core/src/Streamly/Internal/FileSystem/Handle.hs index 899a7d8e4c..2533689ca9 100644 --- a/core/src/Streamly/Internal/FileSystem/Handle.hs +++ b/core/src/Streamly/Internal/FileSystem/Handle.hs @@ -417,7 +417,7 @@ putChunksWith n h xs = putChunks h $ A.compactMax n xs -- {-# INLINE putBytesWith #-} putBytesWith :: MonadIO m => Int -> Handle -> Stream m Word8 -> m () -putBytesWith n h m = putChunks h $ A.pinnedChunksOf n m +putBytesWith n h m = putChunks h $ A.chunksOf' n m -- | Write a byte stream to a file handle. Accumulates the input in chunks of -- up to 'Streamly.Internal.Data.Array.Type.defaultChunkSize' before writing. @@ -487,7 +487,7 @@ writeChunksWithBufferOf = writeChunksWith -- {-# INLINE writeWith #-} writeWith :: MonadIO m => Int -> Handle -> Fold m Word8 () -writeWith n h = FL.groupsOf n (A.unsafePinnedCreateOf n) (writeChunks h) +writeWith n h = FL.groupsOf n (A.unsafeCreateOf' n) (writeChunks h) -- | Same as 'writeWith' -- @@ -505,7 +505,7 @@ writeWithBufferOf = writeWith writeMaybesWith :: (MonadIO m ) => Int -> Handle -> Fold m (Maybe Word8) () writeMaybesWith n h = - let writeNJusts = FL.lmap fromJust $ A.pinnedCreateOf n + let writeNJusts = FL.lmap fromJust $ A.createOf' n writeOnNothing = FL.takeEndBy_ isNothing writeNJusts in FL.many writeOnNothing (writeChunks h) @@ -515,7 +515,7 @@ writeMaybesWith n h = {-# INLINE writerWith #-} writerWith :: MonadIO m => Int -> Refold m Handle Word8 () writerWith n = - FL.refoldMany (FL.take n $ A.unsafePinnedCreateOf n) chunkWriter + FL.refoldMany (FL.take n $ A.unsafeCreateOf' n) chunkWriter -- | Write a byte stream to a file handle. Accumulates the input in chunks of -- up to 'Streamly.Internal.Data.Array.Type.defaultChunkSize' before writing diff --git a/core/src/deprecation.h b/core/src/deprecation.h index b7c1b9aefb..afd0dc48de 100644 --- a/core/src/deprecation.h +++ b/core/src/deprecation.h @@ -1,4 +1,9 @@ -#define RENAME(_old, _new) \ +#define RENAME(_old, _new) \ {-# DEPRECATED _old "Please use _new instead." #-}; \ {-# INLINE _old #-}; \ _old = _new + +#define RENAME_PRIME(_old, _new) \ +{-# DEPRECATED _old "Please use _new' instead." #-}; \ +{-# INLINE _old #-}; \ +_old = _new' diff --git a/src/Streamly/Internal/Data/Stream/Time.hs b/src/Streamly/Internal/Data/Stream/Time.hs index 5c33c5ef0e..d699fca014 100644 --- a/src/Streamly/Internal/Data/Stream/Time.hs +++ b/src/Streamly/Internal/Data/Stream/Time.hs @@ -313,7 +313,7 @@ timedChunksOf timeout n = timedGroupsOf timeout n (Array.unsafeCreateOf n) timedChunksOf' :: (MonadAsync m, Unbox a) => Double -> Int -> Stream m a -> Stream m (Array a) timedChunksOf' timeout n = - timedGroupsOf timeout n (Array.unsafePinnedCreateOf n) + timedGroupsOf timeout n (Array.unsafeCreateOf' n) ------------------------------------------------------------------------------ -- Windowed classification diff --git a/src/Streamly/Internal/Network/Inet/TCP.hs b/src/Streamly/Internal/Network/Inet/TCP.hs index 107dad4939..e55f014f37 100644 --- a/src/Streamly/Internal/Network/Inet/TCP.hs +++ b/src/Streamly/Internal/Network/Inet/TCP.hs @@ -133,7 +133,7 @@ import qualified Streamly.Data.Fold as FL import qualified Streamly.Data.Stream as S import qualified Streamly.Data.Unfold as UF import qualified Streamly.Internal.Data.Array as A - (pinnedChunksOf, unsafePinnedCreateOf) + (chunksOf', unsafeCreateOf') import qualified Streamly.Internal.Data.Unfold as UF (bracketIO) import qualified Streamly.Internal.Data.Fold as FL (Step(..), reduce) @@ -422,7 +422,7 @@ putBytesWithBufferOf -> Stream m Word8 -> m () putBytesWithBufferOf n addr port m = - putChunks addr port $ A.pinnedChunksOf n m + putChunks addr port $ A.chunksOf' n m -- | Like 'write' but provides control over the write buffer. Output will -- be written to the IO device as soon as we collect the specified number of @@ -436,7 +436,7 @@ writeWithBufferOf -> PortNumber -> Fold m Word8 () writeWithBufferOf n addr port = - FL.groupsOf n (A.unsafePinnedCreateOf n) (writeChunks addr port) + FL.groupsOf n (A.unsafeCreateOf' n) (writeChunks addr port) -- | Write a stream to the supplied IPv4 host address and port number. -- diff --git a/src/Streamly/Internal/Network/Socket.hs b/src/Streamly/Internal/Network/Socket.hs index cb621d9a89..f2b1683eb3 100644 --- a/src/Streamly/Internal/Network/Socket.hs +++ b/src/Streamly/Internal/Network/Socket.hs @@ -98,8 +98,8 @@ import qualified Streamly.Data.Fold as FL import qualified Streamly.Data.Stream as S import qualified Streamly.Data.Unfold as UF import qualified Streamly.Internal.Data.Array as A - ( unsafeFreeze, unsafePinnedAsPtr, pinnedChunksOf, - pinnedCreateOf, unsafePinnedCreateOf, scanCompactMin ) + ( unsafeFreeze, unsafePinnedAsPtr, chunksOf', + createOf', unsafeCreateOf, scanCompactMin ) import qualified Streamly.Internal.Data.MutArray as MArray (unsafePinnedCreateUsingPtr) import qualified Streamly.Internal.Data.Stream as S (fromStreamK, Stream(..), Step(..)) @@ -492,14 +492,14 @@ writeChunksWithBufferOf = writeChunksWith -- {-# INLINE putBytesWith #-} putBytesWith :: MonadIO m => Int -> Socket -> Stream m Word8 -> m () -putBytesWith n h m = putChunks h $ A.pinnedChunksOf n m +putBytesWith n h m = putChunks h $ A.chunksOf' n m -- | Write a byte stream to a socket. Accumulates the input in chunks of -- specified number of bytes before writing. -- {-# INLINE writeWith #-} writeWith :: MonadIO m => Int -> Socket -> Fold m Word8 () -writeWith n h = FL.groupsOf n (A.unsafePinnedCreateOf n) (writeChunks h) +writeWith n h = FL.groupsOf n (A.unsafeCreateOf n) (writeChunks h) -- | Same as 'writeWith' -- @@ -517,7 +517,7 @@ writeWithBufferOf = writeWith writeMaybesWith :: (MonadIO m ) => Int -> Socket -> Fold m (Maybe Word8) () writeMaybesWith n h = - let writeNJusts = FL.lmap fromJust $ A.pinnedCreateOf n + let writeNJusts = FL.lmap fromJust $ A.createOf' n writeOnNothing = FL.takeEndBy_ isNothing writeNJusts in FL.many writeOnNothing (writeChunks h) diff --git a/test/Streamly/Test/Data/Array.hs b/test/Streamly/Test/Data/Array.hs index b50758eedd..5f72193188 100644 --- a/test/Streamly/Test/Data/Array.hs +++ b/test/Streamly/Test/Data/Array.hs @@ -152,7 +152,7 @@ testBubbleWith asc = else MA.bubble (flip compare) arr return arr ) - (MA.pinnedEmptyOf $ length ls) + (MA.emptyOf' $ length ls) testBubbleAsc :: Property testBubbleAsc = testBubbleWith True @@ -162,7 +162,7 @@ testBubbleDesc = testBubbleWith False testByteLengthWithMA :: forall a. Unbox a => a -> IO () testByteLengthWithMA _ = do - arrA <- MA.pinnedEmptyOf 100 :: IO (MutArray a) + arrA <- MA.emptyOf' 100 :: IO (MutArray a) let arrW8 = MA.unsafeCast arrA :: MutArray Word8 MA.byteLength arrA `shouldBe` MA.length arrW8 diff --git a/test/Streamly/Test/Data/MutArray.hs b/test/Streamly/Test/Data/MutArray.hs index 5a555de4ae..b91463bc79 100644 --- a/test/Streamly/Test/Data/MutArray.hs +++ b/test/Streamly/Test/Data/MutArray.hs @@ -42,7 +42,7 @@ testAppend = action ls = do x <- Stream.fold - (MArray.append (MArray.pinnedEmptyOf 0)) + (MArray.append (MArray.emptyOf' 0)) (Stream.fromList (ls::[Int])) lst <- MArray.toList x assert (ls == lst) diff --git a/test/Streamly/Test/Data/Serialize.hs b/test/Streamly/Test/Data/Serialize.hs index dac4c8514f..4d4e786926 100644 --- a/test/Streamly/Test/Data/Serialize.hs +++ b/test/Streamly/Test/Data/Serialize.hs @@ -223,7 +223,7 @@ roundtrip val = do -- let sz = Serialize.addSizeTo 0 val -- putStrLn $ "Size is: " ++ show sz - val `shouldBe` fst (Array.deserialize (Array.pinnedSerialize val)) + val `shouldBe` fst (Array.deserialize (Array.serialize' val)) res <- poke val peekAndVerify res val