profunctors-5.3: Profunctors

Copyright(C) 2011-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Profunctor

Contents

Description

For a good explanation of profunctors in Haskell see Dan Piponi's article:

http://blog.sigfpe.com/2011/07/profunctors-in-haskell.html

For more information on strength and costrength, see:

http://comonad.com/reader/2008/deriving-strength-from-laziness/

Synopsis

Profunctors

class Profunctor p where #

Formally, the class Profunctor represents a profunctor from Hask -> Hask.

Intuitively it is a bifunctor where the first argument is contravariant and the second argument is covariant.

You can define a Profunctor by either defining dimap or by defining both lmap and rmap.

If you supply dimap, you should ensure that:

dimap id idid

If you supply lmap and rmap, ensure:

lmap idid
rmap idid

If you supply both, you should also ensure:

dimap f g ≡ lmap f . rmap g

These ensure by parametricity:

dimap (f . g) (h . i) ≡ dimap g h . dimap f i
lmap (f . g) ≡ lmap g . lmap f
rmap (f . g) ≡ rmap f . rmap g

Minimal complete definition

dimap | lmap, rmap

Methods

dimap :: (a -> b) -> (c -> d) -> p b c -> p a d #

Map over both arguments at the same time.

dimap f g ≡ lmap f . rmap g

lmap :: (a -> b) -> p b c -> p a c #

Map the first argument contravariantly.

lmap f ≡ dimap f id

rmap :: (b -> c) -> p a b -> p a c #

Map the second argument covariantly.

rmapdimap id
Instances
Monad m => Profunctor (Kleisli m) # 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Kleisli m b c -> Kleisli m a d #

lmap :: (a -> b) -> Kleisli m b c -> Kleisli m a c #

rmap :: (b -> c) -> Kleisli m a b -> Kleisli m a c #

(#.) :: Coercible c b => q b c -> Kleisli m a b -> Kleisli m a c #

(.#) :: Coercible b a => Kleisli m b c -> q a b -> Kleisli m a c #

Profunctor (Tagged :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Tagged b c -> Tagged a d #

lmap :: (a -> b) -> Tagged b c -> Tagged a c #

rmap :: (b -> c) -> Tagged a b -> Tagged a c #

(#.) :: Coercible c b => q b c -> Tagged a b -> Tagged a c #

(.#) :: Coercible b a => Tagged b c -> q a b -> Tagged a c #

Profunctor (Forget r) # 
Instance details

Defined in Data.Profunctor.Types

Methods

dimap :: (a -> b) -> (c -> d) -> Forget r b c -> Forget r a d #

lmap :: (a -> b) -> Forget r b c -> Forget r a c #

rmap :: (b -> c) -> Forget r a b -> Forget r a c #

(#.) :: Coercible c b => q b c -> Forget r a b -> Forget r a c #

(.#) :: Coercible b a => Forget r b c -> q a b -> Forget r a c #

Arrow p => Profunctor (WrappedArrow p) # 
Instance details

Defined in Data.Profunctor.Types

Methods

dimap :: (a -> b) -> (c -> d) -> WrappedArrow p b c -> WrappedArrow p a d #

lmap :: (a -> b) -> WrappedArrow p b c -> WrappedArrow p a c #

rmap :: (b -> c) -> WrappedArrow p a b -> WrappedArrow p a c #

(#.) :: Coercible c b => q b c -> WrappedArrow p a b -> WrappedArrow p a c #

(.#) :: Coercible b a => WrappedArrow p b c -> q a b -> WrappedArrow p a c #

Functor f => Profunctor (Costar f) # 
Instance details

Defined in Data.Profunctor.Types

Methods

dimap :: (a -> b) -> (c -> d) -> Costar f b c -> Costar f a d #

lmap :: (a -> b) -> Costar f b c -> Costar f a c #

rmap :: (b -> c) -> Costar f a b -> Costar f a c #

(#.) :: Coercible c b => q b c -> Costar f a b -> Costar f a c #

(.#) :: Coercible b a => Costar f b c -> q a b -> Costar f a c #

Functor f => Profunctor (Star f) # 
Instance details

Defined in Data.Profunctor.Types

Methods

dimap :: (a -> b) -> (c -> d) -> Star f b c -> Star f a d #

lmap :: (a -> b) -> Star f b c -> Star f a c #

rmap :: (b -> c) -> Star f a b -> Star f a c #

(#.) :: Coercible c b => q b c -> Star f a b -> Star f a c #

(.#) :: Coercible b a => Star f b c -> q a b -> Star f a c #

Profunctor (Copastro p) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

dimap :: (a -> b) -> (c -> d) -> Copastro p b c -> Copastro p a d #

lmap :: (a -> b) -> Copastro p b c -> Copastro p a c #

rmap :: (b -> c) -> Copastro p a b -> Copastro p a c #

(#.) :: Coercible c b => q b c -> Copastro p a b -> Copastro p a c #

(.#) :: Coercible b a => Copastro p b c -> q a b -> Copastro p a c #

Profunctor (Cotambara p) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

dimap :: (a -> b) -> (c -> d) -> Cotambara p b c -> Cotambara p a d #

lmap :: (a -> b) -> Cotambara p b c -> Cotambara p a c #

rmap :: (b -> c) -> Cotambara p a b -> Cotambara p a c #

(#.) :: Coercible c b => q b c -> Cotambara p a b -> Cotambara p a c #

(.#) :: Coercible b a => Cotambara p b c -> q a b -> Cotambara p a c #

Profunctor (Pastro p) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

dimap :: (a -> b) -> (c -> d) -> Pastro p b c -> Pastro p a d #

lmap :: (a -> b) -> Pastro p b c -> Pastro p a c #

rmap :: (b -> c) -> Pastro p a b -> Pastro p a c #

(#.) :: Coercible c b => q b c -> Pastro p a b -> Pastro p a c #

(.#) :: Coercible b a => Pastro p b c -> q a b -> Pastro p a c #

Profunctor p => Profunctor (Tambara p) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

dimap :: (a -> b) -> (c -> d) -> Tambara p b c -> Tambara p a d #

lmap :: (a -> b) -> Tambara p b c -> Tambara p a c #

rmap :: (b -> c) -> Tambara p a b -> Tambara p a c #

(#.) :: Coercible c b => q b c -> Tambara p a b -> Tambara p a c #

(.#) :: Coercible b a => Tambara p b c -> q a b -> Tambara p a c #

Profunctor (Environment p) # 
Instance details

Defined in Data.Profunctor.Closed

Methods

dimap :: (a -> b) -> (c -> d) -> Environment p b c -> Environment p a d #

lmap :: (a -> b) -> Environment p b c -> Environment p a c #

rmap :: (b -> c) -> Environment p a b -> Environment p a c #

(#.) :: Coercible c b => q b c -> Environment p a b -> Environment p a c #

(.#) :: Coercible b a => Environment p b c -> q a b -> Environment p a c #

Profunctor p => Profunctor (Closure p) # 
Instance details

Defined in Data.Profunctor.Closed

Methods

dimap :: (a -> b) -> (c -> d) -> Closure p b c -> Closure p a d #

lmap :: (a -> b) -> Closure p b c -> Closure p a c #

rmap :: (b -> c) -> Closure p a b -> Closure p a c #

(#.) :: Coercible c b => q b c -> Closure p a b -> Closure p a c #

(.#) :: Coercible b a => Closure p b c -> q a b -> Closure p a c #

Profunctor (CopastroSum p) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

dimap :: (a -> b) -> (c -> d) -> CopastroSum p b c -> CopastroSum p a d #

lmap :: (a -> b) -> CopastroSum p b c -> CopastroSum p a c #

rmap :: (b -> c) -> CopastroSum p a b -> CopastroSum p a c #

(#.) :: Coercible c b => q b c -> CopastroSum p a b -> CopastroSum p a c #

(.#) :: Coercible b a => CopastroSum p b c -> q a b -> CopastroSum p a c #

Profunctor (CotambaraSum p) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

dimap :: (a -> b) -> (c -> d) -> CotambaraSum p b c -> CotambaraSum p a d #

lmap :: (a -> b) -> CotambaraSum p b c -> CotambaraSum p a c #

rmap :: (b -> c) -> CotambaraSum p a b -> CotambaraSum p a c #

(#.) :: Coercible c b => q b c -> CotambaraSum p a b -> CotambaraSum p a c #

(.#) :: Coercible b a => CotambaraSum p b c -> q a b -> CotambaraSum p a c #

Profunctor (PastroSum p) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

dimap :: (a -> b) -> (c -> d) -> PastroSum p b c -> PastroSum p a d #

lmap :: (a -> b) -> PastroSum p b c -> PastroSum p a c #

rmap :: (b -> c) -> PastroSum p a b -> PastroSum p a c #

(#.) :: Coercible c b => q b c -> PastroSum p a b -> PastroSum p a c #

(.#) :: Coercible b a => PastroSum p b c -> q a b -> PastroSum p a c #

Profunctor p => Profunctor (TambaraSum p) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

dimap :: (a -> b) -> (c -> d) -> TambaraSum p b c -> TambaraSum p a d #

lmap :: (a -> b) -> TambaraSum p b c -> TambaraSum p a c #

rmap :: (b -> c) -> TambaraSum p a b -> TambaraSum p a c #

(#.) :: Coercible c b => q b c -> TambaraSum p a b -> TambaraSum p a c #

(.#) :: Coercible b a => TambaraSum p b c -> q a b -> TambaraSum p a c #

Profunctor (FreeTraversing p) # 
Instance details

Defined in Data.Profunctor.Traversing

Methods

dimap :: (a -> b) -> (c -> d) -> FreeTraversing p b c -> FreeTraversing p a d #

lmap :: (a -> b) -> FreeTraversing p b c -> FreeTraversing p a c #

rmap :: (b -> c) -> FreeTraversing p a b -> FreeTraversing p a c #

(#.) :: Coercible c b => q b c -> FreeTraversing p a b -> FreeTraversing p a c #

(.#) :: Coercible b a => FreeTraversing p b c -> q a b -> FreeTraversing p a c #

Profunctor p => Profunctor (CofreeTraversing p) # 
Instance details

Defined in Data.Profunctor.Traversing

Methods

dimap :: (a -> b) -> (c -> d) -> CofreeTraversing p b c -> CofreeTraversing p a d #

lmap :: (a -> b) -> CofreeTraversing p b c -> CofreeTraversing p a c #

rmap :: (b -> c) -> CofreeTraversing p a b -> CofreeTraversing p a c #

(#.) :: Coercible c b => q b c -> CofreeTraversing p a b -> CofreeTraversing p a c #

(.#) :: Coercible b a => CofreeTraversing p b c -> q a b -> CofreeTraversing p a c #

Profunctor (FreeMapping p) # 
Instance details

Defined in Data.Profunctor.Mapping

Methods

dimap :: (a -> b) -> (c -> d) -> FreeMapping p b c -> FreeMapping p a d #

lmap :: (a -> b) -> FreeMapping p b c -> FreeMapping p a c #

rmap :: (b -> c) -> FreeMapping p a b -> FreeMapping p a c #

(#.) :: Coercible c b => q b c -> FreeMapping p a b -> FreeMapping p a c #

(.#) :: Coercible b a => FreeMapping p b c -> q a b -> FreeMapping p a c #

Profunctor p => Profunctor (CofreeMapping p) # 
Instance details

Defined in Data.Profunctor.Mapping

Methods

dimap :: (a -> b) -> (c -> d) -> CofreeMapping p b c -> CofreeMapping p a d #

lmap :: (a -> b) -> CofreeMapping p b c -> CofreeMapping p a c #

rmap :: (b -> c) -> CofreeMapping p a b -> CofreeMapping p a c #

(#.) :: Coercible c b => q b c -> CofreeMapping p a b -> CofreeMapping p a c #

(.#) :: Coercible b a => CofreeMapping p b c -> q a b -> CofreeMapping p a c #

Profunctor p => Profunctor (Codensity p) # 
Instance details

Defined in Data.Profunctor.Ran

Methods

dimap :: (a -> b) -> (c -> d) -> Codensity p b c -> Codensity p a d #

lmap :: (a -> b) -> Codensity p b c -> Codensity p a c #

rmap :: (b -> c) -> Codensity p a b -> Codensity p a c #

(#.) :: Coercible c b => q b c -> Codensity p a b -> Codensity p a c #

(.#) :: Coercible b a => Codensity p b c -> q a b -> Codensity p a c #

Profunctor (Coyoneda p) # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

dimap :: (a -> b) -> (c -> d) -> Coyoneda p b c -> Coyoneda p a d #

lmap :: (a -> b) -> Coyoneda p b c -> Coyoneda p a c #

rmap :: (b -> c) -> Coyoneda p a b -> Coyoneda p a c #

(#.) :: Coercible c b => q b c -> Coyoneda p a b -> Coyoneda p a c #

(.#) :: Coercible b a => Coyoneda p b c -> q a b -> Coyoneda p a c #

Profunctor (Yoneda p) # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

dimap :: (a -> b) -> (c -> d) -> Yoneda p b c -> Yoneda p a d #

lmap :: (a -> b) -> Yoneda p b c -> Yoneda p a c #

rmap :: (b -> c) -> Yoneda p a b -> Yoneda p a c #

(#.) :: Coercible c b => q b c -> Yoneda p a b -> Yoneda p a c #

(.#) :: Coercible b a => Yoneda p b c -> q a b -> Yoneda p a c #

Profunctor ((->) :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> (b -> c) -> a -> d #

lmap :: (a -> b) -> (b -> c) -> a -> c #

rmap :: (b -> c) -> (a -> b) -> a -> c #

(#.) :: Coercible c b => q b c -> (a -> b) -> a -> c #

(.#) :: Coercible b a => (b -> c) -> q a b -> a -> c #

Functor w => Profunctor (Cokleisli w) # 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Cokleisli w b c -> Cokleisli w a d #

lmap :: (a -> b) -> Cokleisli w b c -> Cokleisli w a c #

rmap :: (b -> c) -> Cokleisli w a b -> Cokleisli w a c #

(#.) :: Coercible c b => q b c -> Cokleisli w a b -> Cokleisli w a c #

(.#) :: Coercible b a => Cokleisli w b c -> q a b -> Cokleisli w a c #

(Profunctor p, Profunctor q) => Profunctor (Rift p q) # 
Instance details

Defined in Data.Profunctor.Composition

Methods

dimap :: (a -> b) -> (c -> d) -> Rift p q b c -> Rift p q a d #

lmap :: (a -> b) -> Rift p q b c -> Rift p q a c #

rmap :: (b -> c) -> Rift p q a b -> Rift p q a c #

(#.) :: Coercible c b => q0 b c -> Rift p q a b -> Rift p q a c #

(.#) :: Coercible b a => Rift p q b c -> q0 a b -> Rift p q a c #

(Profunctor p, Profunctor q) => Profunctor (Procompose p q) # 
Instance details

Defined in Data.Profunctor.Composition

Methods

dimap :: (a -> b) -> (c -> d) -> Procompose p q b c -> Procompose p q a d #

lmap :: (a -> b) -> Procompose p q b c -> Procompose p q a c #

rmap :: (b -> c) -> Procompose p q a b -> Procompose p q a c #

(#.) :: Coercible c b => q0 b c -> Procompose p q a b -> Procompose p q a c #

(.#) :: Coercible b a => Procompose p q b c -> q0 a b -> Procompose p q a c #

(Profunctor p, Profunctor q) => Profunctor (Ran p q) # 
Instance details

Defined in Data.Profunctor.Ran

Methods

dimap :: (a -> b) -> (c -> d) -> Ran p q b c -> Ran p q a d #

lmap :: (a -> b) -> Ran p q b c -> Ran p q a c #

rmap :: (b -> c) -> Ran p q a b -> Ran p q a c #

(#.) :: Coercible c b => q0 b c -> Ran p q a b -> Ran p q a c #

(.#) :: Coercible b a => Ran p q b c -> q0 a b -> Ran p q a c #

(Functor f, Profunctor p) => Profunctor (Cayley f p) # 
Instance details

Defined in Data.Profunctor.Cayley

Methods

dimap :: (a -> b) -> (c -> d) -> Cayley f p b c -> Cayley f p a d #

lmap :: (a -> b) -> Cayley f p b c -> Cayley f p a c #

rmap :: (b -> c) -> Cayley f p a b -> Cayley f p a c #

(#.) :: Coercible c b => q b c -> Cayley f p a b -> Cayley f p a c #

(.#) :: Coercible b a => Cayley f p b c -> q a b -> Cayley f p a c #

Functor f => Profunctor (Joker f :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Joker f b c -> Joker f a d #

lmap :: (a -> b) -> Joker f b c -> Joker f a c #

rmap :: (b -> c) -> Joker f a b -> Joker f a c #

(#.) :: Coercible c b => q b c -> Joker f a b -> Joker f a c #

(.#) :: Coercible b a => Joker f b c -> q a b -> Joker f a c #

Contravariant f => Profunctor (Clown f :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Clown f b c -> Clown f a d #

lmap :: (a -> b) -> Clown f b c -> Clown f a c #

rmap :: (b -> c) -> Clown f a b -> Clown f a c #

(#.) :: Coercible c b => q b c -> Clown f a b -> Clown f a c #

(.#) :: Coercible b a => Clown f b c -> q a b -> Clown f a c #

(Profunctor p, Profunctor q) => Profunctor (Sum p q) # 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Sum p q b c -> Sum p q a d #

lmap :: (a -> b) -> Sum p q b c -> Sum p q a c #

rmap :: (b -> c) -> Sum p q a b -> Sum p q a c #

(#.) :: Coercible c b => q0 b c -> Sum p q a b -> Sum p q a c #

(.#) :: Coercible b a => Sum p q b c -> q0 a b -> Sum p q a c #

(Profunctor p, Profunctor q) => Profunctor (Product p q) # 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Product p q b c -> Product p q a d #

lmap :: (a -> b) -> Product p q b c -> Product p q a c #

rmap :: (b -> c) -> Product p q a b -> Product p q a c #

(#.) :: Coercible c b => q0 b c -> Product p q a b -> Product p q a c #

(.#) :: Coercible b a => Product p q b c -> q0 a b -> Product p q a c #

(Functor f, Profunctor p) => Profunctor (Tannen f p) # 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Tannen f p b c -> Tannen f p a d #

lmap :: (a -> b) -> Tannen f p b c -> Tannen f p a c #

rmap :: (b -> c) -> Tannen f p a b -> Tannen f p a c #

(#.) :: Coercible c b => q b c -> Tannen f p a b -> Tannen f p a c #

(.#) :: Coercible b a => Tannen f p b c -> q a b -> Tannen f p a c #

(Profunctor p, Functor f, Functor g) => Profunctor (Biff p f g) # 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Biff p f g b c -> Biff p f g a d #

lmap :: (a -> b) -> Biff p f g b c -> Biff p f g a c #

rmap :: (b -> c) -> Biff p f g a b -> Biff p f g a c #

(#.) :: Coercible c b => q b c -> Biff p f g a b -> Biff p f g a c #

(.#) :: Coercible b a => Biff p f g b c -> q a b -> Biff p f g a c #

Profunctorial Strength

class Profunctor p => Strong p where #

Generalizing Star of a strong Functor

Note: Every Functor in Haskell is strong with respect to (,).

This describes profunctor strength with respect to the product structure of Hask.

http://www-kb.is.s.u-tokyo.ac.jp/~asada/papers/arrStrMnd.pdf

Minimal complete definition

first' | second'

Methods

first' :: p a b -> p (a, c) (b, c) #

Laws:

first'dimap swap swap . second'
lmap fstrmap fst . first'
lmap (second f) . first'rmap (second f) . first
first' . first'dimap assoc unassoc . first' where
  assoc ((a,b),c) = (a,(b,c))
  unassoc (a,(b,c)) = ((a,b),c)

second' :: p a b -> p (c, a) (c, b) #

Laws:

second'dimap swap swap . first'
lmap sndrmap snd . second'
lmap (first f) . second'rmap (first f) . second'
second' . second'dimap unassoc assoc . second' where
  assoc ((a,b),c) = (a,(b,c))
  unassoc (a,(b,c)) = ((a,b),c)
Instances
Monad m => Strong (Kleisli m) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

first' :: Kleisli m a b -> Kleisli m (a, c) (b, c) #

second' :: Kleisli m a b -> Kleisli m (c, a) (c, b) #

Strong (Forget r) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

first' :: Forget r a b -> Forget r (a, c) (b, c) #

second' :: Forget r a b -> Forget r (c, a) (c, b) #

Arrow p => Strong (WrappedArrow p) #

Arrow is Strong Category

Instance details

Defined in Data.Profunctor.Strong

Methods

first' :: WrappedArrow p a b -> WrappedArrow p (a, c) (b, c) #

second' :: WrappedArrow p a b -> WrappedArrow p (c, a) (c, b) #

Functor m => Strong (Star m) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

first' :: Star m a b -> Star m (a, c) (b, c) #

second' :: Star m a b -> Star m (c, a) (c, b) #

Strong (Pastro p) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

first' :: Pastro p a b -> Pastro p (a, c) (b, c) #

second' :: Pastro p a b -> Pastro p (c, a) (c, b) #

Profunctor p => Strong (Tambara p) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

first' :: Tambara p a b -> Tambara p (a, c) (b, c) #

second' :: Tambara p a b -> Tambara p (c, a) (c, b) #

Strong p => Strong (Closure p) # 
Instance details

Defined in Data.Profunctor.Closed

Methods

first' :: Closure p a b -> Closure p (a, c) (b, c) #

second' :: Closure p a b -> Closure p (c, a) (c, b) #

Strong (FreeTraversing p) # 
Instance details

Defined in Data.Profunctor.Traversing

Methods

first' :: FreeTraversing p a b -> FreeTraversing p (a, c) (b, c) #

second' :: FreeTraversing p a b -> FreeTraversing p (c, a) (c, b) #

Profunctor p => Strong (CofreeTraversing p) # 
Instance details

Defined in Data.Profunctor.Traversing

Methods

first' :: CofreeTraversing p a b -> CofreeTraversing p (a, c) (b, c) #

second' :: CofreeTraversing p a b -> CofreeTraversing p (c, a) (c, b) #

Strong (FreeMapping p) # 
Instance details

Defined in Data.Profunctor.Mapping

Methods

first' :: FreeMapping p a b -> FreeMapping p (a, c) (b, c) #

second' :: FreeMapping p a b -> FreeMapping p (c, a) (c, b) #

Profunctor p => Strong (CofreeMapping p) # 
Instance details

Defined in Data.Profunctor.Mapping

Methods

first' :: CofreeMapping p a b -> CofreeMapping p (a, c) (b, c) #

second' :: CofreeMapping p a b -> CofreeMapping p (c, a) (c, b) #

Strong p => Strong (Coyoneda p) # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

first' :: Coyoneda p a b -> Coyoneda p (a, c) (b, c) #

second' :: Coyoneda p a b -> Coyoneda p (c, a) (c, b) #

Strong p => Strong (Yoneda p) # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

first' :: Yoneda p a b -> Yoneda p (a, c) (b, c) #

second' :: Yoneda p a b -> Yoneda p (c, a) (c, b) #

Strong ((->) :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

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

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

(Strong p, Strong q) => Strong (Procompose p q) # 
Instance details

Defined in Data.Profunctor.Composition

Methods

first' :: Procompose p q a b -> Procompose p q (a, c) (b, c) #

second' :: Procompose p q a b -> Procompose p q (c, a) (c, b) #

(Functor f, Strong p) => Strong (Cayley f p) # 
Instance details

Defined in Data.Profunctor.Cayley

Methods

first' :: Cayley f p a b -> Cayley f p (a, c) (b, c) #

second' :: Cayley f p a b -> Cayley f p (c, a) (c, b) #

Contravariant f => Strong (Clown f :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

first' :: Clown f a b -> Clown f (a, c) (b, c) #

second' :: Clown f a b -> Clown f (c, a) (c, b) #

(Strong p, Strong q) => Strong (Product p q) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

first' :: Product p q a b -> Product p q (a, c) (b, c) #

second' :: Product p q a b -> Product p q (c, a) (c, b) #

(Functor f, Strong p) => Strong (Tannen f p) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

first' :: Tannen f p a b -> Tannen f p (a, c) (b, c) #

second' :: Tannen f p a b -> Tannen f p (c, a) (c, b) #

uncurry' :: Strong p => p a (b -> c) -> p (a, b) c #

class Profunctor p => Choice p where #

The generalization of Costar of Functor that is strong with respect to Either.

Note: This is also a notion of strength, except with regards to another monoidal structure that we can choose to equip Hask with: the cocartesian coproduct.

Minimal complete definition

left' | right'

Methods

left' :: p a b -> p (Either a c) (Either b c) #

Laws:

left'dimap swapE swapE . right' where
  swapE :: Either a b -> Either b a
  swapE = either Right Left
rmap Leftlmap Left . left'
lmap (right f) . left'rmap (right f) . left'
left' . left'dimap assocE unassocE . left' where
  assocE :: Either (Either a b) c -> Either a (Either b c)
  assocE (Left (Left a)) = Left a
  assocE (Left (Right b)) = Right (Left b)
  assocE (Right c) = Right (Right c)
  unassocE :: Either a (Either b c) -> Either (Either a b) c
  unassocE (Left a) = Left (Left a)
  unassocE (Right (Left b) = Left (Right b)
  unassocE (Right (Right c)) = Right c)

right' :: p a b -> p (Either c a) (Either c b) #

Laws:

right'dimap swapE swapE . left' where
  swapE :: Either a b -> Either b a
  swapE = either Right Left
rmap Rightlmap Right . right'
lmap (left f) . right'rmap (left f) . right'
right' . right'dimap unassocE assocE . right' where
  assocE :: Either (Either a b) c -> Either a (Either b c)
  assocE (Left (Left a)) = Left a
  assocE (Left (Right b)) = Right (Left b)
  assocE (Right c) = Right (Right c)
  unassocE :: Either a (Either b c) -> Either (Either a b) c
  unassocE (Left a) = Left (Left a)
  unassocE (Right (Left b) = Left (Right b)
  unassocE (Right (Right c)) = Right c)
Instances
Monad m => Choice (Kleisli m) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: Kleisli m a b -> Kleisli m (Either a c) (Either b c) #

right' :: Kleisli m a b -> Kleisli m (Either c a) (Either c b) #

Choice (Tagged :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: Tagged a b -> Tagged (Either a c) (Either b c) #

right' :: Tagged a b -> Tagged (Either c a) (Either c b) #

Monoid r => Choice (Forget r) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: Forget r a b -> Forget r (Either a c) (Either b c) #

right' :: Forget r a b -> Forget r (Either c a) (Either c b) #

ArrowChoice p => Choice (WrappedArrow p) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: WrappedArrow p a b -> WrappedArrow p (Either a c) (Either b c) #

right' :: WrappedArrow p a b -> WrappedArrow p (Either c a) (Either c b) #

Traversable w => Choice (Costar w) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: Costar w a b -> Costar w (Either a c) (Either b c) #

right' :: Costar w a b -> Costar w (Either c a) (Either c b) #

Applicative f => Choice (Star f) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: Star f a b -> Star f (Either a c) (Either b c) #

right' :: Star f a b -> Star f (Either c a) (Either c b) #

Choice p => Choice (Tambara p) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: Tambara p a b -> Tambara p (Either a c) (Either b c) #

right' :: Tambara p a b -> Tambara p (Either c a) (Either c b) #

Choice (PastroSum p) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: PastroSum p a b -> PastroSum p (Either a c) (Either b c) #

right' :: PastroSum p a b -> PastroSum p (Either c a) (Either c b) #

Profunctor p => Choice (TambaraSum p) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: TambaraSum p a b -> TambaraSum p (Either a c) (Either b c) #

right' :: TambaraSum p a b -> TambaraSum p (Either c a) (Either c b) #

Choice (FreeTraversing p) # 
Instance details

Defined in Data.Profunctor.Traversing

Methods

left' :: FreeTraversing p a b -> FreeTraversing p (Either a c) (Either b c) #

right' :: FreeTraversing p a b -> FreeTraversing p (Either c a) (Either c b) #

Profunctor p => Choice (CofreeTraversing p) # 
Instance details

Defined in Data.Profunctor.Traversing

Methods

left' :: CofreeTraversing p a b -> CofreeTraversing p (Either a c) (Either b c) #

right' :: CofreeTraversing p a b -> CofreeTraversing p (Either c a) (Either c b) #

Choice (FreeMapping p) # 
Instance details

Defined in Data.Profunctor.Mapping

Methods

left' :: FreeMapping p a b -> FreeMapping p (Either a c) (Either b c) #

right' :: FreeMapping p a b -> FreeMapping p (Either c a) (Either c b) #

Profunctor p => Choice (CofreeMapping p) # 
Instance details

Defined in Data.Profunctor.Mapping

Methods

left' :: CofreeMapping p a b -> CofreeMapping p (Either a c) (Either b c) #

right' :: CofreeMapping p a b -> CofreeMapping p (Either c a) (Either c b) #

Choice p => Choice (Coyoneda p) # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

left' :: Coyoneda p a b -> Coyoneda p (Either a c) (Either b c) #

right' :: Coyoneda p a b -> Coyoneda p (Either c a) (Either c b) #

Choice p => Choice (Yoneda p) # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

left' :: Yoneda p a b -> Yoneda p (Either a c) (Either b c) #

right' :: Yoneda p a b -> Yoneda p (Either c a) (Either c b) #

Choice ((->) :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: (a -> b) -> Either a c -> Either b c #

right' :: (a -> b) -> Either c a -> Either c b #

Comonad w => Choice (Cokleisli w) #

extract approximates costrength

Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: Cokleisli w a b -> Cokleisli w (Either a c) (Either b c) #

right' :: Cokleisli w a b -> Cokleisli w (Either c a) (Either c b) #

(Choice p, Choice q) => Choice (Procompose p q) # 
Instance details

Defined in Data.Profunctor.Composition

Methods

left' :: Procompose p q a b -> Procompose p q (Either a c) (Either b c) #

right' :: Procompose p q a b -> Procompose p q (Either c a) (Either c b) #

(Functor f, Choice p) => Choice (Cayley f p) # 
Instance details

Defined in Data.Profunctor.Cayley

Methods

left' :: Cayley f p a b -> Cayley f p (Either a c) (Either b c) #

right' :: Cayley f p a b -> Cayley f p (Either c a) (Either c b) #

Functor f => Choice (Joker f :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: Joker f a b -> Joker f (Either a c) (Either b c) #

right' :: Joker f a b -> Joker f (Either c a) (Either c b) #

(Choice p, Choice q) => Choice (Product p q) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: Product p q a b -> Product p q (Either a c) (Either b c) #

right' :: Product p q a b -> Product p q (Either c a) (Either c b) #

(Functor f, Choice p) => Choice (Tannen f p) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: Tannen f p a b -> Tannen f p (Either a c) (Either b c) #

right' :: Tannen f p a b -> Tannen f p (Either c a) (Either c b) #

Closed

class Profunctor p => Closed p where #

A strong profunctor allows the monoidal structure to pass through.

A closed profunctor allows the closed structure to pass through.

Methods

closed :: p a b -> p (x -> a) (x -> b) #

Instances
(Distributive f, Monad f) => Closed (Kleisli f) # 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Kleisli f a b -> Kleisli f (x -> a) (x -> b) #

Closed (Tagged :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Tagged a b -> Tagged (x -> a) (x -> b) #

Functor f => Closed (Costar f) # 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Costar f a b -> Costar f (x -> a) (x -> b) #

Distributive f => Closed (Star f) # 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Star f a b -> Star f (x -> a) (x -> b) #

Closed (Environment p) # 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Environment p a b -> Environment p (x -> a) (x -> b) #

Profunctor p => Closed (Closure p) # 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Closure p a b -> Closure p (x -> a) (x -> b) #

Closed (FreeMapping p) # 
Instance details

Defined in Data.Profunctor.Mapping

Methods

closed :: FreeMapping p a b -> FreeMapping p (x -> a) (x -> b) #

Profunctor p => Closed (CofreeMapping p) # 
Instance details

Defined in Data.Profunctor.Mapping

Methods

closed :: CofreeMapping p a b -> CofreeMapping p (x -> a) (x -> b) #

Closed p => Closed (Coyoneda p) # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

closed :: Coyoneda p a b -> Coyoneda p (x -> a) (x -> b) #

Closed p => Closed (Yoneda p) # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

closed :: Yoneda p a b -> Yoneda p (x -> a) (x -> b) #

Closed ((->) :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: (a -> b) -> (x -> a) -> (x -> b) #

Functor f => Closed (Cokleisli f) # 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Cokleisli f a b -> Cokleisli f (x -> a) (x -> b) #

(Closed p, Closed q) => Closed (Procompose p q) # 
Instance details

Defined in Data.Profunctor.Composition

Methods

closed :: Procompose p q a b -> Procompose p q (x -> a) (x -> b) #

(Closed p, Closed q) => Closed (Product p q) # 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Product p q a b -> Product p q (x -> a) (x -> b) #

(Functor f, Closed p) => Closed (Tannen f p) # 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Tannen f p a b -> Tannen f p (x -> a) (x -> b) #

curry' :: Closed p => p (a, b) c -> p a (b -> c) #

class (Traversing p, Closed p) => Mapping p where #

Methods

map' :: Functor f => p a b -> p (f a) (f b) #

Instances
(Monad m, Distributive m) => Mapping (Kleisli m) # 
Instance details

Defined in Data.Profunctor.Mapping

Methods

map' :: Functor f => Kleisli m a b -> Kleisli m (f a) (f b) #

(Applicative m, Distributive m) => Mapping (Star m) # 
Instance details

Defined in Data.Profunctor.Mapping

Methods

map' :: Functor f => Star m a b -> Star m (f a) (f b) #

Mapping (FreeMapping p) # 
Instance details

Defined in Data.Profunctor.Mapping

Methods

map' :: Functor f => FreeMapping p a b -> FreeMapping p (f a) (f b) #

Profunctor p => Mapping (CofreeMapping p) # 
Instance details

Defined in Data.Profunctor.Mapping

Methods

map' :: Functor f => CofreeMapping p a b -> CofreeMapping p (f a) (f b) #

Mapping p => Mapping (Coyoneda p) # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

map' :: Functor f => Coyoneda p a b -> Coyoneda p (f a) (f b) #

Mapping p => Mapping (Yoneda p) # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

map' :: Functor f => Yoneda p a b -> Yoneda p (f a) (f b) #

Mapping ((->) :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Mapping

Methods

map' :: Functor f => (a -> b) -> f a -> f b #

(Mapping p, Mapping q) => Mapping (Procompose p q) # 
Instance details

Defined in Data.Profunctor.Composition

Methods

map' :: Functor f => Procompose p q a b -> Procompose p q (f a) (f b) #

Profunctorial Costrength

class Profunctor p => Costrong p where #

Analogous to ArrowLoop, loop = unfirst

Minimal complete definition

unfirst | unsecond

Methods

unfirst :: p (a, d) (b, d) -> p a b #

Laws:

unfirstunsecond . dimap swap swap
lmap (,()) ≡ unfirst . rmap (,())
unfirst . lmap (second f) ≡ unfirst . rmap (second f)
unfirst . unfirst = unfirst . dimap assoc unassoc where
  assoc ((a,b),c) = (a,(b,c))
  unassoc (a,(b,c)) = ((a,b),c)

unsecond :: p (d, a) (d, b) -> p a b #

Laws:

unsecondunfirst . dimap swap swap
lmap ((),) ≡ unsecond . rmap ((),)
unsecond . lmap (first f) ≡ unsecond . rmap (first f)
unsecond . unsecond = unsecond . dimap unassoc assoc where
  assoc ((a,b),c) = (a,(b,c))
  unassoc (a,(b,c)) = ((a,b),c)
Instances
MonadFix m => Costrong (Kleisli m) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

unfirst :: Kleisli m (a, d) (b, d) -> Kleisli m a b #

unsecond :: Kleisli m (d, a) (d, b) -> Kleisli m a b #

Costrong (Tagged :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

unfirst :: Tagged (a, d) (b, d) -> Tagged a b #

unsecond :: Tagged (d, a) (d, b) -> Tagged a b #

ArrowLoop p => Costrong (WrappedArrow p) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

unfirst :: WrappedArrow p (a, d) (b, d) -> WrappedArrow p a b #

unsecond :: WrappedArrow p (d, a) (d, b) -> WrappedArrow p a b #

Functor f => Costrong (Costar f) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

unfirst :: Costar f (a, d) (b, d) -> Costar f a b #

unsecond :: Costar f (d, a) (d, b) -> Costar f a b #

Costrong (Copastro p) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

unfirst :: Copastro p (a, d) (b, d) -> Copastro p a b #

unsecond :: Copastro p (d, a) (d, b) -> Copastro p a b #

Costrong (Cotambara p) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

unfirst :: Cotambara p (a, d) (b, d) -> Cotambara p a b #

unsecond :: Cotambara p (d, a) (d, b) -> Cotambara p a b #

Costrong p => Costrong (Coyoneda p) # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

unfirst :: Coyoneda p (a, d) (b, d) -> Coyoneda p a b #

unsecond :: Coyoneda p (d, a) (d, b) -> Coyoneda p a b #

Costrong p => Costrong (Yoneda p) # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

unfirst :: Yoneda p (a, d) (b, d) -> Yoneda p a b #

unsecond :: Yoneda p (d, a) (d, b) -> Yoneda p a b #

Costrong ((->) :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

unfirst :: ((a, d) -> (b, d)) -> a -> b #

unsecond :: ((d, a) -> (d, b)) -> a -> b #

Functor f => Costrong (Cokleisli f) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

unfirst :: Cokleisli f (a, d) (b, d) -> Cokleisli f a b #

unsecond :: Cokleisli f (d, a) (d, b) -> Cokleisli f a b #

(Corepresentable p, Corepresentable q) => Costrong (Procompose p q) # 
Instance details

Defined in Data.Profunctor.Composition

Methods

unfirst :: Procompose p q (a, d) (b, d) -> Procompose p q a b #

unsecond :: Procompose p q (d, a) (d, b) -> Procompose p q a b #

(Costrong p, Costrong q) => Costrong (Product p q) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

unfirst :: Product p q (a, d) (b, d) -> Product p q a b #

unsecond :: Product p q (d, a) (d, b) -> Product p q a b #

(Functor f, Costrong p) => Costrong (Tannen f p) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

unfirst :: Tannen f p (a, d) (b, d) -> Tannen f p a b #

unsecond :: Tannen f p (d, a) (d, b) -> Tannen f p a b #

class Profunctor p => Cochoice p where #

Minimal complete definition

unleft | unright

Methods

unleft :: p (Either a d) (Either b d) -> p a b #

Laws:

unleftunright . dimap swapE swapE where
  swapE :: Either a b -> Either b a
  swapE = either Right Left
rmap (either id absurd) ≡ unleft . lmap (either id absurd)
unfirst . rmap (second f) ≡ unfirst . lmap (second f)
unleft . unleftunleft . dimap assocE unassocE where
  assocE :: Either (Either a b) c -> Either a (Either b c)
  assocE (Left (Left a)) = Left a
  assocE (Left (Right b)) = Right (Left b)
  assocE (Right c) = Right (Right c)
  unassocE :: Either a (Either b c) -> Either (Either a b) c
  unassocE (Left a) = Left (Left a)
  unassocE (Right (Left b) = Left (Right b)
  unassocE (Right (Right c)) = Right c)

unright :: p (Either d a) (Either d b) -> p a b #

Laws:

unrightunleft . dimap swapE swapE where
  swapE :: Either a b -> Either b a
  swapE = either Right Left
rmap (either absurd id) ≡ unright . lmap (either absurd id)
unsecond . rmap (first f) ≡ unsecond . lmap (first f)
unright . unrightunright . dimap unassocE assocE where
  assocE :: Either (Either a b) c -> Either a (Either b c)
  assocE (Left (Left a)) = Left a
  assocE (Left (Right b)) = Right (Left b)
  assocE (Right c) = Right (Right c)
  unassocE :: Either a (Either b c) -> Either (Either a b) c
  unassocE (Left a) = Left (Left a)
  unassocE (Right (Left b) = Left (Right b)
  unassocE (Right (Right c)) = Right c)
Instances
Applicative f => Cochoice (Costar f) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

unleft :: Costar f (Either a d) (Either b d) -> Costar f a b #

unright :: Costar f (Either d a) (Either d b) -> Costar f a b #

Traversable f => Cochoice (Star f) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

unleft :: Star f (Either a d) (Either b d) -> Star f a b #

unright :: Star f (Either d a) (Either d b) -> Star f a b #

Cochoice (CopastroSum p) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

unleft :: CopastroSum p (Either a d) (Either b d) -> CopastroSum p a b #

unright :: CopastroSum p (Either d a) (Either d b) -> CopastroSum p a b #

Cochoice (CotambaraSum p) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

unleft :: CotambaraSum p (Either a d) (Either b d) -> CotambaraSum p a b #

unright :: CotambaraSum p (Either d a) (Either d b) -> CotambaraSum p a b #

Cochoice p => Cochoice (Coyoneda p) # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

unleft :: Coyoneda p (Either a d) (Either b d) -> Coyoneda p a b #

unright :: Coyoneda p (Either d a) (Either d b) -> Coyoneda p a b #

Cochoice p => Cochoice (Yoneda p) # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

unleft :: Yoneda p (Either a d) (Either b d) -> Yoneda p a b #

unright :: Yoneda p (Either d a) (Either d b) -> Yoneda p a b #

Cochoice ((->) :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

unleft :: (Either a d -> Either b d) -> a -> b #

unright :: (Either d a -> Either d b) -> a -> b #

(Cochoice p, Cochoice q) => Cochoice (Product p q) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

unleft :: Product p q (Either a d) (Either b d) -> Product p q a b #

unright :: Product p q (Either d a) (Either d b) -> Product p q a b #

(Functor f, Cochoice p) => Cochoice (Tannen f p) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

unleft :: Tannen f p (Either a d) (Either b d) -> Tannen f p a b #

unright :: Tannen f p (Either d a) (Either d b) -> Tannen f p a b #

Common Profunctors

newtype Star f d c #

Lift a Functor into a Profunctor (forwards).

Constructors

Star 

Fields

Instances
Functor f => Profunctor (Star f) # 
Instance details

Defined in Data.Profunctor.Types

Methods

dimap :: (a -> b) -> (c -> d) -> Star f b c -> Star f a d #

lmap :: (a -> b) -> Star f b c -> Star f a c #

rmap :: (b -> c) -> Star f a b -> Star f a c #

(#.) :: Coercible c b => q b c -> Star f a b -> Star f a c #

(.#) :: Coercible b a => Star f b c -> q a b -> Star f a c #

Functor m => Strong (Star m) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

first' :: Star m a b -> Star m (a, c) (b, c) #

second' :: Star m a b -> Star m (c, a) (c, b) #

Distributive f => Closed (Star f) # 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Star f a b -> Star f (x -> a) (x -> b) #

Traversable f => Cochoice (Star f) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

unleft :: Star f (Either a d) (Either b d) -> Star f a b #

unright :: Star f (Either d a) (Either d b) -> Star f a b #

Applicative f => Choice (Star f) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: Star f a b -> Star f (Either a c) (Either b c) #

right' :: Star f a b -> Star f (Either c a) (Either c b) #

Applicative m => Traversing (Star m) # 
Instance details

Defined in Data.Profunctor.Traversing

Methods

traverse' :: Traversable f => Star m a b -> Star m (f a) (f b) #

wander :: (forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t) -> Star m a b -> Star m s t #

(Applicative m, Distributive m) => Mapping (Star m) # 
Instance details

Defined in Data.Profunctor.Mapping

Methods

map' :: Functor f => Star m a b -> Star m (f a) (f b) #

Functor f => Representable (Star f) # 
Instance details

Defined in Data.Profunctor.Rep

Associated Types

type Rep (Star f) :: Type -> Type #

Methods

tabulate :: (d -> Rep (Star f) c) -> Star f d c #

Functor f => Sieve (Star f) f # 
Instance details

Defined in Data.Profunctor.Sieve

Methods

sieve :: Star f a b -> a -> f b #

Monad f => Category (Star f :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Types

Methods

id :: Star f a a #

(.) :: Star f b c -> Star f a b -> Star f a c #

Monad f => Monad (Star f a) # 
Instance details

Defined in Data.Profunctor.Types

Methods

(>>=) :: Star f a a0 -> (a0 -> Star f a b) -> Star f a b #

(>>) :: Star f a a0 -> Star f a b -> Star f a b #

return :: a0 -> Star f a a0 #

fail :: String -> Star f a a0 #

Functor f => Functor (Star f a) # 
Instance details

Defined in Data.Profunctor.Types

Methods

fmap :: (a0 -> b) -> Star f a a0 -> Star f a b #

(<$) :: a0 -> Star f a b -> Star f a a0 #

Applicative f => Applicative (Star f a) # 
Instance details

Defined in Data.Profunctor.Types

Methods

pure :: a0 -> Star f a a0 #

(<*>) :: Star f a (a0 -> b) -> Star f a a0 -> Star f a b #

liftA2 :: (a0 -> b -> c) -> Star f a a0 -> Star f a b -> Star f a c #

(*>) :: Star f a a0 -> Star f a b -> Star f a b #

(<*) :: Star f a a0 -> Star f a b -> Star f a a0 #

Alternative f => Alternative (Star f a) # 
Instance details

Defined in Data.Profunctor.Types

Methods

empty :: Star f a a0 #

(<|>) :: Star f a a0 -> Star f a a0 -> Star f a a0 #

some :: Star f a a0 -> Star f a [a0] #

many :: Star f a a0 -> Star f a [a0] #

MonadPlus f => MonadPlus (Star f a) # 
Instance details

Defined in Data.Profunctor.Types

Methods

mzero :: Star f a a0 #

mplus :: Star f a a0 -> Star f a a0 -> Star f a a0 #

Distributive f => Distributive (Star f a) # 
Instance details

Defined in Data.Profunctor.Types

Methods

distribute :: Functor f0 => f0 (Star f a a0) -> Star f a (f0 a0) #

collect :: Functor f0 => (a0 -> Star f a b) -> f0 a0 -> Star f a (f0 b) #

distributeM :: Monad m => m (Star f a a0) -> Star f a (m a0) #

collectM :: Monad m => (a0 -> Star f a b) -> m a0 -> Star f a (m b) #

type Rep (Star f) # 
Instance details

Defined in Data.Profunctor.Rep

type Rep (Star f) = f

newtype Costar f d c #

Lift a Functor into a Profunctor (backwards).

Constructors

Costar 

Fields

Instances
Functor f => Profunctor (Costar f) # 
Instance details

Defined in Data.Profunctor.Types

Methods

dimap :: (a -> b) -> (c -> d) -> Costar f b c -> Costar f a d #

lmap :: (a -> b) -> Costar f b c -> Costar f a c #

rmap :: (b -> c) -> Costar f a b -> Costar f a c #

(#.) :: Coercible c b => q b c -> Costar f a b -> Costar f a c #

(.#) :: Coercible b a => Costar f b c -> q a b -> Costar f a c #

Functor f => Costrong (Costar f) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

unfirst :: Costar f (a, d) (b, d) -> Costar f a b #

unsecond :: Costar f (d, a) (d, b) -> Costar f a b #

Functor f => Closed (Costar f) # 
Instance details

Defined in Data.Profunctor.Closed

Methods

closed :: Costar f a b -> Costar f (x -> a) (x -> b) #

Applicative f => Cochoice (Costar f) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

unleft :: Costar f (Either a d) (Either b d) -> Costar f a b #

unright :: Costar f (Either d a) (Either d b) -> Costar f a b #

Traversable w => Choice (Costar w) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: Costar w a b -> Costar w (Either a c) (Either b c) #

right' :: Costar w a b -> Costar w (Either c a) (Either c b) #

Functor f => Corepresentable (Costar f) # 
Instance details

Defined in Data.Profunctor.Rep

Associated Types

type Corep (Costar f) :: Type -> Type #

Methods

cotabulate :: (Corep (Costar f) d -> c) -> Costar f d c #

Functor f => Cosieve (Costar f) f # 
Instance details

Defined in Data.Profunctor.Sieve

Methods

cosieve :: Costar f a b -> f a -> b #

Monad (Costar f a) # 
Instance details

Defined in Data.Profunctor.Types

Methods

(>>=) :: Costar f a a0 -> (a0 -> Costar f a b) -> Costar f a b #

(>>) :: Costar f a a0 -> Costar f a b -> Costar f a b #

return :: a0 -> Costar f a a0 #

fail :: String -> Costar f a a0 #

Functor (Costar f a) # 
Instance details

Defined in Data.Profunctor.Types

Methods

fmap :: (a0 -> b) -> Costar f a a0 -> Costar f a b #

(<$) :: a0 -> Costar f a b -> Costar f a a0 #

Applicative (Costar f a) # 
Instance details

Defined in Data.Profunctor.Types

Methods

pure :: a0 -> Costar f a a0 #

(<*>) :: Costar f a (a0 -> b) -> Costar f a a0 -> Costar f a b #

liftA2 :: (a0 -> b -> c) -> Costar f a a0 -> Costar f a b -> Costar f a c #

(*>) :: Costar f a a0 -> Costar f a b -> Costar f a b #

(<*) :: Costar f a a0 -> Costar f a b -> Costar f a a0 #

Distributive (Costar f d) # 
Instance details

Defined in Data.Profunctor.Types

Methods

distribute :: Functor f0 => f0 (Costar f d a) -> Costar f d (f0 a) #

collect :: Functor f0 => (a -> Costar f d b) -> f0 a -> Costar f d (f0 b) #

distributeM :: Monad m => m (Costar f d a) -> Costar f d (m a) #

collectM :: Monad m => (a -> Costar f d b) -> m a -> Costar f d (m b) #

type Corep (Costar f) # 
Instance details

Defined in Data.Profunctor.Rep

type Corep (Costar f) = f

newtype WrappedArrow p a b #

Wrap an arrow for use as a Profunctor.

Constructors

WrapArrow 

Fields

Instances
Arrow p => Arrow (WrappedArrow p) # 
Instance details

Defined in Data.Profunctor.Types

Methods

arr :: (b -> c) -> WrappedArrow p b c #

first :: WrappedArrow p b c -> WrappedArrow p (b, d) (c, d) #

second :: WrappedArrow p b c -> WrappedArrow p (d, b) (d, c) #

(***) :: WrappedArrow p b c -> WrappedArrow p b' c' -> WrappedArrow p (b, b') (c, c') #

(&&&) :: WrappedArrow p b c -> WrappedArrow p b c' -> WrappedArrow p b (c, c') #

ArrowZero p => ArrowZero (WrappedArrow p) # 
Instance details

Defined in Data.Profunctor.Types

Methods

zeroArrow :: WrappedArrow p b c #

ArrowChoice p => ArrowChoice (WrappedArrow p) # 
Instance details

Defined in Data.Profunctor.Types

Methods

left :: WrappedArrow p b c -> WrappedArrow p (Either b d) (Either c d) #

right :: WrappedArrow p b c -> WrappedArrow p (Either d b) (Either d c) #

(+++) :: WrappedArrow p b c -> WrappedArrow p b' c' -> WrappedArrow p (Either b b') (Either c c') #

(|||) :: WrappedArrow p b d -> WrappedArrow p c d -> WrappedArrow p (Either b c) d #

ArrowApply p => ArrowApply (WrappedArrow p) # 
Instance details

Defined in Data.Profunctor.Types

Methods

app :: WrappedArrow p (WrappedArrow p b c, b) c #

ArrowLoop p => ArrowLoop (WrappedArrow p) # 
Instance details

Defined in Data.Profunctor.Types

Methods

loop :: WrappedArrow p (b, d) (c, d) -> WrappedArrow p b c #

Arrow p => Profunctor (WrappedArrow p) # 
Instance details

Defined in Data.Profunctor.Types

Methods

dimap :: (a -> b) -> (c -> d) -> WrappedArrow p b c -> WrappedArrow p a d #

lmap :: (a -> b) -> WrappedArrow p b c -> WrappedArrow p a c #

rmap :: (b -> c) -> WrappedArrow p a b -> WrappedArrow p a c #

(#.) :: Coercible c b => q b c -> WrappedArrow p a b -> WrappedArrow p a c #

(.#) :: Coercible b a => WrappedArrow p b c -> q a b -> WrappedArrow p a c #

ArrowLoop p => Costrong (WrappedArrow p) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

unfirst :: WrappedArrow p (a, d) (b, d) -> WrappedArrow p a b #

unsecond :: WrappedArrow p (d, a) (d, b) -> WrappedArrow p a b #

Arrow p => Strong (WrappedArrow p) #

Arrow is Strong Category

Instance details

Defined in Data.Profunctor.Strong

Methods

first' :: WrappedArrow p a b -> WrappedArrow p (a, c) (b, c) #

second' :: WrappedArrow p a b -> WrappedArrow p (c, a) (c, b) #

ArrowChoice p => Choice (WrappedArrow p) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: WrappedArrow p a b -> WrappedArrow p (Either a c) (Either b c) #

right' :: WrappedArrow p a b -> WrappedArrow p (Either c a) (Either c b) #

Category p => Category (WrappedArrow p :: Type -> Type -> Type) # 
Instance details

Defined in Data.Profunctor.Types

Methods

id :: WrappedArrow p a a #

(.) :: WrappedArrow p b c -> WrappedArrow p a b -> WrappedArrow p a c #

newtype Forget r a b #

Constructors

Forget 

Fields

Instances
Profunctor (Forget r) # 
Instance details

Defined in Data.Profunctor.Types

Methods

dimap :: (a -> b) -> (c -> d) -> Forget r b c -> Forget r a d #

lmap :: (a -> b) -> Forget r b c -> Forget r a c #

rmap :: (b -> c) -> Forget r a b -> Forget r a c #

(#.) :: Coercible c b => q b c -> Forget r a b -> Forget r a c #

(.#) :: Coercible b a => Forget r b c -> q a b -> Forget r a c #

Strong (Forget r) # 
Instance details

Defined in Data.Profunctor.Strong

Methods

first' :: Forget r a b -> Forget r (a, c) (b, c) #

second' :: Forget r a b -> Forget r (c, a) (c, b) #

Monoid r => Choice (Forget r) # 
Instance details

Defined in Data.Profunctor.Choice

Methods

left' :: Forget r a b -> Forget r (Either a c) (Either b c) #

right' :: Forget r a b -> Forget r (Either c a) (Either c b) #

Monoid m => Traversing (Forget m) # 
Instance details

Defined in Data.Profunctor.Traversing

Methods

traverse' :: Traversable f => Forget m a b -> Forget m (f a) (f b) #

wander :: (forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t) -> Forget m a b -> Forget m s t #

Representable (Forget r) # 
Instance details

Defined in Data.Profunctor.Rep

Associated Types

type Rep (Forget r) :: Type -> Type #

Methods

tabulate :: (d -> Rep (Forget r) c) -> Forget r d c #

Sieve (Forget r) (Const r :: Type -> Type) # 
Instance details

Defined in Data.Profunctor.Sieve

Methods

sieve :: Forget r a b -> a -> Const r b #

Functor (Forget r a) # 
Instance details

Defined in Data.Profunctor.Types

Methods

fmap :: (a0 -> b) -> Forget r a a0 -> Forget r a b #

(<$) :: a0 -> Forget r a b -> Forget r a a0 #

Foldable (Forget r a) # 
Instance details

Defined in Data.Profunctor.Types

Methods

fold :: Monoid m => Forget r a m -> m #

foldMap :: Monoid m => (a0 -> m) -> Forget r a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> Forget r a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> Forget r a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> Forget r a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> Forget r a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> Forget r a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> Forget r a a0 -> a0 #

toList :: Forget r a a0 -> [a0] #

null :: Forget r a a0 -> Bool #

length :: Forget r a a0 -> Int #

elem :: Eq a0 => a0 -> Forget r a a0 -> Bool #

maximum :: Ord a0 => Forget r a a0 -> a0 #

minimum :: Ord a0 => Forget r a a0 -> a0 #

sum :: Num a0 => Forget r a a0 -> a0 #

product :: Num a0 => Forget r a a0 -> a0 #

Traversable (Forget r a) # 
Instance details

Defined in Data.Profunctor.Types

Methods

traverse :: Applicative f => (a0 -> f b) -> Forget r a a0 -> f (Forget r a b) #

sequenceA :: Applicative f => Forget r a (f a0) -> f (Forget r a a0) #

mapM :: Monad m => (a0 -> m b) -> Forget r a a0 -> m (Forget r a b) #

sequence :: Monad m => Forget r a (m a0) -> m (Forget r a a0) #

type Rep (Forget r) # 
Instance details

Defined in Data.Profunctor.Rep

type Rep (Forget r) = (Const r :: Type -> Type)

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