{-# LANGUAGE UndecidableInstances, TypeOperators, FlexibleContexts, MultiParamTypeClasses, FlexibleInstances, TypeFamilies #-}
module Data.Generator.Combinators
(
mapM_
, forM_
, msum
, traverse_
, for_
, asum
, and
, or
, any
, all
, foldMap
, fold
, toList
, concatMap
, elem
, filter
, filterWith
, sum
, product
, notElem
) where
import Prelude hiding
( mapM_, any, all, elem, filter, concatMap, and, or
, sum, product, notElem, replicate, cycle, repeat
, foldMap
)
import Control.Applicative (Alternative)
import Control.Monad (MonadPlus)
import Data.Generator
import Data.Semigroup (Sum(..), Product(..), All(..), Any(..), WrappedMonoid(..))
import Data.Semigroup.Applicative (Traversal(..))
import Data.Semigroup.Alternative (Alternate(..))
import Data.Semigroup.Monad (Action(..))
import Data.Semigroup.MonadPlus (MonadSum(..))
import Data.Semigroup.Reducer (Reducer(..))
traverse_ :: (Generator c, Applicative f) => (Elem c -> f b) -> c -> f ()
traverse_ :: forall c (f :: * -> *) b.
(Generator c, Applicative f) =>
(Elem c -> f b) -> c -> f ()
traverse_ = (Traversal f -> f ()) -> (Elem c -> f b) -> c -> f ()
forall c e m n.
(Generator c, Reducer e m, Monoid m) =>
(m -> n) -> (Elem c -> e) -> c -> n
mapReduceWith Traversal f -> f ()
forall (f :: * -> *). Traversal f -> f ()
getTraversal
{-# INLINE traverse_ #-}
for_ :: (Generator c, Applicative f) => c -> (Elem c -> f b) -> f ()
for_ :: forall c (f :: * -> *) b.
(Generator c, Applicative f) =>
c -> (Elem c -> f b) -> f ()
for_ = ((Elem c -> f b) -> c -> f ()) -> c -> (Elem c -> f b) -> f ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Elem c -> f b) -> c -> f ()
forall c (f :: * -> *) b.
(Generator c, Applicative f) =>
(Elem c -> f b) -> c -> f ()
traverse_
{-# INLINE for_ #-}
asum :: (Generator c, Alternative f, f a ~ Elem c) => c -> f a
asum :: forall c (f :: * -> *) a.
(Generator c, Alternative f, f a ~ Elem c) =>
c -> f a
asum = (Alternate f a -> f a) -> c -> f a
forall c m n.
(Generator c, Reducer (Elem c) m, Monoid m) =>
(m -> n) -> c -> n
reduceWith Alternate f a -> f a
forall (f :: * -> *) a. Alternate f a -> f a
getAlternate
{-# INLINE asum #-}
mapM_ :: (Generator c, Monad m) => (Elem c -> m b) -> c -> m ()
mapM_ :: forall c (m :: * -> *) b.
(Generator c, Monad m) =>
(Elem c -> m b) -> c -> m ()
mapM_ = (Action m -> m ()) -> (Elem c -> m b) -> c -> m ()
forall c e m n.
(Generator c, Reducer e m, Monoid m) =>
(m -> n) -> (Elem c -> e) -> c -> n
mapReduceWith Action m -> m ()
forall (f :: * -> *). Action f -> f ()
getAction
{-# INLINE mapM_ #-}
forM_ :: (Generator c, Monad m) => c -> (Elem c -> m b) -> m ()
forM_ :: forall c (m :: * -> *) b.
(Generator c, Monad m) =>
c -> (Elem c -> m b) -> m ()
forM_ = ((Elem c -> m b) -> c -> m ()) -> c -> (Elem c -> m b) -> m ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Elem c -> m b) -> c -> m ()
forall c (m :: * -> *) b.
(Generator c, Monad m) =>
(Elem c -> m b) -> c -> m ()
mapM_
{-# INLINE forM_ #-}
msum :: (Generator c, MonadPlus m, m a ~ Elem c) => c -> m a
msum :: forall c (m :: * -> *) a.
(Generator c, MonadPlus m, m a ~ Elem c) =>
c -> m a
msum = (MonadSum m a -> m a) -> c -> m a
forall c m n.
(Generator c, Reducer (Elem c) m, Monoid m) =>
(m -> n) -> c -> n
reduceWith MonadSum m a -> m a
forall (f :: * -> *) a. MonadSum f a -> f a
getMonadSum
{-# INLINE msum #-}
foldMap :: (Monoid m, Generator c) => (Elem c -> m) -> c -> m
foldMap :: forall m c. (Monoid m, Generator c) => (Elem c -> m) -> c -> m
foldMap = (WrappedMonoid m -> m) -> (Elem c -> m) -> c -> m
forall c e m n.
(Generator c, Reducer e m, Monoid m) =>
(m -> n) -> (Elem c -> e) -> c -> n
mapReduceWith WrappedMonoid m -> m
forall m. WrappedMonoid m -> m
unwrapMonoid
{-# INLINE foldMap #-}
concatMap :: Generator c => (Elem c -> [b]) -> c -> [b]
concatMap :: forall c b. Generator c => (Elem c -> [b]) -> c -> [b]
concatMap = (Elem c -> [b]) -> c -> [b]
forall m c. (Monoid m, Generator c) => (Elem c -> m) -> c -> m
foldMap
{-# INLINE concatMap #-}
fold :: (Monoid m, Generator c, Elem c ~ m) => c -> m
fold :: forall m c. (Monoid m, Generator c, Elem c ~ m) => c -> m
fold = (WrappedMonoid m -> m) -> c -> m
forall c m n.
(Generator c, Reducer (Elem c) m, Monoid m) =>
(m -> n) -> c -> n
reduceWith WrappedMonoid m -> m
forall m. WrappedMonoid m -> m
unwrapMonoid
{-# INLINE fold #-}
toList :: Generator c => c -> [Elem c]
toList :: forall c. Generator c => c -> [Elem c]
toList = c -> [Elem c]
forall c m. (Generator c, Reducer (Elem c) m, Monoid m) => c -> m
reduce
{-# INLINE toList #-}
and :: (Generator c, Elem c ~ Bool) => c -> Bool
and :: forall c. (Generator c, Elem c ~ Bool) => c -> Bool
and = (All -> Bool) -> c -> Bool
forall c m n.
(Generator c, Reducer (Elem c) m, Monoid m) =>
(m -> n) -> c -> n
reduceWith All -> Bool
getAll
{-# INLINE and #-}
or :: (Generator c, Elem c ~ Bool) => c -> Bool
or :: forall c. (Generator c, Elem c ~ Bool) => c -> Bool
or = (Any -> Bool) -> c -> Bool
forall c m n.
(Generator c, Reducer (Elem c) m, Monoid m) =>
(m -> n) -> c -> n
reduceWith Any -> Bool
getAny
{-# INLINE or #-}
any :: Generator c => (Elem c -> Bool) -> c -> Bool
any :: forall c. Generator c => (Elem c -> Bool) -> c -> Bool
any = (Any -> Bool) -> (Elem c -> Bool) -> c -> Bool
forall c e m n.
(Generator c, Reducer e m, Monoid m) =>
(m -> n) -> (Elem c -> e) -> c -> n
mapReduceWith Any -> Bool
getAny
{-# INLINE any #-}
all :: Generator c => (Elem c -> Bool) -> c -> Bool
all :: forall c. Generator c => (Elem c -> Bool) -> c -> Bool
all = (All -> Bool) -> (Elem c -> Bool) -> c -> Bool
forall c e m n.
(Generator c, Reducer e m, Monoid m) =>
(m -> n) -> (Elem c -> e) -> c -> n
mapReduceWith All -> Bool
getAll
{-# INLINE all #-}
sum :: (Generator c, Num (Elem c)) => c -> Elem c
sum :: forall c. (Generator c, Num (Elem c)) => c -> Elem c
sum = (Sum (Elem c) -> Elem c) -> c -> Elem c
forall c m n.
(Generator c, Reducer (Elem c) m, Monoid m) =>
(m -> n) -> c -> n
reduceWith Sum (Elem c) -> Elem c
forall a. Sum a -> a
getSum
{-# INLINE sum #-}
product :: (Generator c, Num (Elem c)) => c -> Elem c
product :: forall c. (Generator c, Num (Elem c)) => c -> Elem c
product = (Product (Elem c) -> Elem c) -> c -> Elem c
forall c m n.
(Generator c, Reducer (Elem c) m, Monoid m) =>
(m -> n) -> c -> n
reduceWith Product (Elem c) -> Elem c
forall a. Product a -> a
getProduct
{-# INLINE product #-}
elem :: (Generator c, Eq (Elem c)) => Elem c -> c -> Bool
elem :: forall c. (Generator c, Eq (Elem c)) => Elem c -> c -> Bool
elem = (Elem c -> Bool) -> c -> Bool
forall c. Generator c => (Elem c -> Bool) -> c -> Bool
any ((Elem c -> Bool) -> c -> Bool)
-> (Elem c -> Elem c -> Bool) -> Elem c -> c -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Elem c -> Elem c -> Bool
forall a. Eq a => a -> a -> Bool
(==)
{-# INLINE elem #-}
notElem :: (Generator c, Eq (Elem c)) => Elem c -> c -> Bool
notElem :: forall c. (Generator c, Eq (Elem c)) => Elem c -> c -> Bool
notElem Elem c
x = Bool -> Bool
not (Bool -> Bool) -> (c -> Bool) -> c -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Elem c -> c -> Bool
forall c. (Generator c, Eq (Elem c)) => Elem c -> c -> Bool
elem Elem c
x
{-# INLINE notElem #-}
filter :: (Generator c, Reducer (Elem c) m, Monoid m) => (Elem c -> Bool) -> c -> m
filter :: forall c m.
(Generator c, Reducer (Elem c) m, Monoid m) =>
(Elem c -> Bool) -> c -> m
filter Elem c -> Bool
p = (Elem c -> m) -> c -> m
forall m c. (Monoid m, Generator c) => (Elem c -> m) -> c -> m
foldMap Elem c -> m
f where
f :: Elem c -> m
f Elem c
x | Elem c -> Bool
p Elem c
x = Elem c -> m
forall c m. Reducer c m => c -> m
unit Elem c
x
| Bool
otherwise = m
forall a. Monoid a => a
mempty
{-# INLINE filter #-}
filterWith :: (Generator c, Reducer (Elem c) m, Monoid m) => (m -> n) -> (Elem c -> Bool) -> c -> n
filterWith :: forall c m n.
(Generator c, Reducer (Elem c) m, Monoid m) =>
(m -> n) -> (Elem c -> Bool) -> c -> n
filterWith m -> n
f Elem c -> Bool
p = m -> n
f (m -> n) -> (c -> m) -> c -> n
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Elem c -> Bool) -> c -> m
forall c m.
(Generator c, Reducer (Elem c) m, Monoid m) =>
(Elem c -> Bool) -> c -> m
filter Elem c -> Bool
p
{-# INLINE filterWith #-}