semigroupoids-5.2.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.Bifunctor.Apply

Contents

Description

 

Synopsis

Biappliable bifunctors

class Bifunctor p where #

Formally, the class Bifunctor represents a bifunctor from Hask -> Hask.

Intuitively it is a bifunctor where both the first and second arguments are covariant.

You can define a Bifunctor by either defining bimap or by defining both first and second.

If you supply bimap, you should ensure that:

bimap id idid

If you supply first and second, ensure:

first idid
second idid

If you supply both, you should also ensure:

bimap f g ≡ first f . second g

These ensure by parametricity:

bimap  (f . g) (h . i) ≡ bimap f h . bimap g i
first  (f . g) ≡ first  f . first  g
second (f . g) ≡ second f . second g

Since: 4.8.0.0

Minimal complete definition

bimap | first, second

Methods

bimap :: (a -> b) -> (c -> d) -> p a c -> p b d #

Map over both arguments at the same time.

bimap f g ≡ first f . second g

first :: (a -> b) -> p a c -> p b c #

Map covariantly over the first argument.

first f ≡ bimap f id

second :: (b -> c) -> p a b -> p a c #

Map covariantly over the second argument.

secondbimap id

Instances

Bifunctor Either 

Methods

bimap :: (a -> b) -> (c -> d) -> Either a c -> Either b d #

first :: (a -> b) -> Either a c -> Either b c #

second :: (b -> c) -> Either a b -> Either a c #

Bifunctor (,) 

Methods

bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) #

first :: (a -> b) -> (a, c) -> (b, c) #

second :: (b -> c) -> (a, b) -> (a, c) #

Bifunctor Arg 

Methods

bimap :: (a -> b) -> (c -> d) -> Arg a c -> Arg b d #

first :: (a -> b) -> Arg a c -> Arg b c #

second :: (b -> c) -> Arg a b -> Arg a c #

Bifunctor (K1 i) 

Methods

bimap :: (a -> b) -> (c -> d) -> K1 i a c -> K1 i b d #

first :: (a -> b) -> K1 i a c -> K1 i b c #

second :: (b -> c) -> K1 i a b -> K1 i a c #

Bifunctor ((,,) x1) 

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, a, c) -> (x1, b, d) #

first :: (a -> b) -> (x1, a, c) -> (x1, b, c) #

second :: (b -> c) -> (x1, a, b) -> (x1, a, c) #

Bifunctor (Const *) 

Methods

bimap :: (a -> b) -> (c -> d) -> Const * a c -> Const * b d #

first :: (a -> b) -> Const * a c -> Const * b c #

second :: (b -> c) -> Const * a b -> Const * a c #

Bifunctor (Tagged *) 

Methods

bimap :: (a -> b) -> (c -> d) -> Tagged * a c -> Tagged * b d #

first :: (a -> b) -> Tagged * a c -> Tagged * b c #

second :: (b -> c) -> Tagged * a b -> Tagged * a c #

Bifunctor (Constant *) 

Methods

bimap :: (a -> b) -> (c -> d) -> Constant * a c -> Constant * b d #

first :: (a -> b) -> Constant * a c -> Constant * b c #

second :: (b -> c) -> Constant * a b -> Constant * a c #

Bifunctor ((,,,) x1 x2) 

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, a, c) -> (x1, x2, b, d) #

first :: (a -> b) -> (x1, x2, a, c) -> (x1, x2, b, c) #

second :: (b -> c) -> (x1, x2, a, b) -> (x1, x2, a, c) #

Bifunctor ((,,,,) x1 x2 x3) 

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, x3, a, c) -> (x1, x2, x3, b, d) #

first :: (a -> b) -> (x1, x2, x3, a, c) -> (x1, x2, x3, b, c) #

second :: (b -> c) -> (x1, x2, x3, a, b) -> (x1, x2, x3, a, c) #

Bifunctor p => Bifunctor (WrappedBifunctor * * p) 

Methods

bimap :: (a -> b) -> (c -> d) -> WrappedBifunctor * * p a c -> WrappedBifunctor * * p b d #

first :: (a -> b) -> WrappedBifunctor * * p a c -> WrappedBifunctor * * p b c #

second :: (b -> c) -> WrappedBifunctor * * p a b -> WrappedBifunctor * * p a c #

Functor g => Bifunctor (Joker * * g) 

Methods

bimap :: (a -> b) -> (c -> d) -> Joker * * g a c -> Joker * * g b d #

first :: (a -> b) -> Joker * * g a c -> Joker * * g b c #

second :: (b -> c) -> Joker * * g a b -> Joker * * g a c #

Bifunctor p => Bifunctor (Flip * * p) 

Methods

bimap :: (a -> b) -> (c -> d) -> Flip * * p a c -> Flip * * p b d #

first :: (a -> b) -> Flip * * p a c -> Flip * * p b c #

second :: (b -> c) -> Flip * * p a b -> Flip * * p a c #

Functor f => Bifunctor (Clown * * f) 

Methods

bimap :: (a -> b) -> (c -> d) -> Clown * * f a c -> Clown * * f b d #

first :: (a -> b) -> Clown * * f a c -> Clown * * f b c #

second :: (b -> c) -> Clown * * f a b -> Clown * * f a c #

Bifunctor ((,,,,,) x1 x2 x3 x4) 

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, x3, x4, a, c) -> (x1, x2, x3, x4, b, d) #

first :: (a -> b) -> (x1, x2, x3, x4, a, c) -> (x1, x2, x3, x4, b, c) #

second :: (b -> c) -> (x1, x2, x3, x4, a, b) -> (x1, x2, x3, x4, a, c) #

(Bifunctor f, Bifunctor g) => Bifunctor (Product * * f g) 

Methods

bimap :: (a -> b) -> (c -> d) -> Product * * f g a c -> Product * * f g b d #

first :: (a -> b) -> Product * * f g a c -> Product * * f g b c #

second :: (b -> c) -> Product * * f g a b -> Product * * f g a c #

Bifunctor ((,,,,,,) x1 x2 x3 x4 x5) 

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, x3, x4, x5, a, c) -> (x1, x2, x3, x4, x5, b, d) #

first :: (a -> b) -> (x1, x2, x3, x4, x5, a, c) -> (x1, x2, x3, x4, x5, b, c) #

second :: (b -> c) -> (x1, x2, x3, x4, x5, a, b) -> (x1, x2, x3, x4, x5, a, c) #

(Functor f, Bifunctor p) => Bifunctor (Tannen * * * f p) 

Methods

bimap :: (a -> b) -> (c -> d) -> Tannen * * * f p a c -> Tannen * * * f p b d #

first :: (a -> b) -> Tannen * * * f p a c -> Tannen * * * f p b c #

second :: (b -> c) -> Tannen * * * f p a b -> Tannen * * * f p a c #

(Bifunctor p, Functor f, Functor g) => Bifunctor (Biff * * * * p f g) 

Methods

bimap :: (a -> b) -> (c -> d) -> Biff * * * * p f g a c -> Biff * * * * p f g b d #

first :: (a -> b) -> Biff * * * * p f g a c -> Biff * * * * p f g b c #

second :: (b -> c) -> Biff * * * * p f g a b -> Biff * * * * p f g a c #

class Bifunctor p => Biapply p where Source #

Minimal complete definition

(<<.>>)

Methods

(<<.>>) :: p (a -> b) (c -> d) -> p a c -> p b d infixl 4 Source #

(.>>) :: p a b -> p c d -> p c d infixl 4 Source #

a .> b ≡ const id <$> a <.> b

(<<.) :: p a b -> p c d -> p a b infixl 4 Source #

a <. b ≡ const <$> a <.> b

Instances

Biapply (,) Source # 

Methods

(<<.>>) :: (a -> b, c -> d) -> (a, c) -> (b, d) Source #

(.>>) :: (a, b) -> (c, d) -> (c, d) Source #

(<<.) :: (a, b) -> (c, d) -> (a, b) Source #

Biapply Arg Source # 

Methods

(<<.>>) :: Arg (a -> b) (c -> d) -> Arg a c -> Arg b d Source #

(.>>) :: Arg a b -> Arg c d -> Arg c d Source #

(<<.) :: Arg a b -> Arg c d -> Arg a b Source #

Semigroup x => Biapply ((,,) x) Source # 

Methods

(<<.>>) :: (x, a -> b, c -> d) -> (x, a, c) -> (x, b, d) Source #

(.>>) :: (x, a, b) -> (x, c, d) -> (x, c, d) Source #

(<<.) :: (x, a, b) -> (x, c, d) -> (x, a, b) Source #

Biapply (Const *) Source # 

Methods

(<<.>>) :: Const * (a -> b) (c -> d) -> Const * a c -> Const * b d Source #

(.>>) :: Const * a b -> Const * c d -> Const * c d Source #

(<<.) :: Const * a b -> Const * c d -> Const * a b Source #

Biapply (Tagged *) Source # 

Methods

(<<.>>) :: Tagged * (a -> b) (c -> d) -> Tagged * a c -> Tagged * b d Source #

(.>>) :: Tagged * a b -> Tagged * c d -> Tagged * c d Source #

(<<.) :: Tagged * a b -> Tagged * c d -> Tagged * a b Source #

(Semigroup x, Semigroup y) => Biapply ((,,,) x y) Source # 

Methods

(<<.>>) :: (x, y, a -> b, c -> d) -> (x, y, a, c) -> (x, y, b, d) Source #

(.>>) :: (x, y, a, b) -> (x, y, c, d) -> (x, y, c, d) Source #

(<<.) :: (x, y, a, b) -> (x, y, c, d) -> (x, y, a, b) Source #

(Semigroup x, Semigroup y, Semigroup z) => Biapply ((,,,,) x y z) Source # 

Methods

(<<.>>) :: (x, y, z, a -> b, c -> d) -> (x, y, z, a, c) -> (x, y, z, b, d) Source #

(.>>) :: (x, y, z, a, b) -> (x, y, z, c, d) -> (x, y, z, c, d) Source #

(<<.) :: (x, y, z, a, b) -> (x, y, z, c, d) -> (x, y, z, a, b) Source #

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

Methods

(<<.>>) :: WrappedBifunctor * * p (a -> b) (c -> d) -> WrappedBifunctor * * p a c -> WrappedBifunctor * * p b d Source #

(.>>) :: WrappedBifunctor * * p a b -> WrappedBifunctor * * p c d -> WrappedBifunctor * * p c d Source #

(<<.) :: WrappedBifunctor * * p a b -> WrappedBifunctor * * p c d -> WrappedBifunctor * * p a b Source #

Apply g => Biapply (Joker * * g) Source # 

Methods

(<<.>>) :: Joker * * g (a -> b) (c -> d) -> Joker * * g a c -> Joker * * g b d Source #

(.>>) :: Joker * * g a b -> Joker * * g c d -> Joker * * g c d Source #

(<<.) :: Joker * * g a b -> Joker * * g c d -> Joker * * g a b Source #

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

Methods

(<<.>>) :: Flip * * p (a -> b) (c -> d) -> Flip * * p a c -> Flip * * p b d Source #

(.>>) :: Flip * * p a b -> Flip * * p c d -> Flip * * p c d Source #

(<<.) :: Flip * * p a b -> Flip * * p c d -> Flip * * p a b Source #

Apply f => Biapply (Clown * * f) Source # 

Methods

(<<.>>) :: Clown * * f (a -> b) (c -> d) -> Clown * * f a c -> Clown * * f b d Source #

(.>>) :: Clown * * f a b -> Clown * * f c d -> Clown * * f c d Source #

(<<.) :: Clown * * f a b -> Clown * * f c d -> Clown * * f a b Source #

(Biapply p, Biapply q) => Biapply (Product * * p q) Source # 

Methods

(<<.>>) :: Product * * p q (a -> b) (c -> d) -> Product * * p q a c -> Product * * p q b d Source #

(.>>) :: Product * * p q a b -> Product * * p q c d -> Product * * p q c d Source #

(<<.) :: Product * * p q a b -> Product * * p q c d -> Product * * p q a b Source #

(Apply f, Biapply p) => Biapply (Tannen * * * f p) Source # 

Methods

(<<.>>) :: Tannen * * * f p (a -> b) (c -> d) -> Tannen * * * f p a c -> Tannen * * * f p b d Source #

(.>>) :: Tannen * * * f p a b -> Tannen * * * f p c d -> Tannen * * * f p c d Source #

(<<.) :: Tannen * * * f p a b -> Tannen * * * f p c d -> Tannen * * * f p a b Source #

(Biapply p, Apply f, Apply g) => Biapply (Biff * * * * p f g) Source # 

Methods

(<<.>>) :: Biff * * * * p f g (a -> b) (c -> d) -> Biff * * * * p f g a c -> Biff * * * * p f g b d Source #

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

(<<.) :: Biff * * * * p f g a b -> Biff * * * * p f g c d -> Biff * * * * p f g a b Source #

(<<$>>) :: (a -> b) -> a -> b infixl 4 #

(<<..>>) :: Biapply p => p a c -> p (a -> b) (c -> d) -> p b d infixl 4 Source #

bilift2 :: Biapply w => (a -> b -> c) -> (d -> e -> f) -> w a d -> w b e -> w c f Source #

Lift binary functions

bilift3 :: Biapply w => (a -> b -> c -> d) -> (e -> f -> g -> h) -> w a e -> w b f -> w c g -> w d h Source #

Lift ternary functions