@@ -281,6 +281,7 @@ module Streamly.Internal.Data.MutArray.Type
281281 , snoc
282282 , snocGrowBy
283283 , snocMay
284+ , snoc1KB
284285 , unsafeSnoc
285286
286287 -- , revSnoc -- cons
@@ -496,12 +497,12 @@ module Streamly.Internal.Data.MutArray.Type
496497 , splitOn
497498 , pinnedNewAligned
498499 , unsafePinnedAsPtr
499- , grow -- XXX to be deprecated
500- , createWith -- XXX to be deprecated
501- , snocLinear -- XXX deprecate, replace by snocGrowBy or rename snoc1KB
502- , unsafeAppendN -- XXX deprecate, replaced by unsafeAppendMax
503- , appendN -- XXX deprecate, replaced by appendMax
504- , append -- XXX deprecate, replaced by append2
500+ , grow
501+ , createWith
502+ , snocLinear
503+ , unsafeAppendN
504+ , appendN
505+ , append
505506 )
506507where
507508
@@ -1151,8 +1152,7 @@ growTo nElems arr@MutArray{..} = do
11511152 then return arr
11521153 else realloc req arr
11531154
1154- {-# INLINE grow #-}
1155- grow = growTo
1155+ RENAME (grow,growTo)
11561156
11571157-- | Like 'growTo' but specifies the required reserve (unused) capacity rather
11581158-- than the total capacity. Increases the reserve capacity, if required, to at
@@ -1334,9 +1334,10 @@ snocWith sizer arr x = do
13341334-- Performs O(n^2) copies to grow but is thrifty on memory.
13351335--
13361336-- /Pre-release/
1337- {-# INLINE snocLinear #-}
1338- snocLinear :: forall m a . (MonadIO m , Unbox a ) => MutArray a -> a -> m (MutArray a )
1339- snocLinear = snocWith (+ allocBytesToBytes (undefined :: a ) arrayChunkBytes)
1337+ {-# INLINE snoc1KB #-}
1338+ snocLinear , snoc1KB :: forall m a . (MonadIO m , Unbox a ) => MutArray a -> a -> m (MutArray a )
1339+ snoc1KB = snocWith (+ allocBytesToBytes (undefined :: a ) arrayChunkBytes)
1340+ RENAME (snocLinear,snoc1KB)
13401341
13411342-- | The array is mutated to append an additional element to it.
13421343--
@@ -2351,6 +2352,7 @@ foldRev f arr = D.fold f (readRev arr)
23512352-- Any free space left in the array after appending @n@ elements is lost.
23522353--
23532354-- /Internal/
2355+ {-# DEPRECATED unsafeAppendN "Please use unsafeAppendMax instead." #-}
23542356{-# INLINE_NORMAL unsafeAppendN #-}
23552357unsafeAppendN :: forall m a . (MonadIO m , Unbox a ) =>
23562358 Int
@@ -2428,6 +2430,7 @@ writeAppendNUnsafe = unsafeAppendN
24282430--
24292431-- >>> appendN n initial = Fold.take n (MutArray.unsafeAppendN n initial)
24302432--
2433+ {-# DEPRECATED appendN "Please use appendMax instead." #-}
24312434{-# INLINE_NORMAL appendN #-}
24322435appendN :: forall m a . (MonadIO m , Unbox a ) =>
24332436 Int -> m (MutArray a ) -> Fold m a (MutArray a )
@@ -2481,6 +2484,7 @@ writeAppendWith = appendWith
24812484--
24822485-- >>> append = Fold.foldlM' MutArray.snoc
24832486--
2487+ {-# DEPRECATED append "Please use append2 instead." #-}
24842488{-# INLINE append #-}
24852489append :: forall m a . (MonadIO m , Unbox a ) =>
24862490 m (MutArray a ) -> Fold m a (MutArray a )
@@ -2824,7 +2828,7 @@ createMinOf, createWith :: forall m a. (MonadIO m, Unbox a)
28242828-- createWith n = FL.rmapM rightSize $ appendWith (* 2) (emptyOf n)
28252829createMinOf = writeWithAs Unpinned
28262830
2827- createWith = createMinOf
2831+ RENAME ( createWith, createMinOf)
28282832
28292833{-# DEPRECATED writeWith "Please use createMinOf instead." #-}
28302834{-# INLINE writeWith #-}
0 commit comments