Safe Haskell | Trustworthy |
---|---|
Language | Haskell98 |
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
Taking the sum, the sum of squares, ..., upto the sum of x^5
>>>
import Data.Traversable
>>>
let powerSums = sequenceA [L.premap (^n) L.sum | n <- [1..5]]
>>>
L.fold powerSums [1..10]
[55,385,3025,25333,220825]
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)
You might want to try enabling the -flate-dmd-anal
flag when compiling
executables that use this library to further improve performance.
- data Fold a b = Fold (x -> a -> x) x (x -> b)
- data FoldM m a b = 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]
- prescan :: Traversable t => Fold a b -> t a -> t b
- postscan :: Traversable t => Fold a b -> t a -> t 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
- lastN :: Int -> 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
- mean :: Fractional a => Fold a a
- variance :: Fractional a => Fold a a
- std :: Floating a => Fold a a
- maximum :: Ord a => Fold a (Maybe a)
- maximumBy :: (a -> a -> Ordering) -> Fold a (Maybe a)
- minimum :: Ord a => Fold a (Maybe a)
- minimumBy :: (a -> a -> Ordering) -> 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)
- lookup :: Eq a => a -> Fold (a, b) (Maybe b)
- elemIndex :: Eq a => a -> Fold a (Maybe Int)
- findIndex :: (a -> Bool) -> Fold a (Maybe Int)
- random :: FoldM IO a (Maybe a)
- randomN :: Vector v a => Int -> FoldM IO a (Maybe (v a))
- mapM_ :: Monad m => (a -> m ()) -> FoldM m a ()
- sink :: (Monoid w, Monad m) => (a -> m w) -> FoldM m a w
- genericLength :: Num b => Fold a b
- genericIndex :: Integral i => i -> Fold a (Maybe a)
- list :: Fold a [a]
- revList :: Fold a [a]
- nub :: Ord a => Fold a [a]
- eqNub :: Eq a => Fold a [a]
- set :: Ord a => Fold a (Set a)
- hashSet :: (Eq a, Hashable a) => Fold a (HashSet a)
- map :: Ord a => Fold (a, b) (Map a b)
- hashMap :: (Eq a, Hashable a) => Fold (a, b) (HashMap a b)
- vector :: Vector v a => Fold a (v a)
- vectorM :: (PrimMonad m, Vector v a) => FoldM m a (v a)
- purely :: (forall x. (x -> a -> x) -> x -> (x -> b) -> r) -> Fold a b -> r
- purely_ :: (forall x. (x -> a -> x) -> x -> x) -> Fold a b -> b
- impurely :: (forall x. (x -> a -> m x) -> m x -> (x -> m b) -> r) -> FoldM m a b -> r
- impurely_ :: Monad m => (forall x. (x -> a -> m x) -> m x -> m x) -> FoldM m a b -> m b
- generalize :: Monad m => Fold a b -> FoldM m a b
- simplify :: FoldM Identity a b -> Fold a b
- hoists :: (forall x. m x -> n x) -> FoldM m a b -> FoldM n a b
- duplicateM :: Applicative m => FoldM m a b -> FoldM m a (FoldM m a b)
- _Fold1 :: (a -> a -> a) -> Fold a (Maybe a)
- premap :: (a -> b) -> Fold b r -> Fold a r
- premapM :: Monad m => (a -> m b) -> FoldM m b r -> FoldM m a r
- prefilter :: (a -> Bool) -> Fold a r -> Fold a r
- prefilterM :: Monad m => (a -> m Bool) -> FoldM m a r -> FoldM m a r
- type Handler a b = forall x. (b -> Const (Dual (Endo x)) b) -> a -> Const (Dual (Endo x)) a
- handles :: Handler a b -> Fold b r -> Fold a r
- foldOver :: Handler s a -> Fold a b -> s -> b
- newtype EndoM m a = EndoM {
- appEndoM :: a -> m a
- type HandlerM m a b = forall x. (b -> Const (Dual (EndoM m x)) b) -> a -> Const (Dual (EndoM m x)) a
- handlesM :: HandlerM m a b -> FoldM m b r -> FoldM m a r
- foldOverM :: Monad m => HandlerM m s a -> FoldM m a b -> s -> m b
- folded :: (Contravariant f, Applicative f, Foldable t) => (a -> f a) -> t a -> f (t a)
- filtered :: Monoid m => (a -> Bool) -> (a -> m) -> a -> m
- groupBy :: Ord g => (a -> g) -> Fold a r -> Fold a (Map g r)
- module Control.Monad.Primitive
- module Data.Foldable
- module Data.Vector.Generic
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
A 'Fold
a b' processes elements of type a and results in a
value of type b.
Fold (x -> a -> x) x (x -> b) |
|
Choice Fold Source # | |
Profunctor Fold Source # | |
Functor (Fold a) Source # | |
Applicative (Fold a) Source # | |
Comonad (Fold a) Source # | |
Floating b => Floating (Fold a b) Source # | |
Fractional b => Fractional (Fold a b) Source # | |
Num b => Num (Fold a b) Source # | |
Monoid b => Semigroup (Fold a b) Source # | |
Monoid b => Monoid (Fold a b) Source # | |
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 (x -> a -> m x) (m x) (x -> m b) |
|
Monad m => Profunctor (FoldM m) Source # | |
Monad m => Functor (FoldM m a) Source # | |
Monad m => Applicative (FoldM m a) Source # | |
(Monad m, Floating b) => Floating (FoldM m a b) Source # | |
(Monad m, Fractional b) => Fractional (FoldM m a b) Source # | |
(Monad m, Num b) => Num (FoldM m a b) Source # | |
(Monoid b, Monad m) => Semigroup (FoldM m a b) Source # | |
(Monoid b, Monad m) => Monoid (FoldM m a b) Source # | |
Folding
prescan :: Traversable t => Fold a b -> t a -> t b Source #
Convert a Fold
into a prescan for any Traversable
type
"Prescan" means that the last element of the scan is not included
postscan :: Traversable t => Fold a b -> t a -> t b Source #
Convert a Fold
into a postscan for any Traversable
type
"Postscan" means that the first element of the scan is not included
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 a Source #
Get the last element of a container or return a default value if the container is empty
mean :: Fractional a => Fold a a Source #
Compute a numerically stable arithmetic mean of all elements
variance :: Fractional a => Fold a a Source #
Compute a numerically stable (population) variance over all elements
std :: Floating a => Fold a a Source #
Compute a numerically stable (population) standard deviation over all elements
maximumBy :: (a -> a -> Ordering) -> Fold a (Maybe a) Source #
Computes the maximum element with respect to the given comparison function
minimumBy :: (a -> a -> Ordering) -> Fold a (Maybe a) Source #
Computes the minimum element with respect to the given comparison function
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
lookup :: Eq a => a -> Fold (a, b) (Maybe b) Source #
(lookup a)
returns the element paired with the first matching item, or
Nothing
if none matches
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
randomN :: Vector v a => Int -> FoldM IO a (Maybe (v a)) Source #
Pick several random elements, using reservoir sampling
mapM_ :: Monad m => (a -> m ()) -> FoldM m a () Source #
Converts an effectful function to a fold. Specialized version of sink
.
sink :: (Monoid w, Monad m) => (a -> m w) -> FoldM m a w Source #
Converts an effectful function to a fold
sink (f <> g) = sink f <> sink g -- if `(<>)` is commutative sink mempty = mempty
Generic Folds
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
vectorM :: (PrimMonad m, Vector v a) => FoldM m a (v a) Source #
Fold all values into a vector
This is more efficient than vector
but is impure
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 fold
and foldM
functions in
Pipes.Prelude
with the following type:
Pipes.Prelude.fold :: Monad m -> (x -> a -> x) -> x -> (x -> b) -> Producer a m () -> m b Pipes.Prelude.foldM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Producer a m () -> m b
Both fold
and foldM
is set up so that you can wrap them with either
purely
or impurely
to accept a Fold
or FoldM
, respectively:
purely Pipes.Prelude.fold :: Monad m => Fold a b -> Producer a m () -> m b impurely Pipes.Prelude.foldM :: Monad m => FoldM m a b -> Producer a m () -> m b
Other streaming libraries supporting purely
and impurely
include io-streams
and streaming
.
So for example we have:
purely System.IO.Streams.fold_ :: Fold a b -> Streams.InputStream a -> IO b impurely System.IO.Streams.foldM_ :: FoldM IO a b -> Streams.InputStream a -> IO b
The monotraversable
package makes it convenient to apply a
Fold
or FoldM
to pure containers that do not allow
a general Foldable
instance, like unboxed vectors:
purely ofoldlUnwrap :: MonoFoldable mono => Fold (Element mono) b -> mono -> b impurely ofoldMUnwrap :: MonoFoldable mono => FoldM m (Element mono) b -> mono -> m b
purely :: (forall x. (x -> a -> x) -> x -> (x -> b) -> r) -> Fold a b -> r Source #
Upgrade a fold to accept the Fold
type
purely_ :: (forall x. (x -> a -> x) -> x -> x) -> Fold a b -> b Source #
Upgrade a more traditional fold to accept the Fold
type
impurely :: (forall x. (x -> a -> m x) -> m x -> (x -> m b) -> r) -> FoldM m a b -> r Source #
Upgrade a monadic fold to accept the FoldM
type
impurely_ :: Monad m => (forall x. (x -> a -> m x) -> m x -> m x) -> FoldM m a b -> m b Source #
Upgrade a more traditional monadic fold to accept the FoldM
type
duplicateM :: Applicative m => FoldM m a b -> FoldM m a (FoldM m a b) Source #
premap :: (a -> b) -> Fold b r -> Fold a r Source #
(premap f folder)
returns a new Fold
where f is applied at each step
fold (premap f folder) list = fold folder (map f list)
>>>
fold (premap Sum mconcat) [1..10]
Sum {getSum = 55}
>>>
fold mconcat (map Sum [1..10])
Sum {getSum = 55}
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 -> m b) -> FoldM m b r -> FoldM m a r Source #
(premapM f folder)
returns a new FoldM
where f is applied to each input
element
premapM return = id premapM (f <=< g) = premap g . premap f
premapM k (pure r) = pure r premapM k (f <*> x) = premapM k f <*> premapM k x
prefilter :: (a -> Bool) -> Fold a r -> Fold a r Source #
(prefilter f folder)
returns a new Fold
where the folder's input is used
only when the input satisfies a predicate f
This can also be done with handles
(handles (filtered f)
) but prefilter
does not need you to depend on a lens library.
fold (prefilter p folder) list = fold folder (filter p list)
>>>
fold (prefilter (>5) Control.Foldl.sum) [1..10]
40
>>>
fold Control.Foldl.sum (filter (>5) [1..10])
40
prefilterM :: Monad m => (a -> m Bool) -> FoldM m a r -> FoldM m a r Source #
(prefilterM f folder)
returns a new Fold
where the folder's input is used
only when the input satisfies a monadic predicate f.
foldM (prefilterM p folder) list = foldM folder (filter p list)
type Handler a b = forall x. (b -> Const (Dual (Endo x)) b) -> a -> Const (Dual (Endo x)) a Source #
handles :: Handler a b -> Fold b r -> Fold a r Source #
(handles t folder)
transforms the input of a Fold
using a lens,
traversal, or prism:
handles _1 :: Fold a r -> Fold (a, b) r handles _Left :: Fold a r -> Fold (Either a b) r handles traverse :: Traversable t => Fold a r -> Fold (t a) r handles folded :: Foldable t => Fold a r -> Fold (t a) r
>>>
fold (handles traverse sum) [[1..5],[6..10]]
55
>>>
fold (handles (traverse.traverse) sum) [[Nothing, Just 2, Just 7],[Just 13, Nothing, Just 20]]
42
>>>
fold (handles (filtered even) sum) [1..10]
30
>>>
fold (handles _2 mconcat) [(1,"Hello "),(2,"World"),(3,"!")]
"Hello World!"
handles id = id handles (f . g) = handles f . handles g
handles t (pure r) = pure r handles t (f <*> x) = handles t f <*> handles t x
foldOver :: Handler s a -> Fold a b -> s -> b Source #
(foldOver f folder xs)
folds all values from a Lens, Traversal, Prism or Fold with the given folder
>>>
foldOver (_Just . both) L.sum (Just (2, 3))
5
>>>
foldOver (_Just . both) L.sum Nothing
0
L.foldOver f folder xs == L.fold folder (xs^..f)
L.foldOver (folded.f) folder == L.fold (handles f folder)
L.foldOver folded == L.fold
instance Monad m => Monoid (EndoM m a) where mempty = EndoM return mappend (EndoM f) (EndoM g) = EndoM (f <=< g)
type HandlerM m a b = forall x. (b -> Const (Dual (EndoM m x)) b) -> a -> Const (Dual (EndoM m x)) a Source #
handlesM :: HandlerM m a b -> FoldM m b r -> FoldM m a r Source #
(handlesM t folder)
transforms the input of a FoldM
using a lens,
traversal, or prism:
handlesM _1 :: FoldM m a r -> FoldM (a, b) r handlesM _Left :: FoldM m a r -> FoldM (Either a b) r handlesM traverse :: Traversable t => FoldM m a r -> FoldM m (t a) r handlesM folded :: Foldable t => FoldM m a r -> FoldM m (t a) r
handlesM
obeys these laws:
handlesM id = id handlesM (f . g) = handlesM f . handlesM g
handlesM t (pure r) = pure r handlesM t (f <*> x) = handlesM t f <*> handlesM t x
foldOverM :: Monad m => HandlerM m s a -> FoldM m a b -> s -> m b Source #
(foldOverM f folder xs)
folds all values from a Lens, Traversal, Prism or Fold monadically with the given folder
L.foldOverM (folded.f) folder == L.foldM (handlesM f folder)
L.foldOverM folded == L.foldM
folded :: (Contravariant f, Applicative f, Foldable t) => (a -> f a) -> t a -> f (t a) Source #
folded :: Foldable t => Fold (t a) a handles folded :: Foldable t => Fold a r -> Fold (t a) r
filtered :: Monoid m => (a -> Bool) -> (a -> m) -> a -> m Source #
>>>
fold (handles (filtered even) sum) [1..10]
30
>>>
foldM (handlesM (filtered even) (mapM_ print)) [1..10]
2 4 6 8 10
groupBy :: Ord g => (a -> g) -> Fold a r -> Fold a (Map g r) Source #
Perform a Fold
while grouping the data according to a specified group
projection function. Returns the folded result grouped as a map keyed by the
group.
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 Control.Monad.Primitive
module Data.Foldable
module Data.Vector.Generic