kindly-functors-0.1.0.1: A category polymorphic `Functor` typeclass
Safe HaskellSafe-Inferred
LanguageHaskell2010

Kindly.Bifunctor

Description

Two Parameter Functors of arbitrary categories.

Synopsis

Documentation

type Bifunctor cat1 cat2 p = (MapArg2 cat1 cat2 p, forall x. MapArg1 cat2 (p x)) Source #

A CategoricalFunctor of kind Type -> Type mapping from an arbitrary category cat1 to a functor category cat2 ~> (->).

bimap :: forall cat1 cat2 p. Bifunctor cat1 cat2 p => forall a b a' b'. (a `cat1` a') -> (b `cat2` b') -> p a b -> p a' b' Source #

Lift a morphism cat1 a a' and a morphism cat2 b b' into a function p a b -> p a' b'.

lmap :: (Category cat2, Bifunctor cat1 cat2 p) => (a `cat1` b) -> p a x -> p b x Source #

Lift a morphism cat1 a b into a function p a x -> p b x.

rmap :: Bifunctor cat1 cat2 p => (a `cat2` b) -> p x a -> p x b Source #

Lift a morphism cat2 a b into a function p x a -> p x b.

Orphan instances

MapArg2 Op (->) (->) Source # 
Instance details

Methods

map2 :: forall (a :: from) (b :: from). Op a b -> forall (x :: s). (a -> x) -> b -> x Source #

MapArg2 (->) (->) Either Source # 
Instance details

Methods

map2 :: forall (a :: from) (b :: from). (a -> b) -> forall (x :: s). Either a x -> Either b x Source #

MapArg2 (->) (->) Arg Source # 
Instance details

Methods

map2 :: forall (a :: from) (b :: from). (a -> b) -> forall (x :: s). Arg a x -> Arg b x Source #

MapArg2 (->) (->) (,) Source # 
Instance details

Methods

map2 :: forall (a :: from) (b :: from). (a -> b) -> forall (x :: s). (a, x) -> (b, x) Source #

MapArg2 (->) (->) (Const :: Type -> Type -> Type) Source # 
Instance details

Methods

map2 :: forall (a :: from) (b :: from). (a -> b) -> forall (x :: s). Const a x -> Const b x Source #

MapArg2 (->) (->) ((,,) a :: Type -> Type -> Type) Source # 
Instance details

Methods

map2 :: forall (a0 :: from) (b :: from). (a0 -> b) -> forall (x :: s). (a, a0, x) -> (a, b, x) Source #

MapArg2 (->) (->) (K1 i :: Type -> Type -> Type) Source # 
Instance details

Methods

map2 :: forall (a :: from) (b :: from). (a -> b) -> forall (x :: s). K1 i a x -> K1 i b x Source #

MapArg2 (->) (->) ((,,,) a b :: Type -> Type -> Type) Source # 
Instance details

Methods

map2 :: forall (a0 :: from) (b0 :: from). (a0 -> b0) -> forall (x :: s). (a, b, a0, x) -> (a, b, b0, x) Source #

MapArg2 (->) (->) ((,,,,) a b c :: Type -> Type -> Type) Source # 
Instance details

Methods

map2 :: forall (a0 :: from) (b0 :: from). (a0 -> b0) -> forall (x :: s). (a, b, c, a0, x) -> (a, b, c, b0, x) Source #

MapArg2 (->) (->) ((,,,,,) a b c d :: Type -> Type -> Type) Source # 
Instance details

Methods

map2 :: forall (a0 :: from) (b0 :: from). (a0 -> b0) -> forall (x :: s). (a, b, c, d, a0, x) -> (a, b, c, d, b0, x) Source #

MapArg2 (->) (->) ((,,,,,,) a b c d e :: Type -> Type -> Type) Source # 
Instance details

Methods

map2 :: forall (a0 :: from) (b0 :: from). (a0 -> b0) -> forall (x :: s). (a, b, c, d, e, a0, x) -> (a, b, c, d, e, b0, x) Source #

CategoricalFunctor Either Source # 
Instance details

Associated Types

type Dom Either :: from -> from -> Type Source #

type Cod Either :: to -> to -> Type Source #

Methods

map :: forall (a :: from) (b :: from). Dom Either a b -> Cod Either (Either a) (Either b) Source #

CategoricalFunctor Arg Source # 
Instance details

Associated Types

type Dom Arg :: from -> from -> Type Source #

type Cod Arg :: to -> to -> Type Source #

Methods

map :: forall (a :: from) (b :: from). Dom Arg a b -> Cod Arg (Arg a) (Arg b) Source #

CategoricalFunctor These Source # 
Instance details

Associated Types

type Dom These :: from -> from -> Type Source #

type Cod These :: to -> to -> Type Source #

Methods

map :: forall (a :: from) (b :: from). Dom These a b -> Cod These (These a) (These b) Source #

CategoricalFunctor (,) Source # 
Instance details

Associated Types

type Dom (,) :: from -> from -> Type Source #

type Cod (,) :: to -> to -> Type Source #

Methods

map :: forall (a :: from) (b :: from). Dom (,) a b -> Cod (,) ((,) a) ((,) b) Source #

CategoricalFunctor (Const :: Type -> Type -> Type) Source # 
Instance details

Associated Types

type Dom Const :: from -> from -> Type Source #

type Cod Const :: to -> to -> Type Source #

Methods

map :: forall (a :: from) (b :: from). Dom Const a b -> Cod Const (Const a) (Const b) Source #

CategoricalFunctor ((,,) a :: Type -> Type -> Type) Source # 
Instance details

Associated Types

type Dom ((,,) a) :: from -> from -> Type Source #

type Cod ((,,) a) :: to -> to -> Type Source #

Methods

map :: forall (a0 :: from) (b :: from). Dom ((,,) a) a0 b -> Cod ((,,) a) ((,,) a a0) ((,,) a b) Source #

CategoricalFunctor (K1 i :: Type -> Type -> Type) Source # 
Instance details

Associated Types

type Dom (K1 i) :: from -> from -> Type Source #

type Cod (K1 i) :: to -> to -> Type Source #

Methods

map :: forall (a :: from) (b :: from). Dom (K1 i) a b -> Cod (K1 i) (K1 i a) (K1 i b) Source #

CategoricalFunctor ((,,,) a b :: Type -> Type -> Type) Source # 
Instance details

Associated Types

type Dom ((,,,) a b) :: from -> from -> Type Source #

type Cod ((,,,) a b) :: to -> to -> Type Source #

Methods

map :: forall (a0 :: from) (b0 :: from). Dom ((,,,) a b) a0 b0 -> Cod ((,,,) a b) ((,,,) a b a0) ((,,,) a b b0) Source #

CategoricalFunctor (->) Source # 
Instance details

Associated Types

type Dom (->) :: from -> from -> Type Source #

type Cod (->) :: to -> to -> Type Source #

Methods

map :: forall (a :: from) (b :: from). Dom (->) a b -> Cod (->) ((->) a) ((->) b) Source #

CategoricalFunctor ((,,,,) a b c :: Type -> Type -> Type) Source # 
Instance details

Associated Types

type Dom ((,,,,) a b c) :: from -> from -> Type Source #

type Cod ((,,,,) a b c) :: to -> to -> Type Source #

Methods

map :: forall (a0 :: from) (b0 :: from). Dom ((,,,,) a b c) a0 b0 -> Cod ((,,,,) a b c) ((,,,,) a b c a0) ((,,,,) a b c b0) Source #

CategoricalFunctor ((,,,,,) a b c d :: Type -> Type -> Type) Source # 
Instance details

Associated Types

type Dom ((,,,,,) a b c d) :: from -> from -> Type Source #

type Cod ((,,,,,) a b c d) :: to -> to -> Type Source #

Methods

map :: forall (a0 :: from) (b0 :: from). Dom ((,,,,,) a b c d) a0 b0 -> Cod ((,,,,,) a b c d) ((,,,,,) a b c d a0) ((,,,,,) a b c d b0) Source #

CategoricalFunctor ((,,,,,,) a b c d e :: Type -> Type -> Type) Source # 
Instance details

Associated Types

type Dom ((,,,,,,) a b c d e) :: from -> from -> Type Source #

type Cod ((,,,,,,) a b c d e) :: to -> to -> Type Source #

Methods

map :: forall (a0 :: from) (b0 :: from). Dom ((,,,,,,) a b c d e) a0 b0 -> Cod ((,,,,,,) a b c d e) ((,,,,,,) a b c d e a0) ((,,,,,,) a b c d e b0) Source #