|
| Data.Foldable.Speculation |
|
|
|
|
|
| Synopsis |
|
| fold :: (Foldable f, Monoid m, Eq m) => (Int -> m) -> f m -> m | | | foldBy :: (Foldable f, Monoid m) => (m -> m -> Bool) -> (Int -> m) -> f m -> m | | | foldMap :: (Foldable f, Monoid m, Eq m) => (Int -> m) -> (a -> m) -> f a -> m | | | foldMapBy :: (Foldable f, Monoid m) => (m -> m -> Bool) -> (Int -> m) -> (a -> m) -> f a -> m | | | foldr :: (Foldable f, Eq b) => (Int -> b) -> (a -> b -> b) -> b -> f a -> b | | | foldrBy :: Foldable f => (b -> b -> Bool) -> (Int -> b) -> (a -> b -> b) -> b -> f a -> b | | | foldl :: (Foldable f, Eq b) => (Int -> b) -> (b -> a -> b) -> b -> f a -> b | | | foldlBy :: Foldable f => (b -> b -> Bool) -> (Int -> b) -> (b -> a -> b) -> b -> f a -> b | | | foldr1 :: (Foldable f, Eq a) => (Int -> a) -> (a -> a -> a) -> f a -> a | | | foldr1By :: Foldable f => (a -> a -> Bool) -> (Int -> a) -> (a -> a -> a) -> f a -> a | | | foldl1 :: (Foldable f, Eq a) => (Int -> a) -> (a -> a -> a) -> f a -> a | | | foldl1By :: Foldable f => (a -> a -> Bool) -> (Int -> a) -> (a -> a -> a) -> f a -> a | | | foldrM :: (Foldable f, Monad m, Eq (m b)) => (Int -> m b) -> (a -> b -> m b) -> m b -> f a -> m b | | | foldrByM :: (Foldable f, Monad m) => (m b -> m b -> Bool) -> (Int -> m b) -> (a -> b -> m b) -> m b -> f a -> m b | | | foldlM :: (Foldable f, Monad m, Eq (m b)) => (Int -> m b) -> (b -> a -> m b) -> m b -> f a -> m b | | | foldlByM :: (Foldable f, Monad m) => (m b -> m b -> Bool) -> (Int -> m b) -> (b -> a -> m b) -> m b -> f a -> m b | | | foldrSTM :: (Foldable f, Eq b) => (Int -> STM b) -> (a -> b -> STM b) -> STM b -> f a -> STM b | | | foldrBySTM :: Foldable f => (b -> b -> STM Bool) -> (Int -> STM b) -> (a -> b -> STM b) -> STM b -> f a -> STM b | | | foldlSTM :: (Foldable f, Eq a) => (Int -> STM a) -> (a -> b -> STM a) -> STM a -> f b -> STM a | | | foldlBySTM :: Foldable f => (a -> a -> STM Bool) -> (Int -> STM a) -> (a -> b -> STM a) -> STM a -> f b -> STM a | | | traverse_ :: (Foldable t, Applicative f, Eq (f ())) => (Int -> f c) -> (a -> f b) -> t a -> f () | | | traverseBy_ :: (Foldable t, Applicative f) => (f () -> f () -> Bool) -> (Int -> f c) -> (a -> f b) -> t a -> f () | | | for_ :: (Foldable t, Applicative f, Eq (f ())) => (Int -> f c) -> t a -> (a -> f b) -> f () | | | forBy_ :: (Foldable t, Applicative f) => (f () -> f () -> Bool) -> (Int -> f c) -> t a -> (a -> f b) -> f () | | | sequenceA_ :: (Foldable t, Applicative f, Eq (f ())) => (Int -> f b) -> t (f a) -> f () | | | sequenceByA_ :: (Foldable t, Applicative f, Eq (f ())) => (f () -> f () -> Bool) -> (Int -> f b) -> t (f a) -> f () | | | asum :: (Foldable t, Alternative f, Eq (f a)) => (Int -> f a) -> t (f a) -> f a | | | asumBy :: (Foldable t, Alternative f) => (f a -> f a -> Bool) -> (Int -> f a) -> t (f a) -> f a | | | mapM_ :: (Foldable t, Monad m, Eq (m ())) => (Int -> m c) -> (a -> m b) -> t a -> m () | | | mapByM_ :: (Foldable t, Monad m) => (m () -> m () -> Bool) -> (Int -> m c) -> (a -> m b) -> t a -> m () | | | forM_ :: (Foldable t, Monad m, Eq (m ())) => (Int -> m c) -> t a -> (a -> m b) -> m () | | | forByM_ :: (Foldable t, Monad m) => (m () -> m () -> Bool) -> (Int -> m c) -> t a -> (a -> m b) -> m () | | | sequence_ :: (Foldable t, Monad m, Eq (m ())) => (Int -> m b) -> t (m a) -> m () | | | sequenceBy_ :: (Foldable t, Monad m) => (m () -> m () -> Bool) -> (Int -> m b) -> t (m a) -> m () | | | msum :: (Foldable t, MonadPlus m, Eq (m a)) => (Int -> m a) -> t (m a) -> m a | | | msumBy :: (Foldable t, MonadPlus m) => (m a -> m a -> Bool) -> (Int -> m a) -> t (m a) -> m a | | | mapSTM_ :: Foldable t => STM Bool -> (Int -> STM c) -> (a -> STM b) -> t a -> STM () | | | forSTM_ :: Foldable t => STM Bool -> (Int -> STM c) -> t a -> (a -> STM b) -> STM () | | | sequenceSTM_ :: Foldable t => STM Bool -> (Int -> STM a) -> t (STM b) -> STM () | | | toList :: (Foldable t, Eq a) => (Int -> [a]) -> t a -> [a] | | | toListBy :: Foldable t => ([a] -> [a] -> Bool) -> (Int -> [a]) -> t a -> [a] | | | concat :: (Foldable t, Eq a) => (Int -> [a]) -> t [a] -> [a] | | | concatBy :: Foldable t => ([a] -> [a] -> Bool) -> (Int -> [a]) -> t [a] -> [a] | | | concatMap :: (Foldable t, Eq b) => (Int -> [b]) -> (a -> [b]) -> t a -> [b] | | | concatMapBy :: Foldable t => ([b] -> [b] -> Bool) -> (Int -> [b]) -> (a -> [b]) -> t a -> [b] | | | all :: Foldable t => (Int -> Bool) -> (a -> Bool) -> t a -> Bool | | | any :: Foldable t => (Int -> Bool) -> (a -> Bool) -> t a -> Bool | | | and :: Foldable t => (Int -> Bool) -> t Bool -> Bool | | | or :: Foldable t => (Int -> Bool) -> t Bool -> Bool | | | sum :: (Foldable t, Num a) => (Int -> a) -> t a -> a | | | sumBy :: (Foldable t, Num a) => (a -> a -> Bool) -> (Int -> a) -> t a -> a | | | product :: (Foldable t, Num a) => (Int -> a) -> t a -> a | | | productBy :: (Foldable t, Num a) => (a -> a -> Bool) -> (Int -> a) -> t a -> a | | | maximum :: (Foldable t, Ord a) => (Int -> a) -> t a -> a | | | maximumBy :: Foldable t => (a -> a -> Ordering) -> (Int -> a) -> t a -> a | | | minimum :: (Foldable t, Ord a) => (Int -> a) -> t a -> a | | | minimumBy :: Foldable t => (a -> a -> Ordering) -> (Int -> a) -> t a -> a | | | elem :: (Foldable t, Eq a) => (Int -> Bool) -> a -> t a -> Bool | | | elemBy :: Foldable t => (a -> a -> Bool) -> (Int -> Bool) -> a -> t a -> Bool | | | notElem :: (Foldable t, Eq a) => (Int -> Bool) -> a -> t a -> Bool | | | notElemBy :: Foldable t => (a -> a -> Bool) -> (Int -> Bool) -> a -> t a -> Bool | | | find :: (Foldable t, Eq a) => (Int -> Maybe a) -> (a -> Bool) -> t a -> Maybe a | | | findBy :: Foldable t => (Maybe a -> Maybe a -> Bool) -> (Int -> Maybe a) -> (a -> Bool) -> t a -> Maybe a |
|
|
|
| Speculative folds
|
|
|
Given a valid estimator g, fold g f xs yields the same answer as fold f xs.
g n should supply an estimate of the value of the monoidal summation over the last n elements of the container.
If g n is accurate a reasonable percentage of the time and faster to compute than the fold, then this can
provide increased opportunities for parallelism.
|
|
|
| fold using specBy
|
|
|
Given a valid estimator g, foldMap g f xs yields the same answer as foldMap f xs.
g n should supply an estimate of the value of the monoidal summation over the last n elements of the container.
If g n is accurate a reasonable percentage of the time and faster to compute than the fold, then this can
provide increased opportunities for parallelism.
|
|
|
|
|
Given a valid estimator g, foldr g f z xs yields the same answer as foldr' f z xs.
g n should supply an estimate of the value returned from folding over the last n elements of the container.
If g n is accurate a reasonable percentage of the time and faster to compute than the fold, then this can
provide increased opportunities for parallelism.
|
|
|
|
|
Given a valid estimator g, foldl g f z xs yields the same answer as foldl' f z xs.
g n should supply an estimate of the value returned from folding over the first n elements of the container.
If g n is accurate a reasonable percentage of the time and faster to compute than the fold, then this can
provide increased opportunities for parallelism.
|
|
|
|
|
|
|
|
|
|
|
|
| Speculative monadic folds
|
|
|
|
|
|
|
|
|
|
| Speculative transactional monadic folds
|
|
|
|
|
|
|
|
|
|
| Folding actions
|
|
| Applicative actions
|
|
|
| Map each element of a structure to an action, evaluate these actions
from left to right and ignore the results.
|
|
|
|
|
| for_ is traverse_ with its arguments flipped.
|
|
|
|
|
|
|
|
|
|
|
|
| Monadic actions
|
|
|
| Map each element of the structure to a monadic action, evaluating these actions
from left to right and ignoring the results.
|
|
|
|
|
| for_ is mapM_ with its arguments flipped.
|
|
|
|
|
|
|
|
|
|
|
|
| Speculative transactional monadic actions
|
|
|
| Map each element of the structure to a monadic action, evaluating these actions
from left to right and ignoring the results, while transactional side-effects from
mis-speculated actions are rolled back.
|
|
|
| for_ is mapM_ with its arguments flipped.
|
|
|
|
| Specialized folds
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Searches
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| Produced by Haddock version 2.6.1 |