{-# LANGUAGE UndecidableInstances, TypeOperators, FlexibleContexts, MultiParamTypeClasses, FlexibleInstances, TypeFamilies #-} ----------------------------------------------------------------------------- -- | -- Module : Data.Monoid.Combinators -- Copyright : (c) Edward Kmett 2009 -- License : BSD-style -- Maintainer : libraries@haskell.org -- Stability : experimental -- Portability : non-portable (type families, MPTCs) -- -- 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 -- ----------------------------------------------------------------------------- module Data.Monoid.Combinators ( module Data.Monoid.Generator -- * Monadic Reduction , mapM_ , forM_ -- * Applicative Reduction , traverse_ , for_ -- * Logical Reduction , and , or , any , all -- * Monoidal Reduction , foldMap , fold -- * List-Like Reduction , concatMap , elem , filter , find , sum , product , notElem -- * List-Like Monoid Generation , repeat , replicate , cycle ) where import Prelude hiding (mapM_, any, elem, filter, concatMap, and, or, all, sum, product, notElem, replicate, cycle, repeat) import Control.Applicative import Data.Monoid.Generator import Data.Monoid.Applicative import Data.Monoid.Self import Data.Monoid.Monad -- | Efficiently 'mapReduce' a 'Generator' using the 'Traversal' monoid. A specialized version of its namesake in "Data.Foldable" traverse_ :: (Generator c, Applicative f) => (Elem c -> f b) -> c -> f () traverse_ f = getTraversal . mapReduce f -- | flipped 'traverse_' as in "Data.Foldable" for_ :: (Generator c, Applicative f) => c -> (Elem c -> f b) -> f () for_ = flip traverse_ -- | Efficiently 'mapReduce' a 'Generator' using the 'Action' monoid. A specialized version of its namesake from "Data.Foldable" and "Control.Monad" mapM_ :: (Generator c, Monad m) => (Elem c -> m b) -> c -> m () mapM_ f = getAction . mapReduce f -- | flipped 'mapM_' as in "Data.Foldable" and "Control.Monad" forM_ :: (Generator c, Monad m) => c -> (Elem c -> m b) -> m () forM_ = flip mapM_ -- | Efficiently 'mapReduce' a 'Generator' using the 'Self' monoid. A specialized version of its namesake from "Data.Foldable" foldMap :: (Monoid m, Generator c) => (Elem c -> m) -> c -> m foldMap f = getSelf . mapReduce f -- | Efficiently 'reduce' a 'Generator' using the 'Self' monoid. A specialized version of its namesake from "Data.Foldable" fold :: (Monoid m, Generator c, Elem c ~ m) => c -> m fold = getSelf . reduce -- | A further specialization of "foldMap" concatMap :: Generator c => (Elem c -> [b]) -> c -> [b] concatMap = foldMap -- | Efficiently 'reduce' a 'Generator' that contains values of type 'Bool' and :: (Generator c, Elem c ~ Bool) => c -> Bool and = getAll . reduce -- | Efficiently 'reduce' a 'Generator' that contains values of type 'Bool' or :: (Generator c, Elem c ~ Bool) => c -> Bool or = getAny . reduce -- | Efficiently 'mapReduce' any 'Generator' checking to see if any of its values match the supplied predicate any :: Generator c => (Elem c -> Bool) -> c -> Bool any f = getAny . mapReduce f -- | Efficiently 'mapReduce' any 'Generator' checking to see if all of its values match the supplied predicate all :: Generator c => (Elem c -> Bool) -> c -> Bool all f = getAll . mapReduce f -- | Efficiently 'mapReduce' any 'Generator' using the 'Sum' 'Monoid' sum :: (Generator c, Num (Elem c)) => c -> Elem c sum = getSum . reduce -- | Efficiently 'mapReduce' any 'Generator' using the 'Product' 'Monoid' product :: (Generator c, Num (Elem c)) => c -> Elem c product = getProduct . reduce -- | Check to see if 'any' member of the 'Generator' matches the supplied value elem :: (Generator c, Eq (Elem c)) => Elem c -> c -> Bool elem = any . (==) -- | Check to make sure that the supplied value is not a member of the 'Generator' notElem :: (Generator c, Eq (Elem c)) => Elem c -> c -> Bool notElem x = not . elem x -- | Efficiently 'mapReduce' a subset of the elements in a 'Generator' filter :: (Generator c, Elem c `Reducer` m) => (Elem c -> Bool) -> c -> m filter p = foldMap f where f x | p x = unit x | otherwise = mempty -- | A specialization of 'filter' using the 'First' 'Monoid', analogous to 'Data.List.find' find :: Generator c => (Elem c -> Bool) -> c -> Maybe (Elem c) find p = getFirst . filter p -- | A generalization of 'Data.List.replicate' to an arbitrary 'Monoid'. Adapted from -- replicate :: (Monoid m, Integral n) => m -> n -> m replicate x0 y0 | y0 < 0 = mempty -- error "negative length" | y0 == 0 = mempty | otherwise = f x0 y0 where f x y | even y = f (x `mappend` x) (y `quot` 2) | y == 1 = x | otherwise = g (x `mappend` x) ((y - 1) `quot` 2) x g x y z | even y = g (x `mappend` x) (y `quot` 2) z | y == 1 = x `mappend` z | otherwise = g (x `mappend` x) ((y - 1) `quot` 2) (x `mappend` z) -- | A generalization of 'Data.List.cycle' to an arbitrary 'Monoid'. May fail to terminate for some values in some monoids. cycle :: Monoid m => m -> m cycle xs = xs' where xs' = xs `mappend` xs' -- | A generalization of 'Data.List.repeat' to an arbitrary 'Monoid'. May fail to terminate for some values in some monoids. repeat :: (e `Reducer` m) => e -> m repeat x = xs where xs = cons x xs