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

Data.Profunctor.Linear

Description

This module provides profunctor classes and instances.

Please import this module qualified.

Some of the definitions in this module are heavily connected to and motivated by linear optics. Please see Control.Optics.Linear and other optics modules for motivations for the definitions provided here.

Connections to Linear Optics

Synopsis

Documentation

class Profunctor (arr :: Type -> Type -> Type) where Source #

A Profunctor can be thought of as a computation that involves taking a(s) as input and returning b(s). These computations compose with (linear) functions. Profunctors generalize the function arrow ->.

Hence, think of a value of type x arr y for profunctor arr to be something like a function from x to y.

Laws:

lmap id = id
lmap (f . g) = lmap f . lmap g
rmap id = id
rmap (f . g) = rmap f . rmap g

Minimal complete definition

dimap | lmap, rmap

Methods

dimap :: (s %1 -> a) -> (b %1 -> t) -> (a `arr` b) -> s `arr` t Source #

lmap :: (s %1 -> a) -> (a `arr` t) -> s `arr` t Source #

rmap :: (b %1 -> t) -> (s `arr` b) -> s `arr` t Source #

Instances

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

Defined in Data.Profunctor.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 #

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 #

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 #

Profunctor (Exchange a b) Source # 
Instance details

Defined in Data.Profunctor.Linear

Methods

dimap :: (s %1 -> a0) -> (b0 %1 -> t) -> Exchange a b a0 b0 -> Exchange a b s t Source #

lmap :: (s %1 -> a0) -> Exchange a b a0 t -> Exchange a b s t Source #

rmap :: (b0 %1 -> t) -> Exchange a b s b0 -> Exchange a b s t Source #

Profunctor (Market a b) Source # 
Instance details

Defined in Data.Profunctor.Linear

Methods

dimap :: (s %1 -> a0) -> (b0 %1 -> t) -> Market a b a0 b0 -> Market a b s t Source #

lmap :: (s %1 -> a0) -> Market a b a0 t -> Market a b s t Source #

rmap :: (b0 %1 -> t) -> Market a b s b0 -> Market a b s t Source #

Profunctor (->) Source # 
Instance details

Defined in Data.Profunctor.Linear

Methods

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

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

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

Profunctor (FUN 'One :: TYPE LiftedRep -> TYPE LiftedRep -> Type) Source # 
Instance details

Defined in Data.Profunctor.Linear

Methods

dimap :: (s %1 -> a) -> (b %1 -> t) -> FUN 'One a b -> FUN 'One s t Source #

lmap :: (s %1 -> a) -> FUN 'One a t -> FUN 'One s t Source #

rmap :: (b %1 -> t) -> FUN 'One s b -> FUN 'One s t Source #

class (SymmetricMonoidal m u, Profunctor arr) => Monoidal m u arr where Source #

A (Monoidal m u arr) is a profunctor arr that can be sequenced with the bifunctor m. In rough terms, you can combine two function-like things to one function-like thing that holds both input and output types with the bifunctor m.

Methods

(***) :: (a `arr` b) -> (x `arr` y) -> (a `m` x) `arr` (b `m` y) infixr 3 Source #

unit :: u `arr` u Source #

Instances

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

Defined in Data.Profunctor.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 #

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.Linear

Methods

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

unit :: Kleisli f () () 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 #

Monoidal Either Void (->) Source # 
Instance details

Defined in Data.Profunctor.Linear

Methods

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

unit :: Void -> Void Source #

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

Defined in Data.Profunctor.Linear

Methods

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

unit :: () -> () Source #

Monoidal Either Void (FUN 'One :: TYPE LiftedRep -> TYPE LiftedRep -> Type) Source # 
Instance details

Defined in Data.Profunctor.Linear

Methods

(***) :: FUN 'One a b -> FUN 'One x y -> FUN 'One (Either a x) (Either b y) Source #

unit :: FUN 'One Void Void Source #

Monoidal (,) () (FUN 'One :: TYPE LiftedRep -> TYPE LiftedRep -> Type) Source # 
Instance details

Defined in Data.Profunctor.Linear

Methods

(***) :: FUN 'One a b -> FUN 'One x y -> FUN 'One (a, x) (b, y) Source #

unit :: FUN 'One () () Source #

class (SymmetricMonoidal m u, Profunctor arr) => Strong m u arr where Source #

A (Strong m u arr) instance means that the function-like thing of type a arr b can be extended to pass along a value of type c as a constant via the bifunctor of type m.

This typeclass is used primarily to generalize common patterns and instances that are defined when defining optics. The two uses below are used in defining lenses and prisms respectively in Control.Optics.Linear.Internal:

If m is the tuple type constructor (,) then we can create a function-like thing of type (a,c) arr (b,c) passing along c as a constant.

If m is Either then we can create a function-like thing of type Either a c arr Either b c that either does the original function or behaves like the constant function.

Minimal complete definition

first | second

Methods

first :: (a `arr` b) -> (a `m` c) `arr` (b `m` c) Source #

second :: (b `arr` c) -> (a `m` b) `arr` (a `m` c) Source #

Instances

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

Defined in Data.Profunctor.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 #

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 #

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.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 => 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 #

Strong Either Void (Market a b) Source # 
Instance details

Defined in Data.Profunctor.Linear

Methods

first :: Market a b a0 b0 -> Market a b (Either a0 c) (Either b0 c) Source #

second :: Market a b b0 c -> Market a b (Either a0 b0) (Either a0 c) Source #

Strong Either Void (->) Source # 
Instance details

Defined in Data.Profunctor.Linear

Methods

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

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

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

Defined in Data.Profunctor.Linear

Methods

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

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

Strong Either Void (FUN 'One :: TYPE LiftedRep -> TYPE LiftedRep -> Type) Source # 
Instance details

Defined in Data.Profunctor.Linear

Methods

first :: FUN 'One a b -> FUN 'One (Either a c) (Either b c) Source #

second :: FUN 'One b c -> FUN 'One (Either a b) (Either a c) Source #

Strong (,) () (FUN 'One :: TYPE LiftedRep -> TYPE LiftedRep -> Type) Source # 
Instance details

Defined in Data.Profunctor.Linear

Methods

first :: FUN 'One a b -> FUN 'One (a, c) (b, c) Source #

second :: FUN 'One b c -> FUN 'One (a, b) (a, c) Source #

class (Strong (,) () arr, Strong Either Void arr) => Wandering arr where Source #

A Wandering arr instance means that there is a wander function which is the traversable generalization of the classic lens function:

forall f. Functor f => (a -> f b) -> (s -> f t)

in our notation:

forall arr. (HasKleisliFunctor arr) => (a `arr` b) -> (s `arr` t)

wander specializes the Functor constraint to a control applicative:

forall f. Applicative f => (a -> f b) -> (s -> f t)
forall arr. (HasKleisliApplicative arr) => (a `arr` b) -> (s `arr` t)

where HasKleisliFunctor or HasKleisliApplicative are some constraints which allow for the arr to be Kleisli f for control functors or applicatives f.

Methods

wander :: forall s t a b. (forall f. Applicative f => (a %1 -> f b) -> s %1 -> f t) -> (a `arr` b) -> s `arr` t Source #

Equivalently but less efficient in general:

wander :: Data.Traversable f => a `arr` b -> f a `arr` f b

Instances

Instances details
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 #

Wandering (FUN 'One :: TYPE LiftedRep -> TYPE LiftedRep -> Type) Source # 
Instance details

Defined in Data.Profunctor.Linear

Methods

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

data Exchange a b s t Source #

An exchange is a pair of translation functions that encode an isomorphism; an Exchange a b s t is equivalent to a Iso a b s t.

Constructors

Exchange (s %1 -> a) (b %1 -> t) 

Instances

Instances details
Profunctor (Exchange a b) Source # 
Instance details

Defined in Data.Profunctor.Linear

Methods

dimap :: (s %1 -> a0) -> (b0 %1 -> t) -> Exchange a b a0 b0 -> Exchange a b s t Source #

lmap :: (s %1 -> a0) -> Exchange a b a0 t -> Exchange a b s t Source #

rmap :: (b0 %1 -> t) -> Exchange a b s b0 -> Exchange a b s t Source #

data Market a b s t Source #

A market is a pair of constructor and deconstructor functions that encode a prism; a Market a b s t is equivalent to a Prism a b s t.

Constructors

Market (b %1 -> t) (s %1 -> Either t a) 

Instances

Instances details
Strong Either Void (Market a b) Source # 
Instance details

Defined in Data.Profunctor.Linear

Methods

first :: Market a b a0 b0 -> Market a b (Either a0 c) (Either b0 c) Source #

second :: Market a b b0 c -> Market a b (Either a0 b0) (Either a0 c) Source #

Profunctor (Market a b) Source # 
Instance details

Defined in Data.Profunctor.Linear

Methods

dimap :: (s %1 -> a0) -> (b0 %1 -> t) -> Market a b a0 b0 -> Market a b s t Source #

lmap :: (s %1 -> a0) -> Market a b a0 t -> Market a b s t Source #

rmap :: (b0 %1 -> t) -> Market a b s b0 -> Market a b s t Source #

runMarket :: Market a b s t %1 -> (b %1 -> t, s %1 -> Either t a) Source #