profunctors-5.5.2: Profunctors

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

Data.Profunctor.Unsafe

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

This module includes unsafe composition operators that are useful in practice when it comes to generating optimal core in GHC.

If you import this module you are taking upon yourself the obligation that you will only call the operators with # in their names with functions that are operationally identity such as newtype constructors or the field accessor of a newtype.

If you are ever in doubt, use rmap or lmap.

Synopsis
  • class Profunctor p where
    • dimap :: (a -> b) -> (c -> d) -> p b c -> p a d
    • lmap :: (a -> b) -> p b c -> p a c
    • rmap :: (b -> c) -> p a b -> p a c
    • (#.) :: forall a b c q. Coercible c b => q b c -> p a b -> p a c
    • (.#) :: forall a b c q. Coercible b a => p b c -> q a b -> p a c

Profunctors

class Profunctor p where Source #

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 Source #

Map over both arguments at the same time.

dimap f g ≡ lmap f . rmap g

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

Map the first argument contravariantly.

lmap f ≡ dimap f id

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

Map the second argument covariantly.

rmapdimap id

(#.) :: forall a b c q. Coercible c b => q b c -> p a b -> p a c infixr 9 Source #

Strictly map the second argument argument covariantly with a function that is assumed operationally to be a cast, such as a newtype constructor.

Note: This operation is explicitly unsafe since an implementation may choose to use unsafeCoerce to implement this combinator and it has no way to validate that your function meets the requirements.

If you implement this combinator with unsafeCoerce, then you are taking upon yourself the obligation that you don't use GADT-like tricks to distinguish values.

If you import Data.Profunctor.Unsafe you are taking upon yourself the obligation that you will only call this with a first argument that is operationally identity.

The semantics of this function with respect to bottoms should match the default definition:

(#.) ≡ \_ -> \p -> p `seq` rmap coerce p

(.#) :: forall a b c q. Coercible b a => p b c -> q a b -> p a c infixl 8 Source #

Strictly map the first argument argument contravariantly with a function that is assumed operationally to be a cast, such as a newtype constructor.

Note: This operation is explicitly unsafe since an implementation may choose to use unsafeCoerce to implement this combinator and it has no way to validate that your function meets the requirements.

If you implement this combinator with unsafeCoerce, then you are taking upon yourself the obligation that you don't use GADT-like tricks to distinguish values.

If you import Data.Profunctor.Unsafe you are taking upon yourself the obligation that you will only call this with a second argument that is operationally identity.

(.#) ≡ \p -> p `seq` \f -> lmap coerce p
Instances
Monad m => Profunctor (Kleisli m) Source # 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Unsafe

Methods

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

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

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

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

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

Profunctor (Forget r) Source # 
Instance details

Defined in Data.Profunctor.Types

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Types

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Types

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Types

Methods

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

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

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

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

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

Profunctor (Copastro p) Source # 
Instance details

Defined in Data.Profunctor.Strong

Methods

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

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

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

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

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

Profunctor (Cotambara p) Source # 
Instance details

Defined in Data.Profunctor.Strong

Methods

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

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

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

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

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

Profunctor (Pastro p) Source # 
Instance details

Defined in Data.Profunctor.Strong

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Strong

Methods

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

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

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

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

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

Profunctor (Environment p) Source # 
Instance details

Defined in Data.Profunctor.Closed

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Closed

Methods

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

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

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

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

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

Profunctor (CopastroSum p) Source # 
Instance details

Defined in Data.Profunctor.Choice

Methods

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

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

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

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

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

Profunctor (CotambaraSum p) Source # 
Instance details

Defined in Data.Profunctor.Choice

Methods

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

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

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

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

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

Profunctor (PastroSum p) Source # 
Instance details

Defined in Data.Profunctor.Choice

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Choice

Methods

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

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

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

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

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

Profunctor (FreeTraversing p) Source # 
Instance details

Defined in Data.Profunctor.Traversing

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Traversing

Methods

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

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

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

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

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

Profunctor (FreeMapping p) Source # 
Instance details

Defined in Data.Profunctor.Mapping

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Mapping

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Ran

Methods

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

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

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

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

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

Profunctor (Coyoneda p) Source # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

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

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

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

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

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

Profunctor (Yoneda p) Source # 
Instance details

Defined in Data.Profunctor.Yoneda

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Unsafe

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Unsafe

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Composition

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Composition

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Ran

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Cayley

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Unsafe

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Unsafe

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Unsafe

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Unsafe

Methods

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

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

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

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

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

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

Defined in Data.Profunctor.Unsafe

Methods

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

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

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

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

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

(Profunctor p, Functor f, Functor g) => Profunctor (Biff p f g) Source # 
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 Source #

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

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

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

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