profunctor-monad-0.1.0.0: Monadic bidirectional programming

Safe HaskellSafe
LanguageHaskell2010

Profunctor.Monad.Cofunctor

Synopsis

Documentation

type Profunctor p = (Cofunctor p, ForallF Functor p) Source #

A Profunctor is a bifunctor p :: * -> * -> * from the product of an arbitrary category, denoted First p, and (->).

This is a generalization of the profunctors package's Profunctor, where First p ~ (->).

A profunctor is two functors on different domains at once, one contravariant, one covariant, and that is made clear by this definition specifying Cofunctor and Functor separately.

class Category (First p) => Cofunctor p where Source #

Types p :: * -> * -> * which are contravariant functors over their first parameter.

Functor laws:

lmap id = id
lmap (i >>> j) = lmap i . lmap j

If the domain First p is an Arrow, and if for every a, the type p a is an instance of Applicative, then a pure arrow arr f should correspond to an "applicative natural transformation":

lmap (arr f) (p <*> q)
=
lmap (arr f) p <*> lmap (arr f) q
lmap (arr f) (pure a) = pure a

The following may not be true in general, but seems to hold in practice, when the instance Applicative (p a) orders effects from left to right, in particular that should be the case if there is also a Monad (p a):

lmap (first i) (lmap (arr fst) p <*> lmap (arr snd) q)
=
lmap (first i >>> arr fst) p <*> lmap (arr snd) q

Associated Types

type First p :: * -> * -> * Source #

Domain of the functor.

Methods

lmap :: First p y x -> p x a -> p y a Source #

Mapping morphisms from First p to (->).

Instances
Monad m => Cofunctor (Kleisli m) Source # 
Instance details

Defined in Profunctor.Monad.Cofunctor

Associated Types

type First (Kleisli m) :: Type -> Type -> Type Source #

Methods

lmap :: First (Kleisli m) y x -> Kleisli m x a -> Kleisli m y a Source #

Cofunctor ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Profunctor.Monad.Cofunctor

Associated Types

type First (->) :: Type -> Type -> Type Source #

Methods

lmap :: First (->) y x -> (x -> a) -> y -> a Source #

(=.) :: (Cofunctor p, Arrow (First p)) => (y -> x) -> p x a -> p y a infixl 5 Source #

Mapping with a regular function.

(=:) :: (Cofunctor p, First p ~ Kleisli m) => (y -> m x) -> p x a -> p y a infixl 5 Source #

Monadic mapping; e.g., mapping which can fail (Maybe).

cofilter :: (Cofunctor p, First p ~ Kleisli m, Alternative m) => (x -> Bool) -> p x a -> p x a Source #