| Safe Haskell | Trustworthy | 
|---|
Control.Foldl
Description
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
Folds are Applicatives, 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 [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)
- 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
- 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
- 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)
- 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)
- 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
- purely_ :: (forall x. (x -> a -> x) -> x -> x) -> Fold a b -> b
- impurely :: Monad m => (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 :: Monad m => (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 :: (a -> b) -> FoldM m b r -> FoldM m a r
- type Handler a b = forall x. (b -> Constant (Endo x) b) -> a -> Constant (Endo x) a
- handles :: Handler a b -> Fold b r -> Fold a r
- newtype  EndoM m a = EndoM {- appEndoM :: a -> m a
 
- type HandlerM m a b = forall x. (b -> Constant (EndoM m x) b) -> a -> Constant (EndoM m x) a
- handlesM :: Monad m => HandlerM m a b -> FoldM m b r -> FoldM m a 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__.
Constructors
| forall x . Fold (x -> a -> x) x (x -> b) | 
 | 
Instances
| Profunctor Fold | |
| Functor (Fold a) | |
| Applicative (Fold a) | |
| Comonad (Fold a) | |
| Floating b => Floating (Fold a b) | |
| Fractional b => Fractional (Fold a b) | |
| Num b => Num (Fold a b) | |
| Monoid b => Monoid (Fold a b) | 
Like Fold, but monadic.
A 'FoldM m a b' processes elements of type __a__ and
    results in a monadic value of type __m b__.
Constructors
| forall x . FoldM (x -> a -> m x) (m x) (x -> m 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 nth 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
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 wSource
Converts an effectful function to a fold
sink (f <> g) = sink f <> sink g -- if `(<>)` is commutative sink mempty = mempty
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
purely_ :: (forall x. (x -> a -> x) -> x -> x) -> Fold a b -> bSource
Upgrade a more traditional 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
impurely_ :: Monad m => (forall x. (x -> a -> m x) -> m x -> m x) -> FoldM m a b -> m bSource
Upgrade a more traditional monadic fold to accept the FoldM type
generalize :: Monad m => Fold a b -> FoldM m a bSource
duplicateM :: Applicative m => FoldM m a b -> FoldM m a (FoldM m a b)Source
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)
>>>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 :: (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
handles :: Handler a b -> Fold b r -> Fold a rSource
(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
>>>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,3,5,7,21,21]42
>>>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
 instance Monad m => Monoid (EndoM m a) where
     mempty = EndoM return
     mappend (EndoM f) (EndoM g) = EndoM (f >=> g)
handlesM :: Monad m => HandlerM m a b -> FoldM m b r -> FoldM m a rSource
(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 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
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