Deprecate witeLastN & introduce createLastOf in Array.(Generic)

This commit is contained in:
Adithya Kumar 2024-07-16 18:03:25 +05:30
parent e80f61287d
commit c247365972
10 changed files with 41 additions and 34 deletions

View File

@ -98,10 +98,10 @@ o_1_space_elimination :: Int -> [Benchmark]
o_1_space_elimination value =
[ bgroup "elimination"
[ benchPureSink value "length . IsList.toList" (length . GHC.toList)
, benchFold "writeLastN.1"
(S.fold (IA.writeLastN 1)) (P.sourceUnfoldrM value)
, benchFold "writeLastN.10"
(S.fold (IA.writeLastN 10)) (P.sourceUnfoldrM value)
, benchFold "createLastOf.1"
(S.fold (IA.createLastOf 1)) (P.sourceUnfoldrM value)
, benchFold "createLastOf.10"
(S.fold (IA.createLastOf 10)) (P.sourceUnfoldrM value)
#ifdef DEVBUILD
{-
benchPureSink value "foldable/foldl'" foldableFoldl'
@ -116,7 +116,7 @@ o_n_heap_serial value =
[ bgroup "elimination"
[
-- Converting the stream to an array
benchFold "writeLastN.Max" (S.fold (IA.writeLastN (value + 1)))
benchFold "createLastOf.Max" (S.fold (IA.createLastOf (value + 1)))
(P.sourceUnfoldrM value)
]
]

View File

@ -77,10 +77,10 @@ o_1_space_generation value =
o_1_space_elimination :: Int -> [Benchmark]
o_1_space_elimination value =
[ bgroup "elimination"
[ benchFold "writeLastN.1"
(S.fold (IA.writeLastN 1)) (P.sourceUnfoldrM value)
, benchFold "writeLastN.10"
(S.fold (IA.writeLastN 10)) (P.sourceUnfoldrM value)
[ benchFold "createLastOf.1"
(S.fold (IA.createLastOf 1)) (P.sourceUnfoldrM value)
, benchFold "createLastOf.10"
(S.fold (IA.createLastOf 10)) (P.sourceUnfoldrM value)
#ifdef DEVBUILD
{-
benchPureSink value "foldable/foldl'" foldableFoldl'
@ -95,7 +95,7 @@ o_n_heap_serial value =
[ bgroup "elimination"
[
-- Converting the stream to an array
benchFold "writeLastN.Max" (S.fold (IA.writeLastN (value + 1)))
benchFold "createLastOf.Max" (S.fold (IA.createLastOf (value + 1)))
(P.sourceUnfoldrM value)
]
]

View File

@ -55,7 +55,7 @@ module Streamly.Data.Array
-- ** From Stream
, createOf
, create
, writeLastN -- drop old (ring buffer)
, createLastOf -- drop old (ring buffer)
-- ** From List
, fromListN
@ -94,6 +94,7 @@ module Streamly.Data.Array
-- * Deprecated
, writeN -- drop new
, write -- full buffer
, writeLastN
)
where

View File

@ -40,7 +40,7 @@ module Streamly.Data.MutArray
, fromList
, createOf
, create
-- writeLastN
-- createLastOf
-- * Pinning & Unpinning
, pin

View File

@ -20,7 +20,7 @@ module Streamly.Internal.Data.Array
-- * Construction
-- Monadic Folds
, writeLastN
, createLastOf
-- * Random Access
-- , (!!)
@ -94,6 +94,7 @@ module Streamly.Internal.Data.Array
, genSlicesFromLen
, getSlicesFromLen
, getIndices
, writeLastN
)
where
@ -206,13 +207,13 @@ last = getIndexRev 0
-- XXX We should generate this from Ring.
-- | @writeLastN n@ folds a maximum of @n@ elements from the end of the input
-- | @createLastOf n@ folds a maximum of @n@ elements from the end of the input
-- stream to an 'Array'.
--
{-# INLINE writeLastN #-}
writeLastN ::
{-# INLINE createLastOf #-}
createLastOf ::
(Unbox a, MonadIO m) => Int -> Fold m a (Array a)
writeLastN n
createLastOf n
| n <= 0 = fmap (const mempty) FL.drain
| otherwise = unsafeFreeze <$> Fold step initial done done
@ -235,6 +236,11 @@ writeLastN n
| i < n = RB.unsafeFoldRingM
| otherwise = RB.unsafeFoldRingFullM
{-# DEPRECATED writeLastN "Please use createLastOf instead." #-}
{-# INLINE writeLastN #-}
writeLastN :: (Unbox a, MonadIO m) => Int -> Fold m a (Array a)
writeLastN = createLastOf
-------------------------------------------------------------------------------
-- Random Access
-------------------------------------------------------------------------------

View File

@ -14,7 +14,7 @@ module Streamly.Internal.Data.Array.Generic
, createOf
, create
, writeWith
, writeLastN
, createLastOf
, fromStreamN
, fromStream
@ -267,14 +267,14 @@ getIndex i arr@Array {..} =
-- >>> import Data.Function ((&))
-- >>> :{
-- Stream.fromList [1,2,3,4,5::Int]
-- & Stream.scan (Array.writeLastN 2)
-- & Stream.scan (Array.createLastOf 2)
-- & Stream.fold Fold.toList
-- :}
-- [fromList [],fromList [1],fromList [1,2],fromList [2,3],fromList [3,4],fromList [4,5]]
--
{-# INLINE writeLastN #-}
writeLastN :: MonadIO m => Int -> Fold m a (Array a)
writeLastN n = FL.rmapM f (RB.writeLastN n)
{-# INLINE createLastOf #-}
createLastOf :: MonadIO m => Int -> Fold m a (Array a)
createLastOf n = FL.rmapM f (RB.createLastOf n)
where

View File

@ -152,7 +152,7 @@ advance rb ringHead =
moveBy :: Int -> Ring a -> Int -> Int
moveBy by rb ringHead = (ringHead + by) `mod1` ringCapacity rb
-- XXX Move the writeLastN from array module here.
-- XXX Move the createLastOf from array module here.
--
-- | @writeN n@ is a rolling fold that keeps the last n elements of the stream
-- in a ring array.

View File

@ -200,7 +200,7 @@ specialize in the last phase, inlining in the last phase is left to
the compiler. `INLINE [0]` may sound the same as `NOINLINE [0]`,
however, it behaves differently because we ask the compiler to INLINE
it compulsorily and it may not give us the desired results. The
Data.Fold.writeLastN benchmark is one such case where `NOINLINE [0]`
Data.Fold.createLastOf benchmark is one such case where `NOINLINE [0]`
provides much better performance than `INLINE [0]`.
### NoSpecConstr

View File

@ -79,13 +79,13 @@ $(mkZippingType "ZipConcurrent" "app" True)
## Sliding Window
The `writeLastN` fold can be used to create a stream of sliding windows.
The `createLastOf` fold can be used to create a stream of sliding windows.
```haskell docspec
>>> import qualified Streamly.Data.Array as Array
>>> :{
Stream.fromList [1,2,3,4,5::Int]
& Stream.scan (Array.writeLastN 2)
& Stream.scan (Array.createLastOf 2)
& Stream.fold Fold.toList
:}
[fromList [],fromList [1],fromList [1,2],fromList [2,3],fromList [3,4],fromList [4,5]]

View File

@ -67,14 +67,14 @@ testLastN =
monadicIO $ do
xs <- run
$ fmap A.toList
$ S.fold (A.writeLastN n)
$ S.fold (A.createLastOf n)
$ S.fromList list
assert (xs == lastN n list)
testLastN_LN :: Int -> Int -> IO Bool
testLastN_LN len n = do
let list = [1..len]
l1 <- fmap A.toList $ S.fold (A.writeLastN n) $ S.fromList list
l1 <- fmap A.toList $ S.fold (A.createLastOf n) $ S.fromList list
let l2 = lastN n list
return $ l1 == l2
@ -239,12 +239,12 @@ main =
it "middle" (unsafeWriteIndex [1..10] 5 0 `shouldReturn` True)
it "last" (unsafeWriteIndex [1..10] 9 0 `shouldReturn` True)
describe "Fold" $ do
prop "writeLastN : 0 <= n <= len" testLastN
describe "writeLastN boundary conditions" $ do
it "writeLastN -1" (testLastN_LN 10 (-1) `shouldReturn` True)
it "writeLastN 0" (testLastN_LN 10 0 `shouldReturn` True)
it "writeLastN length" (testLastN_LN 10 10 `shouldReturn` True)
it "writeLastN (length + 1)" (testLastN_LN 10 11 `shouldReturn` True)
prop "createLastOf : 0 <= n <= len" testLastN
describe "createLastOf boundary conditions" $ do
it "createLastOf -1" (testLastN_LN 10 (-1) `shouldReturn` True)
it "createLastOf 0" (testLastN_LN 10 0 `shouldReturn` True)
it "createLastOf length" (testLastN_LN 10 10 `shouldReturn` True)
it "createLastOf (length + 1)" (testLastN_LN 10 11 `shouldReturn` True)
describe "Strip" $ do
it "strip" (testStrip `shouldReturn` True)
it "stripLeft" (testStripLeft `shouldReturn` True)