speculation-0.4.0: A framework for safe, programmable, speculative parallelism

Data.Foldable.Speculation

Contents

Synopsis

Speculative folds

fold :: (Foldable f, Monoid m, Eq m) => (Int -> m) -> f m -> mSource

Given a valid estimate 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.

foldBy :: (Foldable f, Monoid m) => (m -> m -> Bool) -> (Int -> m) -> f m -> mSource

fold using specBy

foldMap :: (Foldable f, Monoid m, Eq m) => (Int -> m) -> (a -> m) -> f a -> mSource

Given a valid estimate 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.

foldMapBy :: (Foldable f, Monoid m) => (m -> m -> Bool) -> (Int -> m) -> (a -> m) -> f a -> mSource

foldr :: (Foldable f, Eq b) => (Int -> b) -> (a -> b -> b) -> b -> f a -> bSource

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.

foldrBy :: Foldable f => (b -> b -> Bool) -> (Int -> b) -> (a -> b -> b) -> b -> f a -> bSource

foldl :: (Foldable f, Eq b) => (Int -> b) -> (b -> a -> b) -> b -> f a -> bSource

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.

foldlBy :: Foldable f => (b -> b -> Bool) -> (Int -> b) -> (b -> a -> b) -> b -> f a -> bSource

foldr1 :: (Foldable f, Eq a) => (Int -> a) -> (a -> a -> a) -> f a -> aSource

foldr1By :: Foldable f => (a -> a -> Bool) -> (Int -> a) -> (a -> a -> a) -> f a -> aSource

foldl1 :: (Foldable f, Eq a) => (Int -> a) -> (a -> a -> a) -> f a -> aSource

foldl1By :: Foldable f => (a -> a -> Bool) -> (Int -> a) -> (a -> a -> a) -> f a -> aSource

traverse_ :: (Foldable t, Applicative f, Eq (f ())) => (Int -> f c) -> (a -> f b) -> t a -> f ()Source

Map each element of a structure to an action, evaluate these actions from left to right and ignore the results.

traverseBy_ :: (Foldable t, Applicative f) => (f () -> f () -> Bool) -> (Int -> f c) -> (a -> f b) -> t a -> f ()Source

for_ :: (Foldable t, Applicative f, Eq (f ())) => (Int -> f c) -> t a -> (a -> f b) -> f ()Source

for_ is traverse_ with its arguments flipped.

forBy_ :: (Foldable t, Applicative f) => (f () -> f () -> Bool) -> (Int -> f c) -> t a -> (a -> f b) -> f ()Source

mapM_ :: (Foldable t, Monad m, Eq (m ())) => (Int -> m c) -> (a -> m b) -> t a -> m ()Source

Map each element of the structure to a monadic action, evaluating these actions from left to right and ignore the results.

mapMBy_ :: (Foldable t, Monad m) => (m () -> m () -> Bool) -> (Int -> m c) -> (a -> m b) -> t a -> m ()Source

forM_ :: (Foldable t, Monad m, Eq (m ())) => (Int -> m c) -> t a -> (a -> m b) -> m ()Source

for_ is mapM_ with its arguments flipped.

forMBy_ :: (Foldable t, Monad m) => (m () -> m () -> Bool) -> (Int -> m c) -> t a -> (a -> m b) -> m ()Source

sequenceA_ :: (Foldable t, Applicative f, Eq (f ())) => (Int -> f b) -> t (f a) -> f ()Source

sequenceABy_ :: (Foldable t, Applicative f, Eq (f ())) => (f () -> f () -> Bool) -> (Int -> f b) -> t (f a) -> f ()Source

sequence_ :: (Foldable t, Monad m, Eq (m ())) => (Int -> m b) -> t (m a) -> m ()Source

sequenceBy_ :: (Foldable t, Monad m) => (m () -> m () -> Bool) -> (Int -> m b) -> t (m a) -> m ()Source

asum :: (Foldable t, Alternative f, Eq (f a)) => (Int -> f a) -> t (f a) -> f aSource

asumBy :: (Foldable t, Alternative f) => (f a -> f a -> Bool) -> (Int -> f a) -> t (f a) -> f aSource

msum :: (Foldable t, MonadPlus m, Eq (m a)) => (Int -> m a) -> t (m a) -> m aSource

msumBy :: (Foldable t, MonadPlus m) => (m a -> m a -> Bool) -> (Int -> m a) -> t (m a) -> m aSource

toList :: (Foldable t, Eq a) => (Int -> [a]) -> t a -> [a]Source

toListBy :: Foldable t => ([a] -> [a] -> Bool) -> (Int -> [a]) -> t a -> [a]Source

concat :: (Foldable t, Eq a) => (Int -> [a]) -> t [a] -> [a]Source

concatBy :: Foldable t => ([a] -> [a] -> Bool) -> (Int -> [a]) -> t [a] -> [a]Source

concatMap :: (Foldable t, Eq b) => (Int -> [b]) -> (a -> [b]) -> t a -> [b]Source

concatMapBy :: Foldable t => ([b] -> [b] -> Bool) -> (Int -> [b]) -> (a -> [b]) -> t a -> [b]Source

all :: Foldable t => (Int -> Bool) -> (a -> Bool) -> t a -> BoolSource

any :: Foldable t => (Int -> Bool) -> (a -> Bool) -> t a -> BoolSource

and :: Foldable t => (Int -> Bool) -> t Bool -> BoolSource

or :: Foldable t => (Int -> Bool) -> t Bool -> BoolSource

sum :: (Foldable t, Num a) => (Int -> a) -> t a -> aSource

sumBy :: (Foldable t, Num a) => (a -> a -> Bool) -> (Int -> a) -> t a -> aSource

product :: (Foldable t, Num a) => (Int -> a) -> t a -> aSource

productBy :: (Foldable t, Num a) => (a -> a -> Bool) -> (Int -> a) -> t a -> aSource

maximum :: (Foldable t, Ord a) => (Int -> a) -> t a -> aSource

maximumBy :: Foldable t => (a -> a -> Ordering) -> (Int -> a) -> t a -> aSource

minimum :: (Foldable t, Ord a) => (Int -> a) -> t a -> aSource

minimumBy :: Foldable t => (a -> a -> Ordering) -> (Int -> a) -> t a -> aSource

elem :: (Foldable t, Eq a) => (Int -> Bool) -> a -> t a -> BoolSource

elemBy :: Foldable t => (a -> a -> Bool) -> (Int -> Bool) -> a -> t a -> BoolSource

notElem :: (Foldable t, Eq a) => (Int -> Bool) -> a -> t a -> BoolSource

notElemBy :: Foldable t => (a -> a -> Bool) -> (Int -> Bool) -> a -> t a -> BoolSource

find :: (Foldable t, Eq a) => (Int -> Maybe a) -> (a -> Bool) -> t a -> Maybe aSource

findBy :: Foldable t => (Maybe a -> Maybe a -> Bool) -> (Int -> Maybe a) -> (a -> Bool) -> t a -> Maybe aSource