semigroupoids-5.0.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 
Bifunctor (,) 
Bifunctor Const 
Bifunctor Arg 
Bifunctor ((,,) x1) 
Bifunctor (Tagged *) 
Bifunctor ((,,,) x1 x2) 
Bifunctor ((,,,,) x1 x2 x3) 
Bifunctor p => Bifunctor (WrappedBifunctor * * p) 
Functor g => Bifunctor (Joker * * g) 
Bifunctor p => Bifunctor (Flip * * p) 
Functor f => Bifunctor (Clown * * f) 
Bifunctor ((,,,,,) x1 x2 x3 x4) 
(Bifunctor f, Bifunctor g) => Bifunctor (Product * * f g) 
Bifunctor ((,,,,,,) x1 x2 x3 x4 x5) 
(Functor f, Bifunctor p) => Bifunctor (Tannen * * * f p) 
(Bifunctor p, Functor f, Functor g) => Bifunctor (Biff * * * * p f g) 

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

(<<$>>) :: (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