This commit is contained in:
Ranjeet Kumar Ranjan 2023-07-24 21:09:28 +05:30
parent e26ded674f
commit 15510ac840

View File

@ -41,7 +41,7 @@ module Streamly.Internal.Data.Stream.IsStream.Reduce {-# DEPRECATED "Please use
, chunksOf , chunksOf
, arraysOf , arraysOf
, intervalsOf , intervalsOf
, groupsOfTimeout , chunksOfTimeout
-- ** Splitting -- ** Splitting
-- | Streams can be sliced into segments in space or in time. We use the -- | Streams can be sliced into segments in space or in time. We use the
@ -1025,13 +1025,13 @@ intervalsOf n f xs =
-- is 100 ms. -- is 100 ms.
-- --
-- >>> s = Stream.delayPost 0.3 $ Stream.fromList [1..1000] -- >>> s = Stream.delayPost 0.3 $ Stream.fromList [1..1000]
-- >>> f = Stream.mapM_ print $ Stream.groupsOfTimeout 5 1 Fold.toList s -- >>> f = Stream.mapM_ print $ Stream.chunksOfTimeout 5 1 Fold.toList s
-- --
-- /Pre-release/ -- /Pre-release/
{-# INLINE groupsOfTimeout #-} {-# INLINE chunksOfTimeout #-}
groupsOfTimeout :: (IsStream t, MonadAsync m, Functor (t m)) chunksOfTimeout :: (IsStream t, MonadAsync m, Functor (t m))
=> Int -> Double -> FL.Fold m a b -> t m a -> t m b => Int -> Double -> FL.Fold m a b -> t m a -> t m b
groupsOfTimeout n timeout f = chunksOfTimeout n timeout f =
map snd map snd
. classifySessionsBy . classifySessionsBy
0.1 False (const (return False)) timeout (FL.take n f) 0.1 False (const (return False)) timeout (FL.take n f)