@@ -30,14 +30,14 @@ module Streamly.Internal.Data.Scanl.Combinators
3030 -- , rollingHashLastN
3131
3232 -- *** Saturating Reducers
33- -- | 'product' terminates if it becomes 0. Other folds can theoretically
33+ -- | 'product' terminates if it becomes 0. Other scans can theoretically
3434 -- saturate on bounded types, and therefore terminate, however, they will
3535 -- run forever on unbounded types like Integer/Double.
3636 , sum
3737 , product
3838
3939 -- *** Collectors
40- -- | Avoid using these folds in scalable or performance critical
40+ -- | Avoid using these scans in scalable or performance critical
4141 -- applications, they buffer all the input in GC memory which can be
4242 -- detrimental to performance if the input is large.
4343 , toListRev
@@ -51,7 +51,7 @@ module Streamly.Internal.Data.Scanl.Combinators
5151
5252 -- *** Scanners
5353 -- | Stateful transformation of the elements. Useful in combination with
54- -- the 'postscanlMaybe' combinator. For scanners the result of the fold is
54+ -- the 'postscanlMaybe' combinator. For scanners the result of the scan is
5555 -- usually a transformation of the current element rather than an
5656 -- aggregation of all elements till now.
5757 -- , nthLast -- using RingArray array
@@ -71,16 +71,16 @@ module Streamly.Internal.Data.Scanl.Combinators
7171 , elemIndices
7272
7373 {-
74- -- *** Singleton folds
75- -- | Folds that terminate after consuming exactly one input element. All
76- -- these can be implemented in terms of the 'maybe' fold .
74+ -- *** Singleton scans
75+ -- | Scans that terminate after consuming exactly one input element. All
76+ -- these can be implemented in terms of the 'maybe' scan .
7777 , one
7878 , null -- XXX not very useful and could be problematic, remove it?
7979 , satisfy
8080 , maybe
8181 -}
8282
83- -- *** Multi folds
83+ -- *** Multi scans
8484 -- | Terminate after consuming one or more elements.
8585 , drainN
8686 {-
@@ -111,7 +111,7 @@ module Streamly.Internal.Data.Scanl.Combinators
111111 , droppingWhile
112112 , prune
113113
114- -- -- * Running A Fold
114+ -- -- * Running A Scanl
115115 -- , drive
116116 -- , breakStream
117117
@@ -356,8 +356,8 @@ addStream stream = drive stream . duplicate
356356mapMaybeM :: Monad m => (a -> m (Maybe b )) -> Scanl m b r -> Scanl m a r
357357mapMaybeM f = lmapM f . catMaybes
358358
359- -- | @mapMaybe f fold @ maps a 'Maybe' returning function @f@ on the input of
360- -- the fold , filters out 'Nothing' elements, and return the values extracted
359+ -- | @mapMaybe f scan @ maps a 'Maybe' returning function @f@ on the input of
360+ -- the scan , filters out 'Nothing' elements, and return the values extracted
361361-- from 'Just'.
362362--
363363-- >>> mapMaybe f = Scanl.lmap f . Scanl.catMaybes
@@ -373,15 +373,15 @@ mapMaybe :: Monad m => (a -> Maybe b) -> Scanl m b r -> Scanl m a r
373373mapMaybe f = lmap f . catMaybes
374374
375375------------------------------------------------------------------------------
376- -- Transformations on fold inputs
376+ -- Transformations on scan inputs
377377------------------------------------------------------------------------------
378378
379379-- XXX rather scanl the input of a pipe? And scanr the output?
380380-- pipe :: Monad m => Scanl m a b -> Pipe m b c -> Scanl m a c
381381-- Can we do this too (in the pipe module):
382382-- pipe :: Monad m => Scanl m a b -> Pipe m b c -> Pipe m a c
383383
384- -- | Attach a 'Pipe' on the input of a 'Fold '.
384+ -- | Attach a 'Pipe' on the input of a 'Scanl '.
385385--
386386-- /Pre-release/
387387{-# INLINE pipe #-}
@@ -407,8 +407,8 @@ pipe (Pipe consume produce pinitial) (Scanl fstep finitial fextract ffinal) =
407407 Partial s -> Partial $ Tuple' cs1 s
408408 Done b1 -> Done b1
409409 -- XXX this case is recursive may cause fusion issues.
410- -- To remove recursion we will need a produce mode in folds which makes
411- -- folds similar to pipes except that they do not yield intermediate
410+ -- To remove recursion we will need a produce mode in scans which makes
411+ -- scans similar to pipes except that they do not yield intermediate
412412 -- values.
413413 go acc (Pipe. YieldP ps1 b) = do
414414 acc1 <- fstep acc b
@@ -424,7 +424,7 @@ pipe (Pipe consume produce pinitial) (Scanl fstep finitial fextract ffinal) =
424424 go acc r
425425 -- XXX a Stop in consumer means we dropped the input.
426426 -- XXX Need to use a "Done b" in pipes as well to represent the same
427- -- behavior as folds .
427+ -- behavior as scans .
428428 go acc Pipe. Stop = Done <$> ffinal acc
429429
430430 extract (Tuple' _ fs) = fextract fs
@@ -687,7 +687,7 @@ repeated :: -- (Monad m, Eq a) =>
687687repeated = error " Not implemented yet!"
688688
689689------------------------------------------------------------------------------
690- -- Left folds
690+ -- Left scans
691691------------------------------------------------------------------------------
692692
693693------------------------------------------------------------------------------
@@ -745,7 +745,7 @@ sum :: (Monad m, Num a) => Scanl m a a
745745sum = Scanl. cumulativeScan Scanl. incrSum
746746
747747-- | Determine the product of all elements of a stream of numbers. Returns
748- -- multiplicative identity (@1@) when the stream is empty. The fold terminates
748+ -- multiplicative identity (@1@) when the stream is empty. The scan terminates
749749-- when it encounters (@0@) in its input.
750750--
751751-- Same as the following but terminates on multiplication by @0@:
@@ -829,7 +829,7 @@ rollingHashFirstN :: (Monad m, Enum a) => Int -> Scanl m a Int64
829829rollingHashFirstN n = take n rollingHash
830830
831831------------------------------------------------------------------------------
832- -- Monoidal left folds
832+ -- Monoidal left scans
833833------------------------------------------------------------------------------
834834
835835-- | Semigroup concat. Append the elements of an input stream to a provided
@@ -847,7 +847,7 @@ rollingHashFirstN n = take n rollingHash
847847sconcat :: (Monad m , Semigroup a ) => a -> Scanl m a a
848848sconcat = mkScanl (<>)
849849
850- -- | Monoid concat. Fold an input stream consisting of monoidal elements using
850+ -- | Monoid concat. Scan an input stream consisting of monoidal elements using
851851-- 'mappend' and 'mempty'.
852852--
853853-- Definition:
@@ -869,7 +869,7 @@ mconcat = sconcat mempty
869869--
870870-- >>> foldMap f = Scanl.lmap f Scanl.mconcat
871871--
872- -- Make a fold from a pure function that folds the output of the function
872+ -- Make a scan from a pure function that scans the output of the function
873873-- using 'mappend' and 'mempty'.
874874--
875875-- >>> sum = Scanl.foldMap Data.Monoid.Sum
@@ -885,7 +885,7 @@ foldMap f = lmap f mconcat
885885--
886886-- >>> foldMapM f = Scanl.lmapM f Scanl.mconcat
887887--
888- -- Make a fold from a monadic function that folds the output of the function
888+ -- Make a scan from a monadic function that scans the output of the function
889889-- using 'mappend' and 'mempty'.
890890--
891891-- >>> sum = Scanl.foldMapM (return . Data.Monoid.Sum)
@@ -926,10 +926,10 @@ toListRev :: Monad m => Scanl m a [a]
926926toListRev = mkScanl (flip (:) ) []
927927
928928------------------------------------------------------------------------------
929- -- Partial Folds
929+ -- Partial Scans
930930------------------------------------------------------------------------------
931931
932- -- | A fold that drains the first n elements of its input, running the effects
932+ -- | A scan that drains the first n elements of its input, running the effects
933933-- and discarding the results.
934934--
935935-- Definition:
@@ -1729,7 +1729,7 @@ tee = teeWith (,)
17291729
17301730-- XXX use unboxed Array for output to scale it to a large number of consumers?
17311731
1732- -- | Distribute one copy of the stream to each fold and collect the results in
1732+ -- | Distribute one copy of the stream to each scan and collect the results in
17331733-- a container.
17341734--
17351735-- @
@@ -1788,7 +1788,7 @@ data PartState sL sR = PartLeft !sL !sR | PartRight !sL !sR
17881788-- |-------Scanl c y--------|
17891789-- @
17901790--
1791- -- Example, send input to either fold randomly:
1791+ -- Example, send input to either scan randomly:
17921792--
17931793-- >>> :set -package random
17941794-- >>> import System.Random (randomIO)
@@ -1797,7 +1797,7 @@ data PartState sL sR = PartLeft !sL !sR | PartRight !sL !sR
17971797-- >>> Stream.toList $ Stream.scanl f (Stream.enumerateFromTo 1 10)
17981798-- ...
17991799--
1800- -- Example, send input to the two folds in a proportion of 2:1:
1800+ -- Example, send input to the two scans in a proportion of 2:1:
18011801--
18021802-- >>> :set -fno-warn-unrecognised-warning-flags
18031803-- >>> :set -fno-warn-x-partial
@@ -1888,7 +1888,7 @@ partitionByMinM = partitionByMUsing teeWithMin
18881888-}
18891889
18901890-- Note: we could use (a -> Bool) instead of (a -> Either b c), but the latter
1891- -- makes the signature clearer as to which case belongs to which fold .
1891+ -- makes the signature clearer as to which case belongs to which scan .
18921892-- XXX need to check the performance in both cases.
18931893
18941894-- | Same as 'partitionByM' but with a pure partition function.
@@ -1909,9 +1909,9 @@ partitionBy :: Monad m
19091909 => (a -> Either b c ) -> Scanl m b x -> Scanl m c x -> Scanl m a x
19101910partitionBy f = partitionByM (return . f)
19111911
1912- -- | Compose two folds such that the combined fold accepts a stream of 'Either'
1913- -- and routes the 'Left' values to the first fold and 'Right' values to the
1914- -- second fold .
1912+ -- | Compose two scans such that the combined scan accepts a stream of 'Either'
1913+ -- and routes the 'Left' values to the first scan and 'Right' values to the
1914+ -- second scan .
19151915--
19161916-- Definition:
19171917--
@@ -1946,8 +1946,8 @@ unzipWithMUsing :: Monad m =>
19461946 -> Scanl m c y
19471947 -> Scanl m a (x , y )
19481948unzipWithMUsing t f fld1 fld2 =
1949- let f1 = lmap fst fld1 -- :: Fold m (b, c) b
1950- f2 = lmap snd fld2 -- :: Fold m (b, c) c
1949+ let f1 = lmap fst fld1 -- :: Scanl m (b, c) b
1950+ f2 = lmap snd fld2 -- :: Scanl m (b, c) c
19511951 in lmapM f (t (,) f1 f2)
19521952
19531953-- | Like 'unzipWith' but with a monadic splitter function.
@@ -1979,7 +1979,7 @@ unzipWithMaxM = unzipWithMUsing teeWithMax
19791979-}
19801980
19811981-- | Split elements in the input stream into two parts using a pure splitter
1982- -- function, direct each part to a different fold and zip the results.
1982+ -- function, direct each part to a different scan and zip the results.
19831983--
19841984-- Definitions:
19851985--
@@ -1995,7 +1995,7 @@ unzipWith :: Monad m
19951995unzipWith f = unzipWithM (return . f)
19961996
19971997-- | Send the elements of tuples in a stream of tuples through two different
1998- -- folds .
1998+ -- scans .
19991999--
20002000-- @
20012001--
@@ -2016,7 +2016,7 @@ unzip :: Monad m => Scanl m a x -> Scanl m b y -> Scanl m (a,b) (x,y)
20162016unzip = unzipWith id
20172017
20182018------------------------------------------------------------------------------
2019- -- Combining streams and folds - Zipping
2019+ -- Combining streams and scans - Zipping
20202020------------------------------------------------------------------------------
20212021
20222022-- XXX These can be implemented using the fold scan, using the stream as a
@@ -2028,7 +2028,7 @@ unzip = unzipWith id
20282028-- cmpBy, eqBy, isPrefixOf, isSubsequenceOf etc can be implemented using
20292029-- zipStream.
20302030
2031- -- | Zip a stream with the input of a fold using the supplied function.
2031+ -- | Zip a stream with the input of a scan using the supplied function.
20322032--
20332033-- /Unimplemented/
20342034--
@@ -2037,7 +2037,7 @@ zipStreamWithM :: -- Monad m =>
20372037 (a -> b -> m c ) -> Stream m a -> Scanl m c x -> Scanl m b x
20382038zipStreamWithM = undefined
20392039
2040- -- | Zip a stream with the input of a fold .
2040+ -- | Zip a stream with the input of a scan .
20412041--
20422042-- >>> zip = Scanl.zipStreamWithM (curry return)
20432043--
@@ -2074,15 +2074,15 @@ indexing = indexingWith 0 (+ 1)
20742074indexingRev :: Monad m => Int -> Scanl m a (Maybe (Int , a ))
20752075indexingRev n = indexingWith n (subtract 1 )
20762076
2077- -- | Pair each element of a fold input with its index, starting from index 0.
2077+ -- | Pair each element of a scan input with its index, starting from index 0.
20782078--
20792079-- >>> indexed = Scanl.postscanlMaybe Scanl.indexing
20802080--
20812081{-# INLINE indexed #-}
20822082indexed :: Monad m => Scanl m (Int , a ) b -> Scanl m a b
20832083indexed = postscanlMaybe indexing
20842084
2085- -- | Change the predicate function of a Fold from @a -> b@ to accept an
2085+ -- | Change the predicate function of a Scanl from @a -> b@ to accept an
20862086-- additional state input @(s, a) -> b@. Convenient to filter with an
20872087-- addiitonal index or time input.
20882088--
@@ -2146,7 +2146,7 @@ chunksBetween :: -- Monad m =>
21462146chunksBetween _low _high _f1 _f2 = undefined
21472147-}
21482148
2149- -- | A fold that buffers its input to a pure stream.
2149+ -- | A scan that buffers its input to a pure stream.
21502150--
21512151-- /Warning!/ working on large streams accumulated as buffers in memory could
21522152-- be very inefficient, consider using "Streamly.Data.Array" instead.
@@ -2179,7 +2179,7 @@ toStreamRev = fmap StreamD.fromList toListRev
21792179-- XXX This does not fuse. It contains a recursive step function. We will need
21802180-- a Skip input constructor in the fold type to make it fuse.
21812181
2182- -- | Unfold and flatten the input stream of a fold .
2182+ -- | Unfold and flatten the input stream of a scan .
21832183--
21842184-- @
21852185-- Stream.scanl (unfoldMany u f) == Stream.scanl f . Stream.unfoldMany u
@@ -2264,7 +2264,7 @@ topBy :: (MonadIO m, Unbox a) =>
22642264 -> Scanl m a (MutArray a )
22652265topBy cmp = bottomBy (flip cmp)
22662266
2267- -- | Fold the input stream to top n elements.
2267+ -- | Scan the input stream to top n elements.
22682268--
22692269-- Definition:
22702270--
@@ -2279,7 +2279,7 @@ topBy cmp = bottomBy (flip cmp)
22792279top :: (MonadIO m , Unbox a , Ord a ) => Int -> Scanl m a (MutArray a )
22802280top = bottomBy $ flip compare
22812281
2282- -- | Fold the input stream to bottom n elements.
2282+ -- | Scan the input stream to bottom n elements.
22832283--
22842284-- Definition:
22852285--
0 commit comments