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

Copyright(c) Edward Kmett 2009
LicenseBSD3
Maintainerekmett@gmail.com
Stabilityexperimental
Portabilitynon-portable (MPTCs)
Safe HaskellTrustworthy
LanguageHaskell98

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 where Source #

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

Minimal complete definition

unit

Methods

unit :: c -> m Source #

Convert a value into a Semigroup

snoc :: m -> c -> m Source #

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

cons :: c -> m -> m Source #

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

Instances
Reducer Bool All Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: Bool -> All Source #

snoc :: All -> Bool -> All Source #

cons :: Bool -> All -> All Source #

Reducer Bool Any Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: Bool -> Any Source #

snoc :: Any -> Bool -> Any Source #

cons :: Bool -> Any -> Any Source #

Reducer Int IntSet Source # 
Instance details

Defined in Data.Semigroup.Reducer

Reducer c () Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: c -> () Source #

snoc :: () -> c -> () Source #

cons :: c -> () -> () Source #

Reducer a Count Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: a -> Count Source #

snoc :: Count -> a -> Count Source #

cons :: a -> Count -> Count Source #

Monoid m => Reducer m (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Ord a => Reducer a (Set a) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: a -> Set a Source #

snoc :: Set a -> a -> Set a Source #

cons :: a -> Set a -> Set a Source #

Reducer a (Seq a) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: a -> Seq a Source #

snoc :: Seq a -> a -> Seq a Source #

cons :: a -> Seq a -> Seq a Source #

Reducer a (Last a) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: a -> Last a Source #

snoc :: Last a -> a -> Last a Source #

cons :: a -> Last a -> Last a Source #

Reducer a (First a) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: a -> First a Source #

snoc :: First a -> a -> First a Source #

cons :: a -> First a -> First a Source #

Ord a => Reducer a (Max a) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: a -> Max a Source #

snoc :: Max a -> a -> Max a Source #

cons :: a -> Max a -> Max a Source #

Ord a => Reducer a (Min a) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: a -> Min a Source #

snoc :: Min a -> a -> Min a Source #

cons :: a -> Min a -> Min a Source #

Num a => Reducer a (Product a) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: a -> Product a Source #

snoc :: Product a -> a -> Product a Source #

cons :: a -> Product a -> Product a Source #

Num a => Reducer a (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: a -> Sum a Source #

snoc :: Sum a -> a -> Sum a Source #

cons :: a -> Sum a -> Sum a Source #

Semigroup a => Reducer a (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: a -> Dual a Source #

snoc :: Dual a -> a -> Dual a Source #

cons :: a -> Dual a -> Dual a Source #

Reducer c [c] Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: c -> [c] Source #

snoc :: [c] -> c -> [c] Source #

cons :: c -> [c] -> [c] Source #

Semigroup m => Reducer m (Self m) Source # 
Instance details

Defined in Data.Semigroup.Self

Methods

unit :: m -> Self m Source #

snoc :: Self m -> m -> Self m Source #

cons :: m -> Self m -> Self m Source #

HasUnion f => Reducer f (Union f) Source # 
Instance details

Defined in Data.Semigroup.Union

Methods

unit :: f -> Union f Source #

snoc :: Union f -> f -> Union f Source #

cons :: f -> Union f -> Union f Source #

Measured v a => Reducer a (FingerTree v a) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: a -> FingerTree v a Source #

snoc :: FingerTree v a -> a -> FingerTree v a Source #

cons :: a -> FingerTree v a -> FingerTree v a Source #

(Reducer c m, Reducer c n) => Reducer c (m, n) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: c -> (m, n) Source #

snoc :: (m, n) -> c -> (m, n) Source #

cons :: c -> (m, n) -> (m, n) Source #

(Reducer c m, Reducer c n, Reducer c o) => Reducer c (m, n, o) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: c -> (m, n, o) Source #

snoc :: (m, n, o) -> c -> (m, n, o) Source #

cons :: c -> (m, n, o) -> (m, n, o) Source #

(Reducer c m, Reducer c n, Reducer c o, Reducer c p) => Reducer c (m, n, o, p) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: c -> (m, n, o, p) Source #

snoc :: (m, n, o, p) -> c -> (m, n, o, p) Source #

cons :: c -> (m, n, o, p) -> (m, n, o, p) Source #

Reducer (Maybe a) (Last a) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: Maybe a -> Last a Source #

snoc :: Last a -> Maybe a -> Last a Source #

cons :: Maybe a -> Last a -> Last a Source #

Reducer (Maybe a) (First a) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: Maybe a -> First a Source #

snoc :: First a -> Maybe a -> First a Source #

cons :: Maybe a -> First a -> First a Source #

Monad f => Reducer (f a) (Action f) Source # 
Instance details

Defined in Data.Semigroup.Monad

Methods

unit :: f a -> Action f Source #

snoc :: Action f -> f a -> Action f Source #

cons :: f a -> Action f -> Action f Source #

Apply f => Reducer (f a) (Trav f) Source # 
Instance details

Defined in Data.Semigroup.Apply

Methods

unit :: f a -> Trav f Source #

snoc :: Trav f -> f a -> Trav f Source #

cons :: f a -> Trav f -> Trav f Source #

Applicative f => Reducer (f a) (Traversal f) Source # 
Instance details

Defined in Data.Semigroup.Applicative

Methods

unit :: f a -> Traversal f Source #

snoc :: Traversal f -> f a -> Traversal f Source #

cons :: f a -> Traversal f -> Traversal f Source #

MonadPlus f => Reducer (f a) (MonadSum f a) Source # 
Instance details

Defined in Data.Semigroup.MonadPlus

Methods

unit :: f a -> MonadSum f a Source #

snoc :: MonadSum f a -> f a -> MonadSum f a Source #

cons :: f a -> MonadSum f a -> MonadSum f a Source #

(Monad f, Reducer c m) => Reducer (f c) (Mon f m) Source # 
Instance details

Defined in Data.Semigroup.Monad

Methods

unit :: f c -> Mon f m Source #

snoc :: Mon f m -> f c -> Mon f m Source #

cons :: f c -> Mon f m -> Mon f m Source #

(Apply f, Reducer c m) => Reducer (f c) (App f m) Source # 
Instance details

Defined in Data.Semigroup.Apply

Methods

unit :: f c -> App f m Source #

snoc :: App f m -> f c -> App f m Source #

cons :: f c -> App f m -> App f m Source #

(Applicative f, Reducer c m) => Reducer (f c) (Ap f m) Source # 
Instance details

Defined in Data.Semigroup.Applicative

Methods

unit :: f c -> Ap f m Source #

snoc :: Ap f m -> f c -> Ap f m Source #

cons :: f c -> Ap f m -> Ap f m Source #

Alternative f => Reducer (f a) (Alternate f a) Source # 
Instance details

Defined in Data.Semigroup.Alternative

Methods

unit :: f a -> Alternate f a Source #

snoc :: Alternate f a -> f a -> Alternate f a Source #

cons :: f a -> Alternate f a -> Alternate f a Source #

Alt f => Reducer (f a) (Alter f a) Source # 
Instance details

Defined in Data.Semigroup.Alt

Methods

unit :: f a -> Alter f a Source #

snoc :: Alter f a -> f a -> Alter f a Source #

cons :: f a -> Alter f a -> Alter f a Source #

(HasUnionWith f, Semigroup m, Monoid m) => Reducer (f m) (UnionWith f m) Source # 
Instance details

Defined in Data.Semigroup.Union

Methods

unit :: f m -> UnionWith f m Source #

snoc :: UnionWith f m -> f m -> UnionWith f m Source #

cons :: f m -> UnionWith f m -> UnionWith f m Source #

Reducer c m => Reducer (WithReducer m c) m Source # 
Instance details

Defined in Data.Semigroup.Reducer.With

Methods

unit :: WithReducer m c -> m Source #

snoc :: m -> WithReducer m c -> m Source #

cons :: WithReducer m c -> m -> m Source #

Reducer (a -> a) (Endo a) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: (a -> a) -> Endo a Source #

snoc :: Endo a -> (a -> a) -> Endo a Source #

cons :: (a -> a) -> Endo a -> Endo a Source #

Reducer (Int, v) (IntMap v) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: (Int, v) -> IntMap v Source #

snoc :: IntMap v -> (Int, v) -> IntMap v Source #

cons :: (Int, v) -> IntMap v -> IntMap v Source #

(Eq k, Hashable k) => Reducer (k, v) (HashMap k v) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: (k, v) -> HashMap k v Source #

snoc :: HashMap k v -> (k, v) -> HashMap k v Source #

cons :: (k, v) -> HashMap k v -> HashMap k v Source #

Ord k => Reducer (k, v) (Map k v) Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: (k, v) -> Map k v Source #

snoc :: Map k v -> (k, v) -> Map k v Source #

cons :: (k, v) -> Map k v -> Map k v Source #

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

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 -> m Source #

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

Apply a Reducer to a Foldable mapping each element through unit

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

Apply a Reducer to a Foldable1 mapping each element through unit

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

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

newtype Count Source #

Constructors

Count 

Fields

Instances
Eq Count Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

(==) :: Count -> Count -> Bool #

(/=) :: Count -> Count -> Bool #

Data Count Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Count -> c Count #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Count #

toConstr :: Count -> Constr #

dataTypeOf :: Count -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Count) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Count) #

gmapT :: (forall b. Data b => b -> b) -> Count -> Count #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Count -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Count -> r #

gmapQ :: (forall d. Data d => d -> u) -> Count -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Count -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Count -> m Count #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Count -> m Count #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Count -> m Count #

Ord Count Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

compare :: Count -> Count -> Ordering #

(<) :: Count -> Count -> Bool #

(<=) :: Count -> Count -> Bool #

(>) :: Count -> Count -> Bool #

(>=) :: Count -> Count -> Bool #

max :: Count -> Count -> Count #

min :: Count -> Count -> Count #

Read Count Source # 
Instance details

Defined in Data.Semigroup.Reducer

Show Count Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

showsPrec :: Int -> Count -> ShowS #

show :: Count -> String #

showList :: [Count] -> ShowS #

Semigroup Count Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

(<>) :: Count -> Count -> Count #

sconcat :: NonEmpty Count -> Count #

stimes :: Integral b => b -> Count -> Count #

Monoid Count Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

mempty :: Count #

mappend :: Count -> Count -> Count #

mconcat :: [Count] -> Count #

Hashable Count Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

hashWithSalt :: Int -> Count -> Int #

hash :: Count -> Int #

Reducer a Count Source # 
Instance details

Defined in Data.Semigroup.Reducer

Methods

unit :: a -> Count Source #

snoc :: Count -> a -> Count Source #

cons :: a -> Count -> Count Source #