Safe Haskell | Trustworthy |
---|
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 L
Use fold
to apply a Fold
to a list:
>>>
L.fold L.sum [1..100]
5050
Fold
s are Applicative
s, so you can combine them using Applicative
combinators:
>>>
import Control.Applicative
>>>
let average = (/) <$> L.sum <*> L.genericLength
These combined folds will still traverse the list only once, streaming efficiently over the list in constant space without space leaks:
>>>
L.fold average [1..10000000]
5000000.5>>>
L.fold ((,) <$> L.minimum <*> L.maximum) [1..10000000]
(Just 1,Just 10000000)
- data Fold a b = forall x . Fold (x -> a -> x) x (x -> b)
- data FoldM m a b = forall x . FoldM (x -> a -> m x) (m x) (x -> m b)
- fold :: Foldable f => Fold a b -> f a -> b
- foldM :: (Foldable f, Monad m) => FoldM m a b -> f a -> m b
- scan :: Fold a b -> [a] -> [b]
- mconcat :: Monoid a => Fold a a
- foldMap :: Monoid w => (a -> w) -> (w -> b) -> Fold a b
- head :: Fold a (Maybe a)
- last :: Fold a (Maybe a)
- lastDef :: a -> Fold a a
- null :: Fold a Bool
- length :: Fold a Int
- and :: Fold Bool Bool
- or :: Fold Bool Bool
- all :: (a -> Bool) -> Fold a Bool
- any :: (a -> Bool) -> Fold a Bool
- sum :: Num a => Fold a a
- product :: Num a => Fold a a
- maximum :: Ord a => Fold a (Maybe a)
- minimum :: Ord a => Fold a (Maybe a)
- elem :: Eq a => a -> Fold a Bool
- notElem :: Eq a => a -> Fold a Bool
- find :: (a -> Bool) -> Fold a (Maybe a)
- index :: Int -> Fold a (Maybe a)
- elemIndex :: Eq a => a -> Fold a (Maybe Int)
- findIndex :: (a -> Bool) -> Fold a (Maybe Int)
- genericLength :: Num b => Fold a b
- genericIndex :: Integral i => i -> Fold a (Maybe a)
- list :: Fold a [a]
- nub :: Ord a => Fold a [a]
- eqNub :: Eq a => Fold a [a]
- set :: Ord a => Fold a (Set a)
- vector :: (PrimMonad m, Vector v a) => FoldM m a (v a)
- purely :: (forall x. (x -> a -> x) -> x -> (x -> b) -> r) -> Fold a b -> r
- impurely :: Monad m => (forall x. (x -> a -> m x) -> m x -> (x -> m b) -> r) -> FoldM m a b -> r
- generalize :: Monad m => Fold a b -> FoldM m a b
- simplify :: FoldM Identity a b -> Fold a b
- premap :: (a -> b) -> Fold b r -> Fold a r
- premapM :: Monad m => (a -> b) -> FoldM m b r -> FoldM m a r
- pretraverse :: Traversal' a b -> Fold b r -> Fold a r
- pretraverseM :: Monad m => Traversal' a b -> FoldM m b r -> FoldM m a r
- module Data.Foldable
Fold Types
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
forall x . Fold (x -> a -> x) x (x -> b) |
Folding
Folds
head :: Fold a (Maybe a)Source
Get the first element of a container or return Nothing
if the container is
empty
last :: Fold a (Maybe a)Source
Get the last element of a container or return Nothing
if the container is
empty
lastDef :: a -> Fold a aSource
Get the last element of a container or return a default value if the container is empty
find :: (a -> Bool) -> Fold a (Maybe a)Source
(find predicate)
returns the first element that satisfies the predicate or
Nothing
if no element satisfies the predicate
index :: Int -> Fold a (Maybe a)Source
(index n)
returns the n
th element of the container, or Nothing
if the
container has an insufficient number of elements
elemIndex :: Eq a => a -> Fold a (Maybe Int)Source
(elemIndex a)
returns the index of the first element that equals a
, or
Nothing
if no element matches
findIndex :: (a -> Bool) -> Fold a (Maybe Int)Source
(findIndex predicate)
returns the index of the first element that
satisfies the predicate, or Nothing
if no element satisfies the predicate
Generic Folds
genericIndex :: Integral i => i -> Fold a (Maybe a)Source
Container folds
nub :: Ord a => Fold a [a]Source
O(n log n). Fold values into a list with duplicates removed, while preserving their first occurrences
eqNub :: Eq a => Fold a [a]Source
O(n^2). Fold values into a list with duplicates removed, while preserving their first occurrences
Utilities
purely
and impurely
allow you to write folds compatible with the foldl
library without incurring a foldl
dependency. Write your fold to accept
three parameters corresponding to the step function, initial
accumulator, and extraction function and then users can upgrade your
function to accept a Fold
or FoldM
using the purely
or impurely
combinators.
For example, the pipes
library implements a foldM
function in
Pipes.Prelude
with the following type:
foldM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Producer a m () -> m b
foldM
is set up so that you can wrap it with impurely
to accept a
FoldM
instead:
impurely foldM :: Monad m => FoldM m a b -> Producer a m () -> m b
purely :: (forall x. (x -> a -> x) -> x -> (x -> b) -> r) -> Fold a b -> rSource
Upgrade a fold to accept the Fold
type
impurely :: Monad m => (forall x. (x -> a -> m x) -> m x -> (x -> m b) -> r) -> FoldM m a b -> rSource
Upgrade a monadic fold to accept the FoldM
type
generalize :: Monad m => Fold a b -> FoldM m a bSource
premap :: (a -> b) -> Fold b r -> Fold a rSource
(premap f folder)
returns a new Fold
where f is applied at each step
fold (premap f folder) list = fold folder (map f list)
premap id = id premap (f . g) = premap g . premap f
premap k (pure r) = pure r premap k (f <*> x) = premap k f <*> premap k x
premapM :: Monad m => (a -> b) -> FoldM m b r -> FoldM m a rSource
(premapM f folder)
returns a new FoldM
where f is applied to each input
element
foldM (premapM f folder) list = foldM folder (map f list)
premapM id = id premapM (f . g) = premap g . premap f
premapM k (pure r) = pure r premapM k (f <*> x) = premapM k f <*> premapM k x
pretraverse :: Traversal' a b -> Fold b r -> Fold a rSource
(pretraverse t folder)
traverses each incoming element using Traversal'
t
and folds every target of the Traversal'
pretraverse id = id pretraverse (f . g) = pretraverse f . pretraverse g
pretraverse t (pure r) = pure r pretraverse t (f <*> x) = pretraverse t f <*> pretraverse t x
pretraverseM :: Monad m => Traversal' a b -> FoldM m b r -> FoldM m a rSource
(pretraverseM t folder)
traverses each incoming element using Traversal'
t
and folds every target of the Traversal'
pretraverseM id = id pretraverseM (f . g) = pretraverseM f . pretraverseM g
pretraverseM t (pure r) = pure r pretraverseM t (f <*> x) = pretraverseM t f <*> pretraverseM t x
Re-exports
Control.Monad.Primitive
re-exports the PrimMonad
type class
Data.Foldable
re-exports the Foldable
type class
Data.Vector.Generic
re-exports the Vector
type class
module Data.Foldable