fold package:foldl

Apply a strict left Fold to a Foldable container
Apply a strict left Fold to a lazy bytestring
Apply a strict left Fold to lazy text
Efficient representation of a left fold that preserves the fold's step function, initial accumulator, and extraction function This allows the Applicative instance to assemble derived folds that traverse the container only once A 'Fold a b' processes elements of type a and results in a value of type b.
Fold step initial extract
Composable, streaming, and efficient left folds This library provides strict left folds that stream in constant memory, and you can combine folds using Applicative style to derive new folds. Derived folds still traverse the container just once and are often as efficient as hand-written folds.
Given a Fold, produces a HashMap which applies that fold to each a separated by key k.
>>> List.sort (HashMap.toList (fold (foldByKeyHashMap Control.Foldl.sum) [("a",1), ("b",2), ("b",20), ("a",10)]))
[("a",11),("b",22)]
Given a Fold, produces a Map which applies that fold to each a separated by key k.
>>> fold (foldByKeyMap Control.Foldl.sum) [("a",1), ("b",2), ("b",20), ("a",10)]
fromList [("a",11),("b",22)]
Like fold, but monadic
Convert a "foldMap" to a Fold
(foldOver f folder xs) folds all values from a Lens, Traversal, Prism or Fold with the given folder
>>> foldOver (_Just . both) Foldl.sum (Just (2, 3))
5
>>> foldOver (_Just . both) Foldl.sum Nothing
0
Foldl.foldOver f folder xs == Foldl.fold folder (xs^..f)
Foldl.foldOver (folded . f) folder == Foldl.fold (handles f folder)
Foldl.foldOver folded == Foldl.fold
(foldOverM f folder xs) folds all values from a Lens, Traversal, Prism or Fold monadically with the given folder
Foldl.foldOverM (folded . f) folder == Foldl.foldM (handlesM f folder)
Foldl.foldOverM folded == Foldl.foldM
folded :: Foldable t => Fold (t a) a

handles folded :: Foldable t => Fold a r -> Fold (t a) r
Apply a strict monadic left FoldM to a lazy bytestring
Apply a strict left Fold1 to a NonEmpty list
(foldOver f folder xs) folds all values from a Lens, Traversal1 or Fold1 optic with the given folder
>>> foldOver (_2 . both1) Foldl1.nonEmpty (1, (2, 3))
2 :| [3]
Foldl1.foldOver f folder xs == Foldl1.fold1 folder (xs ^.. f)
Foldl1.foldOver (folded1 . f) folder == Foldl1.fold1 (Foldl1.handles f folder)
Foldl1.foldOver folded1 == Foldl1.fold1
handles folded1 :: Foldable1 t => Fold1 a r -> Fold1 (t a) r
Apply a strict monadic left FoldM to lazy text
This module provides efficient and streaming left folds that you can combine using Applicative style. Import this module qualified to avoid clashing with the Prelude:
>>> import qualified Control.Foldl as Foldl
Use fold to apply a Fold to a list:
>>> Foldl.fold Foldl.sum [1..100]
5050
Folds are Applicatives, so you can combine them using Applicative combinators:
>>> import Control.Applicative

>>> let average = (/) <$> Foldl.sum <*> Foldl.genericLength
… or you can use do notation if you enable the ApplicativeDo language extension:
>>> :set -XApplicativeDo

>>> let average = do total <- Foldl.sum; count <- Foldl.genericLength; return (total / count)
… or you can use the fact that the Fold type implements Num to do this:
>>> let average = Foldl.sum / Foldl.genericLength
These combined folds will still traverse the list only once, streaming efficiently over the list in constant space without space leaks:
>>> Foldl.fold average [1..10000000]
5000000.5

>>> Foldl.fold ((,) <$> Foldl.minimum <*> Foldl.maximum) [1..10000000]
(Just 1,Just 10000000)
You might want to try enabling the -flate-dmd-anal flag when compiling executables that use this library to further improve performance.
Like Fold, but monadic. A 'FoldM m a b' processes elements of type a and results in a monadic value of type m b.
FoldM step initial extract
The Foldable class represents data structures that can be reduced to a summary value one element at a time. Strict left-associative folds are a good fit for space-efficient reduction, while lazy right-associative folds are a good fit for corecursive iteration, or for folds that short-circuit after processing an initial subsequence of the structure's elements. Instances can be derived automatically by enabling the DeriveFoldable extension. For example, a derived instance for a binary tree might be:
{-# LANGUAGE DeriveFoldable #-}
data Tree a = Empty
| Leaf a
| Node (Tree a) a (Tree a)
deriving Foldable
A more detailed description can be found in the Overview section of Data.Foldable#overview. For the class laws see the Laws section of Data.Foldable#laws.
A Fold1 is like a Fold except that it consumes at least one input element
Fold1_ is an alternative to the Fold1 constructor if you need to explicitly work with an initial, step and extraction function. Fold1_ is similar to the Fold constructor, which also works with an initial, step and extraction function. However, note that Fold takes the step function as the first argument and the initial accumulator as the second argument, whereas Fold1_ takes them in swapped order: Fold1_ initial step extract While Fold resembles foldl, Fold1_ resembles foldlMap1.