bifunctors-5.2: Bifunctors

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

Data.Biapplicative

Contents

Description

 

Synopsis

Biapplicative bifunctors

class Bifunctor p => Biapplicative p where Source

Minimal complete definition

bipure, (<<*>>)

Methods

bipure :: a -> b -> p a b Source

(<<*>>) :: 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 ≡ bimap (const id) (const id) <<$>> a <<*>> b

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

Instances

Biapplicative (,) Source 

Methods

bipure :: a -> b -> (a, b) Source

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

(*>>) :: (a, b) -> (c, d) -> (c, d) Source

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

Biapplicative Const Source 

Methods

bipure :: a -> b -> Const a b Source

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

Biapplicative Arg Source 

Methods

bipure :: a -> b -> Arg a b Source

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

Monoid x => Biapplicative ((,,) x) Source 

Methods

bipure :: a -> b -> (x, a, b) Source

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

Biapplicative (Tagged *) Source 

Methods

bipure :: a -> b -> Tagged * a b Source

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

(Monoid x, Monoid y) => Biapplicative ((,,,) x y) Source 

Methods

bipure :: a -> b -> (x, y, a, b) Source

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

(Monoid x, Monoid y, Monoid z) => Biapplicative ((,,,,) x y z) Source 

Methods

bipure :: a -> b -> (x, y, z, a, b) Source

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

Applicative f => Biapplicative (Clown * * f) Source 

Methods

bipure :: a -> b -> Clown * * f a b Source

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

Biapplicative p => Biapplicative (Flip * * p) Source 

Methods

bipure :: a -> b -> Flip * * p a b Source

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

Applicative g => Biapplicative (Joker * * g) Source 

Methods

bipure :: a -> b -> Joker * * g a b Source

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

Biapplicative p => Biapplicative (WrappedBifunctor * * p) Source 

Methods

bipure :: a -> b -> WrappedBifunctor * * p a b Source

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

(Monoid x, Monoid y, Monoid z, Monoid w) => Biapplicative ((,,,,,) x y z w) Source 

Methods

bipure :: a -> b -> (x, y, z, w, a, b) Source

(<<*>>) :: (x, y, z, w, a -> b, c -> d) -> (x, y, z, w, a, c) -> (x, y, z, w, b, d) Source

(*>>) :: (x, y, z, w, a, b) -> (x, y, z, w, c, d) -> (x, y, z, w, c, d) Source

(<<*) :: (x, y, z, w, a, b) -> (x, y, z, w, c, d) -> (x, y, z, w, a, b) Source

(Biapplicative f, Biapplicative g) => Biapplicative (Product * * f g) Source 

Methods

bipure :: a -> b -> Product * * f g a b Source

(<<*>>) :: Product * * f g (a -> b) (c -> d) -> Product * * f g a c -> Product * * f g b d Source

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

(<<*) :: Product * * f g a b -> Product * * f g c d -> Product * * f g a b Source

(Monoid x, Monoid y, Monoid z, Monoid w, Monoid v) => Biapplicative ((,,,,,,) x y z w v) Source 

Methods

bipure :: a -> b -> (x, y, z, w, v, a, b) Source

(<<*>>) :: (x, y, z, w, v, a -> b, c -> d) -> (x, y, z, w, v, a, c) -> (x, y, z, w, v, b, d) Source

(*>>) :: (x, y, z, w, v, a, b) -> (x, y, z, w, v, c, d) -> (x, y, z, w, v, c, d) Source

(<<*) :: (x, y, z, w, v, a, b) -> (x, y, z, w, v, c, d) -> (x, y, z, w, v, a, b) Source

(Applicative f, Biapplicative p) => Biapplicative (Tannen * * * f p) Source 

Methods

bipure :: a -> b -> Tannen * * * f p a b Source

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

(Biapplicative p, Applicative f, Applicative g) => Biapplicative (Biff * * * * p f g) Source 

Methods

bipure :: a -> b -> Biff * * * * p f g a b Source

(<<*>>) :: 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 Source

(<<**>>) :: Biapplicative p => p a c -> p (a -> b) (c -> d) -> p b d infixl 4 Source

biliftA2 :: Biapplicative w => (a -> b -> c) -> (d -> e -> f) -> w a d -> w b e -> w c f Source

Lift binary functions

biliftA3 :: Biapplicative 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