reducers-3.0.0.1: Semigroups, specialized containers and a general map/reduce framework

Portabilitynon-portable (MPTCs)
Stabilityexperimental
Maintainerekmett@gmail.com
Safe HaskellNone

Data.Semigroup.Reducer

Description

A c-Reducer is a Semigroup with a canonical mapping from c to the Semigroup.

Synopsis

Documentation

class Semigroup m => Reducer c m whereSource

This type may be best read infix. A c Reducer m is a Semigroup m that maps values of type c through unit to values of type m. A c-Reducer may also supply operations which tack-on another c to an existing Monoid m on the left or right. These specialized reductions may be more efficient in some scenarios and are used when appropriate by a Generator. The names cons and snoc work by analogy to the synonymous operations in the list monoid.

This class deliberately avoids functional-dependencies, so that () can be a c-Reducer for all c, and so many common reducers can work over multiple types, for instance, First and Last may reduce both a and Maybe a. Since a Generator has a fixed element type, the input to the reducer is generally known and extracting from the monoid usually is sufficient to fix the result type. Combinators are available for most scenarios where this is not the case, and the few remaining cases can be handled by using an explicit type annotation.

Minimal definition: unit or snoc

Methods

unit :: c -> mSource

Convert a value into a Semigroup

snoc :: m -> c -> mSource

Append a value to a Semigroup for use in left-to-right reduction

cons :: c -> m -> mSource

Prepend a value onto a Semigroup for use during right-to-left reduction

Instances

Reducer Bool All 
Reducer Bool Any 
Reducer Int IntSet 
Semigroup () => Reducer c () 
Semigroup Count => Reducer a Count 
(Semigroup (WrappedMonoid m), Monoid m) => Reducer m (WrappedMonoid m) 
(Semigroup (Set a), Ord a) => Reducer a (Set a) 
Semigroup (Seq a) => Reducer a (Seq a) 
Semigroup (Last a) => Reducer a (Last a) 
Semigroup (First a) => Reducer a (First a) 
(Semigroup (Max a), Ord a) => Reducer a (Max a) 
(Semigroup (Min a), Ord a) => Reducer a (Min a) 
(Semigroup (Product a), Num a) => Reducer a (Product a) 
(Semigroup (Sum a), Num a) => Reducer a (Sum a) 
(Semigroup (Dual a), Semigroup a) => Reducer a (Dual a) 
Semigroup [c] => Reducer c [c] 
(Semigroup (Union f), HasUnion f) => Reducer f (Union f) 
(Semigroup (Self m), Semigroup m) => Reducer m (Self m) 
(Semigroup (FingerTree v a), Measured v a) => Reducer a (FingerTree v a) 
(Semigroup (m, n), Reducer c m, Reducer c n) => Reducer c (m, n) 
(Semigroup (m, n, o), Reducer c m, Reducer c n, Reducer c o) => Reducer c (m, n, o) 
(Semigroup (m, n, o, p), Reducer c m, Reducer c n, Reducer c o, Reducer c p) => Reducer c (m, n, o, p) 
(Semigroup (Traversal f), Applicative f) => Reducer (f a) (Traversal f) 
(Semigroup (Action f), Monad f) => Reducer (f a) (Action f) 
(Semigroup (Trav f), Apply f) => Reducer (f a) (Trav f) 
Semigroup (Last a) => Reducer (Maybe a) (Last a) 
Semigroup (First a) => Reducer (Maybe a) (First a) 
(Semigroup (Ap f m), Applicative f, Reducer c m) => Reducer (f c) (Ap f m) 
(Semigroup (Alternate f a), Alternative f) => Reducer (f a) (Alternate f a) 
(Semigroup (Mon f m), Monad f, Reducer c m) => Reducer (f c) (Mon f m) 
(Semigroup (MonadSum f a), MonadPlus f) => Reducer (f a) (MonadSum f a) 
(Semigroup (UnionWith f m), HasUnionWith f, Semigroup m, Monoid m) => Reducer (f m) (UnionWith f m) 
(Semigroup (App f m), Apply f, Reducer c m) => Reducer (f c) (App f m) 
(Semigroup (Alter f a), Alt f) => Reducer (f a) (Alter f a) 
(Semigroup m, Reducer c m) => Reducer (WithReducer m c) m 
Semigroup (Endo a) => Reducer (a -> a) (Endo a) 
Semigroup (IntMap v) => Reducer (Int, v) (IntMap v) 
(Semigroup (Map k v), Ord k) => Reducer (k, v) (Map k v) 

foldMapReduce :: (Foldable f, Monoid m, Reducer e m) => (a -> e) -> f a -> mSource

Apply a Reducer to a Foldable container, after mapping the contents into a suitable form for reduction.

foldMapReduce1 :: (Foldable1 f, Reducer e m) => (a -> e) -> f a -> mSource

foldReduce :: (Foldable f, Monoid m, Reducer e m) => f e -> mSource

Apply a Reducer to a Foldable mapping each element through unit

foldReduce1 :: (Foldable1 f, Reducer e m) => f e -> mSource

Apply a Reducer to a Foldable1 mapping each element through unit

pureUnit :: (Applicative f, Reducer c n) => c -> f nSource

returnUnit :: (Monad m, Reducer c n) => c -> m nSource