monoids-0.1.20: Monoids, specialized containers and a general map/reduce frameworkSource codeContentsIndex
Data.Monoid.Combinators
Portabilitynon-portable (type families, MPTCs)
Stabilityexperimental
Maintainerekmett@gmail.com
Contents
Monadic Reduction
Applicative Reduction
Logical Reduction
Monoidal Reduction
List-Like Reduction
List-Like Monoid Production
QuickCheck Properties
Description

Utilities for working with Monoids that conflict with names from the Prelude, Data.Foldable, Control.Monad or elsewhere. Intended to be imported qualified.

 import Data.Group.Combinators as Monoid 
Synopsis
module Data.Monoid.Generator
mapM_ :: (Generator c, Monad m) => (Elem c -> m b) -> c -> m ()
forM_ :: (Generator c, Monad m) => c -> (Elem c -> m b) -> m ()
msum :: (Generator c, MonadPlus m, m a ~ Elem c) => c -> m a
traverse_ :: (Generator c, Applicative f) => (Elem c -> f b) -> c -> f ()
for_ :: (Generator c, Applicative f) => c -> (Elem c -> f b) -> f ()
asum :: (Generator c, Alternative f, f a ~ Elem c) => c -> f a
and :: (Generator c, Elem c ~ Bool) => c -> Bool
or :: (Generator c, Elem c ~ Bool) => c -> Bool
any :: Generator c => (Elem c -> Bool) -> c -> Bool
all :: Generator c => (Elem c -> Bool) -> c -> Bool
foldMap :: (Monoid m, Generator c) => (Elem c -> m) -> c -> m
fold :: (Monoid m, Generator c, Elem c ~ m) => c -> m
toList :: Generator c => c -> [Elem c]
concatMap :: Generator c => (Elem c -> [b]) -> c -> [b]
elem :: (Generator c, Eq (Elem c)) => Elem c -> c -> Bool
filter :: (Generator c, Reducer (Elem c) m) => (Elem c -> Bool) -> c -> m
filterWith :: (Generator c, Reducer (Elem c) m) => (m -> n) -> (Elem c -> Bool) -> c -> n
find :: Generator c => (Elem c -> Bool) -> c -> Maybe (Elem c)
sum :: (Generator c, Num (Elem c)) => c -> Elem c
product :: (Generator c, Num (Elem c)) => c -> Elem c
notElem :: (Generator c, Eq (Elem c)) => Elem c -> c -> Bool
repeat :: Reducer e m => e -> m
replicate :: (Monoid m, Integral n) => m -> n -> m
cycle :: Monoid m => m -> m
prop_replicate_right_distributive :: (Eq m, Monoid m, Arbitrary m, Integral n) => m -> n -> n -> Bool
Documentation
module Data.Monoid.Generator
Monadic Reduction
mapM_ :: (Generator c, Monad m) => (Elem c -> m b) -> c -> m ()Source

Efficiently mapReduce a Generator using the Action monoid. A specialized version of its namesake from Data.Foldable and Control.Monad

    mapReduceWith getAction
forM_ :: (Generator c, Monad m) => c -> (Elem c -> m b) -> m ()Source

Convenience function as found in Data.Foldable and Control.Monad

     flip mapM_
msum :: (Generator c, MonadPlus m, m a ~ Elem c) => c -> m aSource

The sum of a collection of actions, generalizing concat

     reduceWith getMonadSum
Applicative Reduction
traverse_ :: (Generator c, Applicative f) => (Elem c -> f b) -> c -> f ()Source

Efficiently mapReduce a Generator using the Traversal monoid. A specialized version of its namesake from Data.Foldable

     mapReduce getTraversal
for_ :: (Generator c, Applicative f) => c -> (Elem c -> f b) -> f ()Source

Convenience function as found in Data.Foldable

     flip traverse_
asum :: (Generator c, Alternative f, f a ~ Elem c) => c -> f aSource

The sum of a collection of actions, generalizing concat

    reduceWith getAlt
Logical Reduction
and :: (Generator c, Elem c ~ Bool) => c -> BoolSource

Efficiently reduce a Generator that contains values of type Bool

     reduceWith getAll
or :: (Generator c, Elem c ~ Bool) => c -> BoolSource

Efficiently reduce a Generator that contains values of type Bool

     reduceWith getAny
any :: Generator c => (Elem c -> Bool) -> c -> BoolSource

Efficiently mapReduce any Generator checking to see if any of its values match the supplied predicate

     mapReduceWith getAny
all :: Generator c => (Elem c -> Bool) -> c -> BoolSource

Efficiently mapReduce any Generator checking to see if all of its values match the supplied predicate

     mapReduceWith getAll
Monoidal Reduction
foldMap :: (Monoid m, Generator c) => (Elem c -> m) -> c -> mSource

Efficiently mapReduce a Generator using the Self monoid. A specialized version of its namesake from Data.Foldable

     mapReduceWith getSelf
fold :: (Monoid m, Generator c, Elem c ~ m) => c -> mSource

Efficiently reduce a Generator using the Self monoid. A specialized version of its namesake from Data.Foldable

     reduceWith getSelf
toList :: Generator c => c -> [Elem c]Source
Convert any Generator to a list of its contents. Specialization of reduce
List-Like Reduction
concatMap :: Generator c => (Elem c -> [b]) -> c -> [b]Source
Type specialization of foldMap above
elem :: (Generator c, Eq (Elem c)) => Elem c -> c -> BoolSource
Check to see if any member of the Generator matches the supplied value
filter :: (Generator c, Reducer (Elem c) m) => (Elem c -> Bool) -> c -> mSource
Efficiently mapReduce a subset of the elements in a Generator
filterWith :: (Generator c, Reducer (Elem c) m) => (m -> n) -> (Elem c -> Bool) -> c -> nSource
Allows idiomatic specialization of filter by proving a function that will be used to transform the output
find :: Generator c => (Elem c -> Bool) -> c -> Maybe (Elem c)Source

A specialization of filter using the First Monoid, analogous to Data.List.find

     filterWith getFirst
sum :: (Generator c, Num (Elem c)) => c -> Elem cSource

Efficiently sum over the members of any Generator

     reduceWith getSum
product :: (Generator c, Num (Elem c)) => c -> Elem cSource

Efficiently take the product of every member of a Generator

     reduceWith getProduct
notElem :: (Generator c, Eq (Elem c)) => Elem c -> c -> BoolSource
Check to make sure that the supplied value is not a member of the Generator
List-Like Monoid Production
repeat :: Reducer e m => e -> mSource
A generalization of Data.List.repeat to an arbitrary Monoid. May fail to terminate for some values in some monoids.
replicate :: (Monoid m, Integral n) => m -> n -> mSource
A generalization of Data.List.replicate to an arbitrary Monoid. Adapted from http://augustss.blogspot.com/2008/07/lost-and-found-if-i-write-108-in.html
cycle :: Monoid m => m -> mSource
A generalization of Data.List.cycle to an arbitrary Monoid. May fail to terminate for some values in some monoids.
QuickCheck Properties
prop_replicate_right_distributive :: (Eq m, Monoid m, Arbitrary m, Integral n) => m -> n -> n -> BoolSource
Produced by Haddock version 2.4.1