Add window prefix to combinators in Fold.Window module (#2517)

This commit is contained in:
Ranjeet Ranjan 2023-08-11 01:15:43 +05:30 committed by Harendra Kumar
parent 8b55b1a03e
commit 96eebafafe
8 changed files with 101 additions and 104 deletions

View File

@ -8,8 +8,8 @@ import Streamly.Internal.Data.Stream (Stream)
import System.Random (randomRIO)
import qualified Streamly.Data.Fold as Fold
import qualified Streamly.Internal.Data.Fold as Window
import qualified Streamly.Internal.Data.Ring as Ring
import qualified Streamly.Internal.Data.Fold.Window as Window
import qualified Streamly.Internal.Data.Stream as Stream
import Streamly.Benchmark.Common
@ -70,55 +70,55 @@ o_1_space_folds :: Int -> [Benchmark]
o_1_space_folds numElements =
[ bgroup "fold"
[ benchWithFold numElements "minimum (window size 100)"
(Window.minimum 100)
(Window.windowMinimum 100)
, benchWithFold numElements "minimum (window size 1000)"
(Window.minimum 1000)
(Window.windowMinimum 1000)
, benchWith sourceDescendingInt numElements
"minimum descending (window size 1000)"
(Window.minimum 1000)
(Window.windowMinimum 1000)
, benchWithFold numElements "maximum (window size 100)"
(Window.maximum 100)
(Window.windowMaximum 100)
, benchWithFold numElements "maximum (window size 1000)"
(Window.maximum 1000)
(Window.windowMaximum 1000)
, benchWith sourceDescendingInt numElements
"maximum descending (window size 1000)"
(Window.maximum 1000)
(Window.windowMaximum 1000)
, benchWithFold numElements "range (window size 100)"
(Window.range 100)
(Window.windowRange 100)
, benchWithFold numElements "range (window size 1000)"
(Window.range 1000)
(Window.windowRange 1000)
, benchWith sourceDescendingInt numElements
"range descending (window size 1000)"
(Window.range 1000)
(Window.windowRange 1000)
, benchWithFoldInt numElements "sumInt (window size 100)"
(Ring.slidingWindow 100 Window.sumInt)
(Ring.slidingWindow 100 Window.windowSumInt)
, benchWithFoldInt numElements "sum for Int (window size 100)"
(Ring.slidingWindow 100 Window.sum)
(Ring.slidingWindow 100 Window.windowSum)
, benchWithFold numElements "sum (window size 100)"
(Ring.slidingWindow 100 Window.sum)
(Ring.slidingWindow 100 Window.windowSum)
, benchWithFold numElements "sum (window size 1000)"
(Ring.slidingWindow 1000 Window.sum)
(Ring.slidingWindow 1000 Window.windowSum)
, benchWithFold numElements "sum (entire stream)"
(Window.cumulative Window.sum)
(Window.cumulative Window.windowSum)
, benchWithFold numElements "sum (Data.Fold)"
Fold.sum
, benchWithFold numElements "mean (window size 100)"
(Ring.slidingWindow 100 Window.mean)
(Ring.slidingWindow 100 Window.windowMean)
, benchWithFold numElements "mean (window size 1000)"
(Ring.slidingWindow 1000 Window.mean)
(Ring.slidingWindow 1000 Window.windowMean)
, benchWithFold numElements "mean (entire stream)"
(Window.cumulative Window.mean)
(Window.cumulative Window.windowMean)
, benchWithFold numElements "mean (Data.Fold)"
Fold.mean
, benchWithFold numElements "powerSum 2 (window size 100)"
(Ring.slidingWindow 100 (Window.powerSum 2))
(Ring.slidingWindow 100 (Window.windowPowerSum 2))
, benchWithFold numElements "powerSum 2 (entire stream)"
(Window.cumulative (Window.powerSum 2))
(Window.cumulative (Window.windowPowerSum 2))
]
]
@ -127,51 +127,51 @@ o_1_space_scans :: Int -> [Benchmark]
o_1_space_scans numElements =
[ bgroup "scan"
[ benchWithPostscan numElements "minimum (window size 10)"
(Window.minimum 10)
(Window.windowMinimum 10)
-- Below window size 30 the linear search based impl performs better
-- than the dequeue based implementation.
, benchWithPostscan numElements "minimum (window size 30)"
(Window.minimum 30)
(Window.windowMinimum 30)
, benchWithPostscan numElements "minimum (window size 1000)"
(Window.minimum 1000)
(Window.windowMinimum 1000)
, benchScanWith sourceDescendingInt numElements
"minimum descending (window size 1000)"
(Window.minimum 1000)
(Window.windowMinimum 1000)
, benchWithPostscan numElements "maximum (window size 10)"
(Window.maximum 10)
(Window.windowMaximum 10)
, benchWithPostscan numElements "maximum (window size 30)"
(Window.maximum 30)
(Window.windowMaximum 30)
, benchWithPostscan numElements "maximum (window size 1000)"
(Window.maximum 1000)
(Window.windowMaximum 1000)
, benchScanWith sourceDescendingInt numElements
"maximum descending (window size 1000)"
(Window.maximum 1000)
(Window.windowMaximum 1000)
, benchWithPostscan numElements "range (window size 10)"
(Window.range 10)
(Window.windowRange 10)
, benchWithPostscan numElements "range (window size 30)"
(Window.range 30)
(Window.windowRange 30)
, benchWithPostscan numElements "range (window size 1000)"
(Window.range 1000)
(Window.windowRange 1000)
, benchScanWith sourceDescendingInt numElements
"range descending (window size 1000)"
(Window.range 1000)
(Window.windowRange 1000)
, benchWithPostscan numElements "sum (window size 100)"
(Ring.slidingWindow 100 Window.sum)
(Ring.slidingWindow 100 Window.windowSum)
, benchWithPostscan numElements "sum (window size 1000)"
(Ring.slidingWindow 1000 Window.sum)
(Ring.slidingWindow 1000 Window.windowSum)
, benchWithPostscan numElements "mean (window size 100)"
(Ring.slidingWindow 100 Window.mean)
(Ring.slidingWindow 100 Window.windowMean)
, benchWithPostscan numElements "mean (window size 1000)"
(Ring.slidingWindow 1000 Window.mean)
(Ring.slidingWindow 1000 Window.windowMean)
, benchWithPostscan numElements "powerSum 2 (window size 100)"
(Ring.slidingWindow 100 (Window.powerSum 2))
(Ring.slidingWindow 100 (Window.windowPowerSum 2))
, benchWithPostscan numElements "powerSum 2 (window size 1000)"
(Ring.slidingWindow 1000 (Window.powerSum 2))
(Ring.slidingWindow 1000 (Window.windowPowerSum 2))
]
]

View File

@ -24,5 +24,4 @@
For APIs that have not been released yet.
>>> import qualified Streamly.Internal.Data.Fold as Fold
>>> import qualified Streamly.Internal.Data.Fold.Window as FoldW
-}

View File

@ -30,7 +30,6 @@
For APIs that have not been released yet.
>>> import qualified Streamly.Internal.Data.Fold as Fold
>>> import qualified Streamly.Internal.Data.Fold.Window as Window
>>> import qualified Streamly.Internal.Data.Parser as Parser
>>> import qualified Streamly.Internal.Data.Stream as Stream
>>> import qualified Streamly.Internal.Data.Unfold as Unfold

View File

@ -20,7 +20,7 @@ module Streamly.Internal.Data.Fold
, module Streamly.Internal.Data.Fold.Tee
, module Streamly.Internal.Data.Fold.Combinators
, module Streamly.Internal.Data.Fold.Container
-- , module Streamly.Internal.Data.Fold.Window
, module Streamly.Internal.Data.Fold.Window
)
where
@ -28,6 +28,6 @@ import Streamly.Internal.Data.Fold.Combinators
import Streamly.Internal.Data.Fold.Container
import Streamly.Internal.Data.Fold.Tee
import Streamly.Internal.Data.Fold.Type
-- import Streamly.Internal.Data.Fold.Window
import Streamly.Internal.Data.Fold.Window
#include "DocTestDataFold.hs"

View File

@ -245,7 +245,7 @@ import Streamly.Internal.Data.Stream.StreamD.Type (Stream)
import qualified Prelude
import qualified Streamly.Internal.Data.MutArray.Type as MA
import qualified Streamly.Internal.Data.Array.Type as Array
import qualified Streamly.Internal.Data.Fold.Window as FoldW
import qualified Streamly.Internal.Data.Fold.Window as Fold
import qualified Streamly.Internal.Data.Pipe.Type as Pipe
import qualified Streamly.Internal.Data.Ring as Ring
import qualified Streamly.Internal.Data.Stream.StreamD.Type as StreamD
@ -730,7 +730,7 @@ length = lengthGeneric
-- identity (@0@) when the stream is empty. Note that this is not numerically
-- stable for floating point numbers.
--
-- >>> sum = FoldW.cumulative FoldW.sum
-- >>> sum = Fold.cumulative Fold.windowSum
--
-- Same as following but numerically stable:
--
@ -739,7 +739,7 @@ length = lengthGeneric
--
{-# INLINE sum #-}
sum :: (Monad m, Num a) => Fold m a a
sum = FoldW.cumulative FoldW.sum
sum = Fold.cumulative Fold.windowSum
-- | Determine the product of all elements of a stream of numbers. Returns
-- multiplicative identity (@1@) when the stream is empty. The fold terminates

View File

@ -36,24 +36,24 @@ module Streamly.Internal.Data.Fold.Window
-- window folds by keeping the second element of the input tuple as
-- @Nothing@.
--
lmap
windowLmap
, cumulative
, rollingMap
, rollingMapM
, windowRollingMap
, windowRollingMapM
-- ** Sums
, length
, sum
, sumInt
, powerSum
, powerSumFrac
, windowLength
, windowSum
, windowSumInt
, windowPowerSum
, windowPowerSumFrac
-- ** Location
, minimum
, maximum
, range
, mean
, windowMinimum
, windowMaximum
, windowRange
, windowMean
)
where
@ -73,7 +73,7 @@ import Prelude hiding (length, sum, minimum, maximum)
-- $setup
-- >>> import Data.Bifunctor(bimap)
-- >>> import qualified Streamly.Data.Fold as Fold
-- >>> import qualified Streamly.Internal.Data.Fold.Window as FoldW
-- >>> import qualified Streamly.Internal.Data.Fold.Window as Fold
-- >>> import qualified Streamly.Internal.Data.Ring as Ring
-- >>> import qualified Streamly.Data.Stream as Stream
-- >>> import Prelude hiding (length, sum, minimum, maximum)
@ -87,9 +87,9 @@ import Prelude hiding (length, sum, minimum, maximum)
--
-- >>> lmap f = Fold.lmap (bimap f (f <$>))
--
{-# INLINE lmap #-}
lmap :: (c -> a) -> Fold m (a, Maybe a) b -> Fold m (c, Maybe c) b
lmap f = Fold.lmap (bimap f (f <$>))
{-# INLINE windowLmap #-}
windowLmap :: (c -> a) -> Fold m (a, Maybe a) b -> Fold m (c, Maybe c) b
windowLmap f = Fold.lmap (bimap f (f <$>))
-- | Convert an incremental fold to a cumulative fold using the entire input
-- stream as a single window.
@ -105,10 +105,10 @@ cumulative = Fold.lmap (, Nothing)
-- | Apply an effectful function on the latest and the oldest element of the
-- window.
{-# INLINE rollingMapM #-}
rollingMapM :: Monad m =>
{-# INLINE windowRollingMapM #-}
windowRollingMapM :: Monad m =>
(Maybe a -> a -> m (Maybe b)) -> Fold m (a, Maybe a) (Maybe b)
rollingMapM f = Fold.foldlM' f1 initial
windowRollingMapM f = Fold.foldlM' f1 initial
where
@ -118,12 +118,12 @@ rollingMapM f = Fold.foldlM' f1 initial
-- | Apply a pure function on the latest and the oldest element of the window.
--
-- >>> rollingMap f = FoldW.rollingMapM (\x y -> return $ f x y)
-- >>> windowRollingMap f = Fold.windowRollingMapM (\x y -> return $ f x y)
--
{-# INLINE rollingMap #-}
rollingMap :: Monad m =>
{-# INLINE windowRollingMap #-}
windowRollingMap :: Monad m =>
(Maybe a -> a -> Maybe b) -> Fold m (a, Maybe a) (Maybe b)
rollingMap f = Fold.foldl' f1 initial
windowRollingMap f = Fold.foldl' f1 initial
where
@ -146,9 +146,9 @@ rollingMap f = Fold.foldl' f1 initial
--
-- /Internal/
--
{-# INLINE sumInt #-}
sumInt :: forall m a. (Monad m, Integral a) => Fold m (a, Maybe a) a
sumInt = Fold step initial extract
{-# INLINE windowSumInt #-}
windowSumInt :: forall m a. (Monad m, Integral a) => Fold m (a, Maybe a) a
windowSumInt = Fold step initial extract
where
@ -180,9 +180,9 @@ sumInt = Fold step initial extract
--
-- /Time/: \(\mathcal{O}(n)\)
--
{-# INLINE sum #-}
sum :: forall m a. (Monad m, Num a) => Fold m (a, Maybe a) a
sum = Fold step initial extract
{-# INLINE windowSum #-}
windowSum :: forall m a. (Monad m, Num a) => Fold m (a, Maybe a) a
windowSum = Fold step initial extract
where
@ -219,9 +219,9 @@ sum = Fold step initial extract
--
-- >>> length = powerSum 0
--
{-# INLINE length #-}
length :: (Monad m, Num b) => Fold m (a, Maybe a) b
length = Fold.foldl' step 0
{-# INLINE windowLength #-}
windowLength :: (Monad m, Num b) => Fold m (a, Maybe a) b
windowLength = Fold.foldl' step 0
where
@ -237,18 +237,18 @@ length = Fold.foldl' step 0
-- /Space/: \(\mathcal{O}(1)\)
--
-- /Time/: \(\mathcal{O}(n)\)
{-# INLINE powerSum #-}
powerSum :: (Monad m, Num a) => Int -> Fold m (a, Maybe a) a
powerSum k = lmap (^ k) sum
{-# INLINE windowPowerSum #-}
windowPowerSum :: (Monad m, Num a) => Int -> Fold m (a, Maybe a) a
windowPowerSum k = windowLmap (^ k) windowSum
-- | Like 'powerSum' but powers can be negative or fractional. This is slower
-- than 'powerSum' for positive intergal powers.
--
-- >>> powerSumFrac p = lmap (** p) sum
--
{-# INLINE powerSumFrac #-}
powerSumFrac :: (Monad m, Floating a) => a -> Fold m (a, Maybe a) a
powerSumFrac p = lmap (** p) sum
{-# INLINE windowPowerSumFrac #-}
windowPowerSumFrac :: (Monad m, Floating a) => a -> Fold m (a, Maybe a) a
windowPowerSumFrac p = windowLmap (** p) windowSum
-------------------------------------------------------------------------------
-- Location
@ -265,9 +265,9 @@ powerSumFrac p = lmap (** p) sum
--
-- /Time/: \(\mathcal{O}(n*w)\) where \(w\) is the window size.
--
{-# INLINE range #-}
range :: (MonadIO m, Storable a, Ord a) => Int -> Fold m a (Maybe (a, a))
range n = Fold step initial extract
{-# INLINE windowRange #-}
windowRange :: (MonadIO m, Storable a, Ord a) => Int -> Fold m a (Maybe (a, a))
windowRange n = Fold step initial extract
where
@ -316,9 +316,9 @@ range n = Fold step initial extract
--
-- /Time/: \(\mathcal{O}(n*w)\) where \(w\) is the window size.
--
{-# INLINE minimum #-}
minimum :: (MonadIO m, Storable a, Ord a) => Int -> Fold m a (Maybe a)
minimum n = fmap (fmap fst) $ range n
{-# INLINE windowMinimum #-}
windowMinimum :: (MonadIO m, Storable a, Ord a) => Int -> Fold m a (Maybe a)
windowMinimum n = fmap (fmap fst) $ windowRange n
-- | The maximum element in a rolling window.
--
@ -329,9 +329,9 @@ minimum n = fmap (fmap fst) $ range n
--
-- /Time/: \(\mathcal{O}(n*w)\) where \(w\) is the window size.
--
{-# INLINE maximum #-}
maximum :: (MonadIO m, Storable a, Ord a) => Int -> Fold m a (Maybe a)
maximum n = fmap (fmap snd) $ range n
{-# INLINE windowMaximum #-}
windowMaximum :: (MonadIO m, Storable a, Ord a) => Int -> Fold m a (Maybe a)
windowMaximum n = fmap (fmap snd) $ windowRange n
-- | Arithmetic mean of elements in a sliding window:
--
@ -346,6 +346,6 @@ maximum n = fmap (fmap snd) $ range n
-- /Space/: \(\mathcal{O}(1)\)
--
-- /Time/: \(\mathcal{O}(n)\)
{-# INLINE mean #-}
mean :: forall m a. (Monad m, Fractional a) => Fold m (a, Maybe a) a
mean = Fold.teeWith (/) sum length
{-# INLINE windowMean #-}
windowMean :: forall m a. (Monad m, Fractional a) => Fold m (a, Maybe a) a
windowMean = Fold.teeWith (/) windowSum windowLength

View File

@ -324,7 +324,6 @@ library
, Streamly.Internal.Data.Unfold
, Streamly.Internal.Data.Fold.Tee
, Streamly.Internal.Data.Fold.Chunked
, Streamly.Internal.Data.Fold.Window
, Streamly.Internal.Data.Parser
, Streamly.Internal.Data.Pipe
@ -411,6 +410,7 @@ library
, Streamly.Internal.Data.Fold.Type
, Streamly.Internal.Data.Fold.Combinators
, Streamly.Internal.Data.Fold.Container
, Streamly.Internal.Data.Fold.Window
, Streamly.Internal.Data.Stream.StreamD.Container
, Streamly.Internal.Data.Stream.StreamD.Eliminate

View File

@ -1,6 +1,5 @@
module Streamly.Test.Data.Fold.Window (main) where
import Streamly.Internal.Data.Fold.Window
import Test.Hspec (hspec, describe, it, runIO)
import qualified Streamly.Internal.Data.Ring as Ring
import qualified Streamly.Internal.Data.Stream as S
@ -29,8 +28,8 @@ main = hspec $ do
it ("should not deviate more than " ++ show deviationLimit)
$ c1 >= -1 * deviationLimit && c1 <= deviationLimit
describe "Sum" $ testFunc sum
describe "mean" $ testFunc mean
describe "Sum" $ testFunc Fold.windowSum
describe "mean" $ testFunc Fold.windowMean
describe "Correctness" $ do
let winSize = 3
@ -53,16 +52,16 @@ main = hspec $ do
it (show tc) $ a == expec
describe "minimum" $ do
testFunc2 testCase1 (Just (-2.5)) minimum
testFunc2 testCase1 (Just (-2.5)) Fold.windowMinimum
describe "maximum" $ do
testFunc2 testCase1 (Just 7.0) maximum
testFunc2 testCase1 (Just 7.0) Fold.windowMaximum
describe "range" $ do
testFunc2 testCase1 (Just (-2.5, 7.0)) range
testFunc2 testCase1 (Just (-2.5, 7.0)) Fold.windowRange
describe "sum" $ do
let scanInf = [1, 2, 3, 4, 5, 12] :: [Double]
scanWin = [1, 2, 3, 3, 3, 9] :: [Double]
testFunc testCase2 sum scanInf scanWin
testFunc testCase2 Fold.windowSum scanInf scanWin
describe "mean" $ do
let scanInf = [1, 1, 1, 1, 1, 2] :: [Double]
scanWin = [1, 1, 1, 1, 1, 3] :: [Double]
testFunc testCase2 mean scanInf scanWin
testFunc testCase2 Fold.windowMean scanInf scanWin