| Copyright | (C) 2011-2013 Edward Kmett | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | provisional | 
| Portability | portable | 
| Safe Haskell | Trustworthy | 
| Language | Haskell2010 | 
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.
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:
dimapidid≡id
If you supply lmap and rmap, ensure:
lmapid≡idrmapid≡id
If you supply both, you should also ensure:
dimapf g ≡lmapf.rmapg
These ensure by parametricity:
dimap(f.g) (h.i) ≡dimapg h.dimapf ilmap(f.g) ≡lmapg.lmapfrmap(f.g) ≡rmapf.rmapg
Methods
dimap :: (a -> b) -> (c -> d) -> p b c -> p a d Source
lmap :: (a -> b) -> p b c -> p a c Source
rmap :: (b -> c) -> p a b -> p a c Source
(#.) :: Coercible c b => (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:
(#.) ≡ \f -> \p -> p `seq`rmapf p
(.#) :: Coercible b a => p b c -> (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 ->lmapf p
Instances
| Profunctor (->) | |
| Monad m => Profunctor (Kleisli m) | |
| Functor w => Profunctor (Cokleisli w) | |
| Profunctor (Tagged *) | |
| Profunctor (Forget r) | |
| Arrow p => Profunctor (WrappedArrow p) | |
| Functor f => Profunctor (DownStar f) | |
| Functor f => Profunctor (UpStar f) | |
| Profunctor p => Profunctor (Environment p) | |
| Profunctor p => Profunctor (Closure p) | |
| Profunctor p => Profunctor (Codensity p) | |
| Profunctor p => Profunctor (Copastro p) | |
| Profunctor p => Profunctor (Cotambara p) | |
| Profunctor p => Profunctor (Pastro p) | |
| Profunctor p => Profunctor (Tambara p) | |
| (Functor f, Profunctor p) => Profunctor (Cayley f p) | |
| (Profunctor p, Profunctor q) => Profunctor (Rift p q) | |
| (Profunctor p, Profunctor q) => Profunctor (Procompose p q) | |
| (Profunctor p, Profunctor q) => Profunctor (Ran p q) |