bifunctors-5.5.1: Bifunctors

Safe HaskellSafe
LanguageHaskell98

Data.Bifunctor.Functor

Synopsis

Documentation

type (:->) p q = forall a b. p a b -> q a b infixr 0 Source #

Using parametricity as an approximation of a natural transformation in two arguments.

class BifunctorFunctor t where Source #

Minimal complete definition

bifmap

Methods

bifmap :: (p :-> q) -> t p :-> t q Source #

Instances

BifunctorFunctor k2 k1 k1 k2 (Flip k1 k2) Source # 

Methods

bifmap :: (Flip k1 k2 :-> k) p q -> (k :-> k) (t p) (t q) Source #

BifunctorFunctor k1 k2 k1 k2 (Product k1 k2 p) Source # 

Methods

bifmap :: (Product k1 k2 p :-> k) p q -> (k :-> k) (t p) (t q) Source #

BifunctorFunctor k1 k2 k1 k2 (Sum k1 k2 p) Source # 

Methods

bifmap :: (Sum k1 k2 p :-> k) p q -> (k :-> k) (t p) (t q) Source #

Functor f => BifunctorFunctor k1 k2 k1 k2 (Tannen * k1 k2 f) Source # 

Methods

bifmap :: (Tannen * k1 k2 f :-> k) p q -> (k :-> k) (t p) (t q) Source #

class BifunctorFunctor t => BifunctorMonad t where Source #

Minimal complete definition

bireturn, (bibind | bijoin)

Methods

bireturn :: p :-> t p Source #

bibind :: (p :-> t q) -> t p :-> t q Source #

bijoin :: t (t p) :-> t p Source #

Instances

BifunctorMonad k1 k2 (Sum k1 k2 p) Source # 

Methods

bireturn :: p a b -> t p a b Source #

bibind :: (Sum k1 k2 p :-> k) p (t q) -> (Sum k1 k2 p :-> k) (t p) (t q) Source #

bijoin :: t (t p) a b -> t p a b Source #

(Functor f, Monad f) => BifunctorMonad k1 k2 (Tannen * k1 k2 f) Source # 

Methods

bireturn :: p a b -> t p a b Source #

bibind :: (Tannen * k1 k2 f :-> k) p (t q) -> (Tannen * k1 k2 f :-> k) (t p) (t q) Source #

bijoin :: t (t p) a b -> t p a b Source #

biliftM :: BifunctorMonad t => (p :-> q) -> t p :-> t q Source #

class BifunctorFunctor t => BifunctorComonad t where Source #

Minimal complete definition

biextract, (biextend | biduplicate)

Methods

biextract :: t p :-> p Source #

biextend :: (t p :-> q) -> t p :-> t q Source #

biduplicate :: t p :-> t (t p) Source #

Instances

BifunctorComonad k1 k2 (Product k1 k2 p) Source # 

Methods

biextract :: t p a b -> p a b Source #

biextend :: (Product k1 k2 p :-> k) (t p) q -> (Product k1 k2 p :-> k) (t p) (t q) Source #

biduplicate :: t p a b -> t (t p) a b Source #

Comonad f => BifunctorComonad k1 k2 (Tannen * k1 k2 f) Source # 

Methods

biextract :: t p a b -> p a b Source #

biextend :: (Tannen * k1 k2 f :-> k) (t p) q -> (Tannen * k1 k2 f :-> k) (t p) (t q) Source #

biduplicate :: t p a b -> t (t p) a b Source #

biliftW :: BifunctorComonad t => (p :-> q) -> t p :-> t q Source #