bifunctors-5.2: Bifunctors

Copyright(C) 2008-2016 Jesse Selover, Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Data.Bifunctor.Product

Description

The product of two bifunctors.

Synopsis

Documentation

data Product f g a b Source

Form the product of two bifunctors

Constructors

Pair (f a b) (g a b) 

Instances

BifunctorFunctor k k k k (Product k k p) Source 

Methods

bifmap :: (k :-> k) a q -> (k :-> k) (Product k k p a) (Product k k p q) Source

BifunctorComonad k k (Product k k p) Source 

Methods

biextract :: Product k k p a b c -> a b c Source

biextend :: (k :-> k) (Product k k p a) q -> (k :-> k) (Product k k p a) (Product k k p q) Source

biduplicate :: Product k k p a b c -> Product k k p (Product k k p a) b c Source

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

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

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

Methods

bifold :: Monoid m => Product * * f g m m -> m Source

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Product * * f g a b -> m Source

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

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

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

Methods

bitraverse :: Applicative b => (a -> b c) -> (d -> b e) -> Product * * f g a d -> b (Product * * f g c e) 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

Generic1 (Product k * f g a) Source 

Associated Types

type Rep1 (Product k * f g a :: * -> *) :: * -> *

Methods

from1 :: Product k * f g a b -> Rep1 (Product k * f g a) b

to1 :: Rep1 (Product k * f g a) b -> Product k * f g a b

(Eq (f a b), Eq (g a b)) => Eq (Product k k f g a b) Source 

Methods

(==) :: Product k k f g a b -> Product k k f g a b -> Bool

(/=) :: Product k k f g a b -> Product k k f g a b -> Bool

(Ord (f a b), Ord (g a b)) => Ord (Product k k f g a b) Source 

Methods

compare :: Product k k f g a b -> Product k k f g a b -> Ordering

(<) :: Product k k f g a b -> Product k k f g a b -> Bool

(<=) :: Product k k f g a b -> Product k k f g a b -> Bool

(>) :: Product k k f g a b -> Product k k f g a b -> Bool

(>=) :: Product k k f g a b -> Product k k f g a b -> Bool

max :: Product k k f g a b -> Product k k f g a b -> Product k k f g a b

min :: Product k k f g a b -> Product k k f g a b -> Product k k f g a b

(Read (f a b), Read (g a b)) => Read (Product k k f g a b) Source 

Methods

readsPrec :: Int -> ReadS (Product k k f g a b)

readList :: ReadS [Product k k f g a b]

readPrec :: ReadPrec (Product k k f g a b)

readListPrec :: ReadPrec [Product k k f g a b]

(Show (f a b), Show (g a b)) => Show (Product k k f g a b) Source 

Methods

showsPrec :: Int -> Product k k f g a b -> ShowS

show :: Product k k f g a b -> String

showList :: [Product k k f g a b] -> ShowS

Generic (Product k k f g a b) Source 

Associated Types

type Rep (Product k k f g a b) :: * -> *

Methods

from :: Product k k f g a b -> Rep (Product k k f g a b) x

to :: Rep (Product k k f g a b) x -> Product k k f g a b

type Rep1 (Product k k1 f g a) Source 
type Rep (Product k k1 f g a b) Source