monoids-0.1.25: Monoids, specialized containers and a general map/reduce frameworkSource codeContentsIndex
Data.Monoid.Reducer
Portabilitynon-portable (MPTCs)
Stabilityexperimental
Maintainerekmett@gmail.com
Description
A c-Reducer is a Monoid with a canonical mapping from c to the Monoid. This unit acts in many ways like return for a Monad but is limited to a single type.
Synopsis
module Data.Monoid
class Monoid m => Reducer c m where
unit :: c -> m
snoc :: m -> c -> m
cons :: c -> m -> m
foldMapReduce :: (Foldable f, Reducer e m) => (a -> e) -> f a -> m
foldReduce :: (Foldable f, Reducer e m) => f e -> m
pureUnit :: (Applicative f, Reducer c n) => c -> f n
returnUnit :: (Monad m, Reducer c n) => c -> m n
data ReducedBy m s = Reduction {
getReduction :: m
}
Documentation
module Data.Monoid
class Monoid m => Reducer c m whereSource

This type may be best read infix. A c Reducer m is a Monoid 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 Monoid
snoc :: m -> c -> mSource
Append a value to a Monoid for use in left-to-right reduction
cons :: c -> m -> mSource
Prepend a value onto a Monoid for use during right-to-left reduction
show/hide Instances
Reducer Bool All
Reducer Bool All
Reducer Bool Any
Reducer Bool Any
Reducer Bool BoolRing
Reducer Bool BoolRing
Reducer Int IntSet
Reducer Int IntSet
Reducer c ()
Reducer Char (SourcePosition file)
Reducer Char (SourcePosition file)
Reducer Char m => Reducer Char (Unlined m)
Reducer Char m => Reducer Char (Unlined m)
Reducer Char m => Reducer Char (Unspaced m)
Reducer Char m => Reducer Char (Unspaced m)
Reducer Char m => Reducer Char (Lines m)
Reducer Char m => Reducer Char (Lines m)
Reducer Char m => Reducer Char (Words m)
Reducer Char m => Reducer Char (Words m)
Reducer Char m => Reducer Char (FromString m)
Reducer Char m => Reducer Char (FromString m)
Num a => Reducer Integer (FromNum a)
Num a => Reducer Integer (FromNum a)
CharReducer m => Reducer Word8 (UTF8 m)
CharReducer m => Reducer Word8 (UTF8 m)
Ord a => Reducer a (Set a)
Reducer a (Seq a)
Reducer a (Last a)
Reducer a (First a)
Num a => Reducer a (Product a)
Num a => Reducer a (Sum a)
Monoid a => Reducer a (Dual a)
Reducer c ([] c)
HasUnion f => Reducer f (Union f)
Monoid m => Reducer m (Self m)
(Ord a, Bounded a) => Reducer a (Min a)
(Ord a, Bounded a) => Reducer a (Max a)
Ord a => Reducer a (Priority a)
(Bounded a, Ord a) => Reducer a (Order a)
Ord a => Reducer a (Tropical a)
Reducer a (Free a)
(Reflects s (a -> m), Monoid m) => Reducer a (ReducedBy m s)
Measured v a => Reducer a (FingerTree v a)
(Reducer c m, Reducer c n) => Reducer c ((,) m n)
Eq a => Reducer a (RLE Seq a)
(Reducer c m, Applicative f) => Reducer c (App f m)
(Reducer c m, Monad f) => Reducer c (Mon f m)
(Reducer c m, Reducer c n, Reducer c o) => Reducer c ((,,) m n o)
Reducer c m => Reducer c (CMonoid m m m)
(Reducer c r, Reducer c m) => Reducer c (D s r m)
(Stream s m t, Reducer c a) => Reducer c (ParsecT s u m a)
(Reducer c m, Reducer c n, Reducer c o, Reducer c p) => Reducer c ((,,,) m n o p)
Applicative f => Reducer (f a) (Traversal f)
Monad m => Reducer (m a) (Action m)
Reducer (Maybe a) (Last a)
Reducer (Maybe a) (Last a)
Reducer (Maybe a) (First a)
Reducer (Maybe a) (First a)
Ord a => Reducer (Maybe a) (MinPriority a)
Ord a => Reducer (Maybe a) (MinPriority a)
Ord a => Reducer (Maybe a) (MaxPriority a)
Ord a => Reducer (Maybe a) (MaxPriority a)
Ord a => Reducer (Maybe a) (Tropical a)
Ord a => Reducer (Maybe a) (Tropical a)
Ord a => Reducer (MinPriority a) (Priority a)
Ord a => Reducer (MinPriority a) (Priority a)
Ord a => Reducer (MinPriority a) (Tropical a)
Ord a => Reducer (MinPriority a) (Tropical a)
Ord a => Reducer (MaxPriority a) (Priority a)
Ord a => Reducer (MaxPriority a) (Priority a)
(HasUnionWith f, Monoid m) => Reducer (f m) (UnionWith f m)
Alternative f => Reducer (f a) (Alt f a)
MonadPlus m => Reducer (m a) (MonadSum m a)
Reducer c m => Reducer (WithReducer c m) m
Reducer (a -> a) (Endo a)
Reducer (a -> a) (Endo a)
Reducer ((,) Int v) (IntMap v)
Reducer ((,) Int v) (IntMap v)
Ord k => Reducer ((,) k v) (Map k v)
Ord k => Reducer ((,) k v) (Map k v)
Monoid m => Reducer (CMonoid m m m) m
foldMapReduce :: (Foldable f, 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.
foldReduce :: (Foldable f, Reducer e m) => f e -> mSource
Apply a Reducer to a Foldable mapping each element through unit
pureUnit :: (Applicative f, Reducer c n) => c -> f nSource
returnUnit :: (Monad m, Reducer c n) => c -> m nSource
data ReducedBy m s Source
Constructors
Reduction
getReduction :: m
show/hide Instances
Produced by Haddock version 2.4.2