semigroupoids-5.3.4: Semigroupoids: Category sans id

Copyright(C) 2011-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Data.Semigroup.Bifoldable

Description

 
Synopsis

Documentation

class Bifoldable t => Bifoldable1 t where Source #

Minimal complete definition

Nothing

Methods

bifold1 :: Semigroup m => t m m -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> t a b -> m Source #

Instances
Bifoldable1 Either Source # 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => Either m m -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> Either a b -> m Source #

Bifoldable1 (,) Source # 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => (m, m) -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> (a, b) -> m Source #

Bifoldable1 Arg Source # 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => Arg m m -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> Arg a b -> m Source #

Bifoldable1 ((,,) x) Source # 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => (x, m, m) -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> (x, a, b) -> m Source #

Bifoldable1 (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => Const m m -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> Const a b -> m Source #

Bifoldable1 (Tagged :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => Tagged m m -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> Tagged a b -> m Source #

Bifoldable1 ((,,,) x y) Source # 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => (x, y, m, m) -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> (x, y, a, b) -> m Source #

Bifoldable1 ((,,,,) x y z) Source # 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => (x, y, z, m, m) -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> (x, y, z, a, b) -> m Source #

Bifoldable1 p => Bifoldable1 (WrappedBifunctor p) Source # 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => WrappedBifunctor p m m -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> WrappedBifunctor p a b -> m Source #

Foldable1 g => Bifoldable1 (Joker g :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => Joker g m m -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> Joker g a b -> m Source #

Bifoldable1 p => Bifoldable1 (Flip p) Source # 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => Flip p m m -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> Flip p a b -> m Source #

Foldable1 f => Bifoldable1 (Clown f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => Clown f m m -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> Clown f a b -> m Source #

(Bifoldable1 f, Bifoldable1 g) => Bifoldable1 (Product f g) Source # 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => Product f g m m -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> Product f g a b -> m Source #

(Foldable1 f, Bifoldable1 p) => Bifoldable1 (Tannen f p) Source # 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => Tannen f p m m -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> Tannen f p a b -> m Source #

(Bifoldable1 p, Foldable1 f, Foldable1 g) => Bifoldable1 (Biff p f g) Source # 
Instance details

Defined in Data.Semigroup.Foldable.Class

Methods

bifold1 :: Semigroup m => Biff p f g m m -> m Source #

bifoldMap1 :: Semigroup m => (a -> m) -> (b -> m) -> Biff p f g a b -> m Source #

bitraverse1_ :: (Bifoldable1 t, Apply f) => (a -> f b) -> (c -> f d) -> t a c -> f () Source #

bifor1_ :: (Bifoldable1 t, Apply f) => t a c -> (a -> f b) -> (c -> f d) -> f () Source #

bisequenceA1_ :: (Bifoldable1 t, Apply f) => t (f a) (f b) -> f () Source #

bifoldMapDefault1 :: (Bifoldable1 t, Monoid m) => (a -> m) -> (b -> m) -> t a b -> m Source #

Usable default for foldMap, but only if you define bifoldMap1 yourself