planet-mitchell-0.0.0: Planet Mitchell

Safe HaskellSafe
LanguageHaskell2010

Profunctor

Synopsis

Documentation

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
Profunctor Fold 
Instance details

Defined in Control.Foldl

Methods

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

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

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

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

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

Profunctor ReifiedGetter 
Instance details

Defined in Control.Lens.Reified

Methods

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

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

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

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

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

Profunctor ReifiedFold 
Instance details

Defined in Control.Lens.Reified

Methods

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

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

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

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

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

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 => (b -> c) -> Kleisli m a b -> Kleisli m a c #

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

Functor m => Profunctor (FoldM m) 
Instance details

Defined in Control.Foldl

Methods

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

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

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

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

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

Profunctor (ReifiedIndexedGetter i) 
Instance details

Defined in Control.Lens.Reified

Methods

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

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

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

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

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

Profunctor (ReifiedIndexedFold i) 
Instance details

Defined in Control.Lens.Reified

Methods

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

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

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

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

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

Profunctor (Indexed i) 
Instance details

Defined in Control.Lens.Internal.Indexed

Methods

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

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

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

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

(.#) :: Coercible b a => Indexed i b c -> (a -> b) -> Indexed i 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 => (b -> c) -> CofreeMapping p a b -> CofreeMapping p a c #

(.#) :: Coercible b a => CofreeMapping p b c -> (a -> b) -> CofreeMapping 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 => (b -> c) -> FreeMapping p a b -> FreeMapping p a c #

(.#) :: Coercible b a => FreeMapping p b c -> (a -> b) -> FreeMapping 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 => (b -> c) -> TambaraSum p a b -> TambaraSum p a c #

(.#) :: Coercible b a => TambaraSum p b c -> (a -> b) -> TambaraSum 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 => (b -> c) -> PastroSum p a b -> PastroSum p a c #

(.#) :: Coercible b a => PastroSum p b c -> (a -> b) -> PastroSum 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 => (b -> c) -> CotambaraSum p a b -> CotambaraSum p a c #

(.#) :: Coercible b a => CotambaraSum p b c -> (a -> b) -> CotambaraSum 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 => (b -> c) -> CopastroSum p a b -> CopastroSum p a c #

(.#) :: Coercible b a => CopastroSum p b c -> (a -> b) -> CopastroSum 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 => (b -> c) -> Closure p a b -> Closure p a c #

(.#) :: Coercible b a => Closure p b c -> (a -> b) -> Closure 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 => (b -> c) -> Environment p a b -> Environment p a c #

(.#) :: Coercible b a => Environment p b c -> (a -> b) -> Environment 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 => (b -> c) -> Tambara p a b -> Tambara p a c #

(.#) :: Coercible b a => Tambara p b c -> (a -> b) -> Tambara 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 => (b -> c) -> Pastro p a b -> Pastro p a c #

(.#) :: Coercible b a => Pastro p b c -> (a -> b) -> Pastro 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 => (b -> c) -> Cotambara p a b -> Cotambara p a c #

(.#) :: Coercible b a => Cotambara p b c -> (a -> b) -> Cotambara p 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 => (b -> c) -> Copastro p a b -> Copastro p a c #

(.#) :: Coercible b a => Copastro p b c -> (a -> b) -> Copastro p 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 => (b -> c) -> Star f a b -> Star f a c #

(.#) :: Coercible b a => Star f b c -> (a -> b) -> Star f 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 => (b -> c) -> Costar f a b -> Costar f a c #

(.#) :: Coercible b a => Costar f b c -> (a -> b) -> Costar f 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 => (b -> c) -> WrappedArrow p a b -> WrappedArrow p a c #

(.#) :: Coercible b a => WrappedArrow p b c -> (a -> b) -> WrappedArrow p 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 => (b -> c) -> Forget r a b -> Forget r a c #

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

Profunctor (Tagged :: * -> * -> *) 
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 => (b -> c) -> Tagged a b -> Tagged a c #

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

Profunctor ((->) :: * -> * -> *) 
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 => (b -> c) -> (a -> b) -> a -> c #

(.#) :: Coercible b a => (b -> c) -> (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 => (b -> c) -> Cokleisli w a b -> Cokleisli w a c #

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

Profunctor (Exchange a b) 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

dimap :: (a0 -> b0) -> (c -> d) -> Exchange a b b0 c -> Exchange a b a0 d #

lmap :: (a0 -> b0) -> Exchange a b b0 c -> Exchange a b a0 c #

rmap :: (b0 -> c) -> Exchange a b a0 b0 -> Exchange a b a0 c #

(#.) :: Coercible c b0 => (b0 -> c) -> Exchange a b a0 b0 -> Exchange a b a0 c #

(.#) :: Coercible b0 a0 => Exchange a b b0 c -> (a0 -> b0) -> Exchange a b a0 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 => (b -> c) -> Procompose p q a b -> Procompose p q a c #

(.#) :: Coercible b a => Procompose p q b c -> (a -> b) -> Procompose p q 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 => (b -> c) -> Rift p q a b -> Rift p q a c #

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

Functor f => Profunctor (Joker f :: * -> * -> *) 
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 => (b -> c) -> Joker f a b -> Joker f a c #

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

Contravariant f => Profunctor (Clown f :: * -> * -> *) 
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 => (b -> c) -> Clown f a b -> Clown f a c #

(.#) :: Coercible b a => Clown f b c -> (a -> b) -> Clown f 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 => (b -> c) -> Product p q a b -> Product p q a c #

(.#) :: Coercible b a => Product p q b c -> (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 => (b -> c) -> Tannen f p a b -> Tannen f p a c #

(.#) :: Coercible b a => Tannen f p b c -> (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 => (b -> c) -> Biff p f g a b -> Biff p f g a c #

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