linear-base-0.3.1: Standard library for linear types.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Profunctor.Kleisli.Linear

Description

This module provides (linear) Kleisli and CoKleisli arrows

This module is meant to be imported qualified, perhaps as below.

import qualified Data.Profunctor.Kleisli as Linear

What are Kleisli arrows?

The basic idea is that a Kleisli arrow is like a function arrow and Kleisli m a b is similar to a function from a to b. Basically:

type Kleisli m a b = a %1-> m b

Why make this definition?

It let's us view Kleisli m for a certain m as a certain kind of function arrow, give it instances, abstract over it an so on.

For instance, if m is any functor, Kleisli m is a Profunctor.

CoKleisli

A CoKleisli arrow is just one that represents a computation from a m a to an a via a linear arrow. (It's a Co-something because it reverses the order of the function arrows in the something.)

Synopsis

Documentation

newtype Kleisli m a b Source #

Linear Kleisli arrows for the monad m. These arrows are still useful in the case where m is not a monad however, and some profunctorial properties still hold in this weaker setting.

Constructors

Kleisli 

Fields

Instances

Instances details
Functor f => Monoidal Either Void (Kleisli f) Source # 
Instance details

Defined in Data.Profunctor.Kleisli.Linear

Methods

(***) :: Kleisli f a b -> Kleisli f x y -> Kleisli f (Either a x) (Either b y) Source #

unit :: Kleisli f Void Void Source #

Applicative f => Monoidal (,) () (Kleisli f) Source # 
Instance details

Defined in Data.Profunctor.Kleisli.Linear

Methods

(***) :: Kleisli f a b -> Kleisli f x y -> Kleisli f (a, x) (b, y) Source #

unit :: Kleisli f () () Source #

Applicative f => Strong Either Void (Kleisli f) Source # 
Instance details

Defined in Data.Profunctor.Kleisli.Linear

Methods

first :: Kleisli f a b -> Kleisli f (Either a c) (Either b c) Source #

second :: Kleisli f b c -> Kleisli f (Either a b) (Either a c) Source #

Functor f => Strong (,) () (Kleisli f) Source # 
Instance details

Defined in Data.Profunctor.Kleisli.Linear

Methods

first :: Kleisli f a b -> Kleisli f (a, c) (b, c) Source #

second :: Kleisli f b c -> Kleisli f (a, b) (a, c) Source #

Functor f => Profunctor (Kleisli f) Source # 
Instance details

Defined in Data.Profunctor.Kleisli.Linear

Methods

dimap :: (s %1 -> a) -> (b %1 -> t) -> Kleisli f a b -> Kleisli f s t Source #

lmap :: (s %1 -> a) -> Kleisli f a t -> Kleisli f s t Source #

rmap :: (b %1 -> t) -> Kleisli f s b -> Kleisli f s t Source #

Applicative f => Wandering (Kleisli f) Source # 
Instance details

Defined in Data.Profunctor.Kleisli.Linear

Methods

wander :: forall s t a b. (forall (f0 :: Type -> Type). Applicative f0 => (a %1 -> f0 b) -> s %1 -> f0 t) -> Kleisli f a b -> Kleisli f s t Source #

newtype CoKleisli w a b Source #

Linear co-Kleisli arrows for the comonad w. These arrows are still useful in the case where w is not a comonad however, and some profunctorial properties still hold in this weaker setting. However stronger requirements on f are needed for profunctorial strength, so we have fewer instances.

Constructors

CoKleisli 

Fields

Instances

Instances details
Strong Either Void (CoKleisli (Const x :: Type -> Type)) Source # 
Instance details

Defined in Data.Profunctor.Kleisli.Linear

Methods

first :: CoKleisli (Const x) a b -> CoKleisli (Const x) (Either a c) (Either b c) Source #

second :: CoKleisli (Const x) b c -> CoKleisli (Const x) (Either a b) (Either a c) Source #

Functor f => Profunctor (CoKleisli f) Source # 
Instance details

Defined in Data.Profunctor.Kleisli.Linear

Methods

dimap :: (s %1 -> a) -> (b %1 -> t) -> CoKleisli f a b -> CoKleisli f s t Source #

lmap :: (s %1 -> a) -> CoKleisli f a t -> CoKleisli f s t Source #

rmap :: (b %1 -> t) -> CoKleisli f s b -> CoKleisli f s t Source #