semigroupoids-5.1: 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.Bitraversable

Description

 

Documentation

class (Bifoldable1 t, Bitraversable t) => Bitraversable1 t where Source #

Minimal complete definition

bitraverse1 | bisequence1

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> t a c -> f (t b d) Source #

bisequence1 :: Apply f => t (f a) (f b) -> f (t a b) Source #

Instances

Bitraversable1 Either Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Either a c -> f (Either b d) Source #

bisequence1 :: Apply f => Either (f a) (f b) -> f (Either a b) Source #

Bitraversable1 (,) Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> (a, c) -> f (b, d) Source #

bisequence1 :: Apply f => (f a, f b) -> f (a, b) Source #

Bitraversable1 Arg Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Arg a c -> f (Arg b d) Source #

bisequence1 :: Apply f => Arg (f a) (f b) -> f (Arg a b) Source #

Bitraversable1 ((,,) x) Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> (x, a, c) -> f (x, b, d) Source #

bisequence1 :: Apply f => (x, f a, f b) -> f (x, a, b) Source #

Bitraversable1 (Const *) Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Const * a c -> f (Const * b d) Source #

bisequence1 :: Apply f => Const * (f a) (f b) -> f (Const * a b) Source #

Bitraversable1 (Tagged *) Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Tagged * a c -> f (Tagged * b d) Source #

bisequence1 :: Apply f => Tagged * (f a) (f b) -> f (Tagged * a b) Source #

Bitraversable1 ((,,,) x y) Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> (x, y, a, c) -> f (x, y, b, d) Source #

bisequence1 :: Apply f => (x, y, f a, f b) -> f (x, y, a, b) Source #

Bitraversable1 ((,,,,) x y z) Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> (x, y, z, a, c) -> f (x, y, z, b, d) Source #

bisequence1 :: Apply f => (x, y, z, f a, f b) -> f (x, y, z, a, b) Source #

Bitraversable1 p => Bitraversable1 (WrappedBifunctor * * p) Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> WrappedBifunctor * * p a c -> f (WrappedBifunctor * * p b d) Source #

bisequence1 :: Apply f => WrappedBifunctor * * p (f a) (f b) -> f (WrappedBifunctor * * p a b) Source #

Traversable1 g => Bitraversable1 (Joker * * g) Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Joker * * g a c -> f (Joker * * g b d) Source #

bisequence1 :: Apply f => Joker * * g (f a) (f b) -> f (Joker * * g a b) Source #

Bitraversable1 p => Bitraversable1 (Flip * * p) Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Flip * * p a c -> f (Flip * * p b d) Source #

bisequence1 :: Apply f => Flip * * p (f a) (f b) -> f (Flip * * p a b) Source #

Traversable1 f => Bitraversable1 (Clown * * f) Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Clown * * f a c -> f (Clown * * f b d) Source #

bisequence1 :: Apply f => Clown * * f (f a) (f b) -> f (Clown * * f a b) Source #

(Bitraversable1 f, Bitraversable1 g) => Bitraversable1 (Product * * f g) Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Product * * f g a c -> f (Product * * f g b d) Source #

bisequence1 :: Apply f => Product * * f g (f a) (f b) -> f (Product * * f g a b) Source #

(Traversable1 f, Bitraversable1 p) => Bitraversable1 (Tannen * * * f p) Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Tannen * * * f p a c -> f (Tannen * * * f p b d) Source #

bisequence1 :: Apply f => Tannen * * * f p (f a) (f b) -> f (Tannen * * * f p a b) Source #

(Bitraversable1 p, Traversable1 f, Traversable1 g) => Bitraversable1 (Biff * * * * p f g) Source # 

Methods

bitraverse1 :: Apply f => (a -> f b) -> (c -> f d) -> Biff * * * * p f g a c -> f (Biff * * * * p f g b d) Source #

bisequence1 :: Apply f => Biff * * * * p f g (f a) (f b) -> f (Biff * * * * p f g a b) Source #

bifoldMap1Default :: (Bitraversable1 t, Semigroup m) => (a -> m) -> (b -> m) -> t a b -> m Source #