Copyright | (C) 2012-16 Edward Kmett |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | Rank2Types, TypeFamilies, FunctionalDependencies |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Synopsis
- type Iso s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t)
- type Iso' s a = Iso s s a a
- type AnIso s t a b = Exchange a b a (Identity b) -> Exchange a b s (Identity t)
- type AnIso' s a = AnIso s s a a
- iso :: (s -> a) -> (b -> t) -> Iso s t a b
- from :: AnIso s t a b -> Iso b a t s
- cloneIso :: AnIso s t a b -> Iso s t a b
- withIso :: forall s t a b rep (r :: TYPE rep). AnIso s t a b -> ((s -> a) -> (b -> t) -> r) -> r
- au :: Functor f => AnIso s t a b -> ((b -> t) -> f s) -> f a
- auf :: (Functor f, Functor g) => AnIso s t a b -> (f t -> g s) -> f b -> g a
- xplat :: Optic (Costar ((->) s)) g s t a b -> ((s -> a) -> g b) -> g t
- xplatf :: Optic (Costar f) g s t a b -> (f a -> g b) -> f s -> g t
- under :: AnIso s t a b -> (t -> s) -> b -> a
- mapping :: (Functor f, Functor g) => AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
- simple :: Equality' a a
- non :: Eq a => a -> Iso' (Maybe a) a
- non' :: APrism' a () -> Iso' (Maybe a) a
- anon :: a -> (a -> Bool) -> Iso' (Maybe a) a
- enum :: Enum a => Iso' Int a
- curried :: Iso ((a, b) -> c) ((d, e) -> f) (a -> b -> c) (d -> e -> f)
- uncurried :: Iso (a -> b -> c) (d -> e -> f) ((a, b) -> c) ((d, e) -> f)
- flipped :: Iso (a -> b -> c) (a' -> b' -> c') (b -> a -> c) (b' -> a' -> c')
- swapped :: Swap p => Iso (p a b) (p c d) (p b a) (p d c)
- pattern Swapped :: Swap p => p b a -> p a b
- strict :: Strict lazy strict => Iso' lazy strict
- lazy :: Strict lazy strict => Iso' strict lazy
- pattern Strict :: Strict s t => t -> s
- pattern Lazy :: Strict t s => t -> s
- class Reversing t where
- reversing :: t -> t
- reversed :: Reversing a => Iso' a a
- pattern Reversed :: Reversing t => t -> t
- involuted :: (a -> a) -> Iso' a a
- pattern List :: IsList l => [Item l] -> l
- magma :: LensLike (Mafic a b) s t a b -> Iso s u (Magma Int t b a) (Magma j u c c)
- imagma :: Over (Indexed i) (Molten i a b) s t a b -> Iso s t' (Magma i t b a) (Magma j t' c c)
- data Magma i t b a
- contramapping :: Contravariant f => AnIso s t a b -> Iso (f a) (f b) (f s) (f t)
- class Profunctor (p :: Type -> Type -> Type) where
- dimapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> AnIso s' t' a' b' -> Iso (p a s') (q b t') (p s a') (q t b')
- lmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p a x) (q b y) (p s x) (q t y)
- rmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p x s) (q y t) (p x a) (q y b)
- bimapping :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> AnIso s' t' a' b' -> Iso (f s s') (g t t') (f a a') (g b b')
- firsting :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> Iso (f s x) (g t y) (f a x) (g b y)
- seconding :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> Iso (f x s) (g y t) (f x a) (g y b)
- coerced :: forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Isomorphism Lenses
type Iso s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t) Source #
type AnIso s t a b = Exchange a b a (Identity b) -> Exchange a b s (Identity t) Source #
When you see this as an argument to a function, it expects an Iso
.
Isomorphism Construction
Consuming Isomorphisms
cloneIso :: AnIso s t a b -> Iso s t a b Source #
Convert from AnIso
back to any Iso
.
This is useful when you need to store an isomorphism as a data type inside a container and later reconstitute it as an overloaded function.
See cloneLens
or cloneTraversal
for more information on why you might want to do this.
withIso :: forall s t a b rep (r :: TYPE rep). AnIso s t a b -> ((s -> a) -> (b -> t) -> r) -> r Source #
Extract the two functions, one from s -> a
and
one from b -> t
that characterize an Iso
.
Working with isomorphisms
au :: Functor f => AnIso s t a b -> ((b -> t) -> f s) -> f a Source #
Based on ala
from Conor McBride's work on Epigram.
This version is generalized to accept any Iso
, not just a newtype
.
>>>
au (_Wrapping Sum) foldMap [1,2,3,4]
10
You may want to think of this combinator as having the following, simpler type:
au :: AnIso s t a b -> ((b -> t) -> e -> s) -> e -> a
au = xplat . from
auf :: (Functor f, Functor g) => AnIso s t a b -> (f t -> g s) -> f b -> g a Source #
Based on ala'
from Conor McBride's work on Epigram.
This version is generalized to accept any Iso
, not just a newtype
.
For a version you pass the name of the newtype
constructor to, see alaf
.
>>>
auf (_Wrapping Sum) (foldMapOf both) Prelude.length ("hello","world")
10
Mnemonically, the German auf plays a similar role to à la, and the combinator
is au
with an extra function argument:
auf
::Iso
s t a b -> ((r -> t) -> e -> s) -> (r -> b) -> e -> a
but the signature is general.
Note: The direction of the Iso
required for this function changed in lens
4.18 to match up
with the behavior of au
. For the old behavior use xplatf
or for a version that is compatible
across both old and new versions of lens
you can just use coerce
!
Common Isomorphisms
non :: Eq a => a -> Iso' (Maybe a) a Source #
If v
is an element of a type a
, and a'
is a
sans the element v
, then
is an isomorphism from
non
v
to Maybe
a'a
.
non
≡non'
.
only
Keep in mind this is only a real isomorphism if you treat the domain as being
.Maybe
(a sans v)
This is practically quite useful when you want to have a Map
where all the entries should have non-zero values.
>>>
Map.fromList [("hello",1)] & at "hello" . non 0 +~ 2
fromList [("hello",3)]
>>>
Map.fromList [("hello",1)] & at "hello" . non 0 -~ 1
fromList []
>>>
Map.fromList [("hello",1)] ^. at "hello" . non 0
1
>>>
Map.fromList [] ^. at "hello" . non 0
0
This combinator is also particularly useful when working with nested maps.
e.g. When you want to create the nested Map
when it is missing:
>>>
Map.empty & at "hello" . non Map.empty . at "world" ?~ "!!!"
fromList [("hello",fromList [("world","!!!")])]
and when have deleting the last entry from the nested Map
mean that we
should delete its entry from the surrounding one:
>>>
Map.fromList [("hello",Map.fromList [("world","!!!")])] & at "hello" . non Map.empty . at "world" .~ Nothing
fromList []
It can also be used in reverse to exclude a given value:
>>>
non 0 # rem 10 4
Just 2
>>>
non 0 # rem 10 5
Nothing
non' :: APrism' a () -> Iso' (Maybe a) a Source #
generalizes non'
p
to take any unit non
(p # ())Prism
This function generates an isomorphism between
and Maybe
(a | isn't
p a)a
.
>>>
Map.singleton "hello" Map.empty & at "hello" . non' _Empty . at "world" ?~ "!!!"
fromList [("hello",fromList [("world","!!!")])]
>>>
Map.fromList [("hello",Map.fromList [("world","!!!")])] & at "hello" . non' _Empty . at "world" .~ Nothing
fromList []
anon :: a -> (a -> Bool) -> Iso' (Maybe a) a Source #
generalizes anon
a p
to take any value and a predicate.non
a
This function assumes that p a
holds
and generates an isomorphism between True
and Maybe
(a | not
(p a))a
.
>>>
Map.empty & at "hello" . anon Map.empty Map.null . at "world" ?~ "!!!"
fromList [("hello",fromList [("world","!!!")])]
>>>
Map.fromList [("hello",Map.fromList [("world","!!!")])] & at "hello" . anon Map.empty Map.null . at "world" .~ Nothing
fromList []
enum :: Enum a => Iso' Int a Source #
This isomorphism can be used to convert to or from an instance of Enum
.
>>>
LT^.from enum
0
>>>
97^.enum :: Char
'a'
Note: this is only an isomorphism from the numeric range actually used
and it is a bit of a pleasant fiction, since there are questionable
Enum
instances for Double
, and Float
that exist solely for
[1.0 .. 4.0]
sugar and the instances for those and Integer
don't
cover all values in their range.
flipped :: Iso (a -> b -> c) (a' -> b' -> c') (b -> a -> c) (b' -> a' -> c') Source #
The isomorphism for flipping a function.
>>>
((,)^.flipped) 1 2
(2,1)
class Reversing t where Source #
This class provides a generalized notion of list reversal extended to other containers.
Instances
Reversing ByteString Source # | |
Defined in Control.Lens.Internal.Iso reversing :: ByteString -> ByteString Source # | |
Reversing ByteString Source # | |
Defined in Control.Lens.Internal.Iso reversing :: ByteString -> ByteString Source # | |
Reversing Text Source # | |
Reversing Text Source # | |
Reversing [a] Source # | |
Defined in Control.Lens.Internal.Iso | |
Reversing (NonEmpty a) Source # | |
Reversing (Seq a) Source # | |
Unbox a => Reversing (Vector a) Source # | |
Storable a => Reversing (Vector a) Source # | |
Prim a => Reversing (Vector a) Source # | |
Reversing (Vector a) Source # | |
Reversing (Deque a) Source # | |
reversed :: Reversing a => Iso' a a Source #
An Iso
between a list, ByteString
, Text
fragment, etc. and its reversal.
>>>
"live" ^. reversed
"evil"
>>>
"live" & reversed %~ ('d':)
"lived"
Uncommon Isomorphisms
imagma :: Over (Indexed i) (Molten i a b) s t a b -> Iso s t' (Magma i t b a) (Magma j t' c c) Source #
This isomorphism can be used to inspect an IndexedTraversal
to see how it associates
the structure and it can also be used to bake the IndexedTraversal
into a Magma
so
that you can traverse over it multiple times with access to the original indices.
This provides a way to peek at the internal structure of a
Traversal
or IndexedTraversal
Instances
FunctorWithIndex i (Magma i t b) Source # | |
Defined in Control.Lens.Internal.Magma | |
FoldableWithIndex i (Magma i t b) Source # | |
Defined in Control.Lens.Internal.Magma ifoldMap :: Monoid m => (i -> a -> m) -> Magma i t b a -> m # ifoldMap' :: Monoid m => (i -> a -> m) -> Magma i t b a -> m # ifoldr :: (i -> a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 # ifoldl :: (i -> b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 # ifoldr' :: (i -> a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 # ifoldl' :: (i -> b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 # | |
TraversableWithIndex i (Magma i t b) Source # | |
Defined in Control.Lens.Internal.Magma itraverse :: Applicative f => (i -> a -> f b0) -> Magma i t b a -> f (Magma i t b b0) # | |
Functor (Magma i t b) Source # | |
Foldable (Magma i t b) Source # | |
Defined in Control.Lens.Internal.Magma fold :: Monoid m => Magma i t b m -> m # foldMap :: Monoid m => (a -> m) -> Magma i t b a -> m # foldMap' :: Monoid m => (a -> m) -> Magma i t b a -> m # foldr :: (a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 # foldr' :: (a -> b0 -> b0) -> b0 -> Magma i t b a -> b0 # foldl :: (b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 # foldl' :: (b0 -> a -> b0) -> b0 -> Magma i t b a -> b0 # foldr1 :: (a -> a -> a) -> Magma i t b a -> a # foldl1 :: (a -> a -> a) -> Magma i t b a -> a # toList :: Magma i t b a -> [a] # null :: Magma i t b a -> Bool # length :: Magma i t b a -> Int # elem :: Eq a => a -> Magma i t b a -> Bool # maximum :: Ord a => Magma i t b a -> a # minimum :: Ord a => Magma i t b a -> a # | |
Traversable (Magma i t b) Source # | |
Defined in Control.Lens.Internal.Magma | |
(Show i, Show a) => Show (Magma i t b a) Source # | |
Contravariant functors
contramapping :: Contravariant f => AnIso s t a b -> Iso (f a) (f b) (f s) (f t) Source #
Lift an Iso
into a Contravariant
functor.
contramapping ::Contravariant
f =>Iso
s t a b ->Iso
(f a) (f b) (f s) (f t) contramapping ::Contravariant
f =>Iso'
s a ->Iso'
(f a) (f s)
Profunctors
class Profunctor (p :: Type -> Type -> Type) 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
id
≡id
If you supply lmap
and rmap
, ensure:
lmap
id
≡id
rmap
id
≡id
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 ilmap
(f.
g) ≡lmap
g.
lmap
frmap
(f.
g) ≡rmap
f.
rmap
g
Instances
Profunctor ReifiedFold Source # | |
Defined in Control.Lens.Reified 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 # (#.) :: forall a b c q. Coercible c b => q b c -> ReifiedFold a b -> ReifiedFold a c # (.#) :: forall a b c q. Coercible b a => ReifiedFold b c -> q a b -> ReifiedFold a c # | |
Profunctor ReifiedGetter Source # | |
Defined in Control.Lens.Reified 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 # (#.) :: forall a b c q. Coercible c b => q b c -> ReifiedGetter a b -> ReifiedGetter a c # (.#) :: forall a b c q. Coercible b a => ReifiedGetter b c -> q a b -> ReifiedGetter a c # | |
Monad m => Profunctor (Kleisli m) | |
Defined in Data.Profunctor.Unsafe 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Kleisli m a b -> Kleisli m a c # (.#) :: forall a b c q. Coercible b a => Kleisli m b c -> q a b -> Kleisli m a c # | |
Profunctor p => Profunctor (CofreeMapping p) | |
Defined in Data.Profunctor.Mapping 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 # (#.) :: forall a b c q. Coercible c b => q b c -> CofreeMapping p a b -> CofreeMapping p a c # (.#) :: forall a b c q. Coercible b a => CofreeMapping p b c -> q a b -> CofreeMapping p a c # | |
Profunctor (FreeMapping p) | |
Defined in Data.Profunctor.Mapping 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 # (#.) :: forall a b c q. Coercible c b => q b c -> FreeMapping p a b -> FreeMapping p a c # (.#) :: forall a b c q. Coercible b a => FreeMapping p b c -> q a b -> FreeMapping p a c # | |
Profunctor p => Profunctor (CofreeTraversing p) | |
Defined in Data.Profunctor.Traversing 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 # (#.) :: forall a b c q. Coercible c b => q b c -> CofreeTraversing p a b -> CofreeTraversing p a c # (.#) :: forall a b c q. Coercible b a => CofreeTraversing p b c -> q a b -> CofreeTraversing p a c # | |
Profunctor (FreeTraversing p) | |
Defined in Data.Profunctor.Traversing 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 # (#.) :: forall a b c q. Coercible c b => q b c -> FreeTraversing p a b -> FreeTraversing p a c # (.#) :: forall a b c q. Coercible b a => FreeTraversing p b c -> q a b -> FreeTraversing p a c # | |
Profunctor p => Profunctor (TambaraSum p) | |
Defined in Data.Profunctor.Choice 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 # (#.) :: forall a b c q. Coercible c b => q b c -> TambaraSum p a b -> TambaraSum p a c # (.#) :: forall a b c q. Coercible b a => TambaraSum p b c -> q a b -> TambaraSum p a c # | |
Profunctor (PastroSum p) | |
Defined in Data.Profunctor.Choice 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 # (#.) :: forall a b c q. Coercible c b => q b c -> PastroSum p a b -> PastroSum p a c # (.#) :: forall a b c q. Coercible b a => PastroSum p b c -> q a b -> PastroSum p a c # | |
Profunctor (CotambaraSum p) | |
Defined in Data.Profunctor.Choice 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 # (#.) :: forall a b c q. Coercible c b => q b c -> CotambaraSum p a b -> CotambaraSum p a c # (.#) :: forall a b c q. Coercible b a => CotambaraSum p b c -> q a b -> CotambaraSum p a c # | |
Profunctor (CopastroSum p) | |
Defined in Data.Profunctor.Choice 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 # (#.) :: forall a b c q. Coercible c b => q b c -> CopastroSum p a b -> CopastroSum p a c # (.#) :: forall a b c q. Coercible b a => CopastroSum p b c -> q a b -> CopastroSum p a c # | |
Profunctor p => Profunctor (Closure p) | |
Defined in Data.Profunctor.Closed 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Closure p a b -> Closure p a c # (.#) :: forall a b c q. Coercible b a => Closure p b c -> q a b -> Closure p a c # | |
Profunctor (Environment p) | |
Defined in Data.Profunctor.Closed 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Environment p a b -> Environment p a c # (.#) :: forall a b c q. Coercible b a => Environment p b c -> q a b -> Environment p a c # | |
Profunctor p => Profunctor (Tambara p) | |
Defined in Data.Profunctor.Strong 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Tambara p a b -> Tambara p a c # (.#) :: forall a b c q. Coercible b a => Tambara p b c -> q a b -> Tambara p a c # | |
Profunctor (Pastro p) | |
Defined in Data.Profunctor.Strong 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Pastro p a b -> Pastro p a c # (.#) :: forall a b c q. Coercible b a => Pastro p b c -> q a b -> Pastro p a c # | |
Profunctor (Cotambara p) | |
Defined in Data.Profunctor.Strong 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Cotambara p a b -> Cotambara p a c # (.#) :: forall a b c q. Coercible b a => Cotambara p b c -> q a b -> Cotambara p a c # | |
Profunctor (Copastro p) | |
Defined in Data.Profunctor.Strong 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Copastro p a b -> Copastro p a c # (.#) :: forall a b c q. Coercible b a => Copastro p b c -> q a b -> Copastro p a c # | |
Profunctor (Tagged :: Type -> Type -> Type) | |
Defined in Data.Profunctor.Unsafe 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Tagged a b -> Tagged a c # (.#) :: forall a b c q. Coercible b a => Tagged b c -> q a b -> Tagged a c # | |
Profunctor (Indexed i) Source # | |
Defined in Control.Lens.Internal.Indexed 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Indexed i a b -> Indexed i a c # (.#) :: forall a b c q. Coercible b a => Indexed i b c -> q a b -> Indexed i a c # | |
Profunctor (ReifiedIndexedFold i) Source # | |
Defined in Control.Lens.Reified 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 # (#.) :: forall a b c q. Coercible c b => q b c -> ReifiedIndexedFold i a b -> ReifiedIndexedFold i a c # (.#) :: forall a b c q. Coercible b a => ReifiedIndexedFold i b c -> q a b -> ReifiedIndexedFold i a c # | |
Profunctor (ReifiedIndexedGetter i) Source # | |
Defined in Control.Lens.Reified 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 # (#.) :: forall a b c q. Coercible c b => q b c -> ReifiedIndexedGetter i a b -> ReifiedIndexedGetter i a c # (.#) :: forall a b c q. Coercible b a => ReifiedIndexedGetter i b c -> q a b -> ReifiedIndexedGetter i a c # | |
Profunctor (Bazaar a) | |
Defined in Data.Profunctor.Traversing dimap :: (a0 -> b) -> (c -> d) -> Bazaar a b c -> Bazaar a a0 d # lmap :: (a0 -> b) -> Bazaar a b c -> Bazaar a a0 c # rmap :: (b -> c) -> Bazaar a a0 b -> Bazaar a a0 c # (#.) :: forall a0 b c q. Coercible c b => q b c -> Bazaar a a0 b -> Bazaar a a0 c # (.#) :: forall a0 b c q. Coercible b a0 => Bazaar a b c -> q a0 b -> Bazaar a a0 c # | |
Profunctor (Baz t) | |
Defined in Data.Profunctor.Traversing | |
Profunctor ((->) :: Type -> Type -> Type) | |
Defined in Data.Profunctor.Unsafe | |
Functor w => Profunctor (Cokleisli w) | |
Defined in Data.Profunctor.Unsafe 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Cokleisli w a b -> Cokleisli w a c # (.#) :: forall a b c q. Coercible b a => Cokleisli w b c -> q a b -> Cokleisli w a c # | |
Functor f => Profunctor (Star f) | |
Defined in Data.Profunctor.Types 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Star f a b -> Star f a c # (.#) :: forall a b c q. Coercible b a => Star f b c -> q a b -> Star f a c # | |
Functor f => Profunctor (Costar f) | |
Defined in Data.Profunctor.Types 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Costar f a b -> Costar f a c # (.#) :: forall a b c q. Coercible b a => Costar f b c -> q a b -> Costar f a c # | |
Profunctor (Forget r :: Type -> Type -> Type) | |
Defined in Data.Profunctor.Types 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Forget r a b -> Forget r a c # (.#) :: forall a b c q. Coercible b a => Forget r b c -> q a b -> Forget r a c # | |
Profunctor (Exchange a b) Source # | |
Defined in Control.Lens.Internal.Iso 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 # (#.) :: forall a0 b0 c q. Coercible c b0 => q b0 c -> Exchange a b a0 b0 -> Exchange a b a0 c # (.#) :: forall a0 b0 c q. Coercible b0 a0 => Exchange a b b0 c -> q a0 b0 -> Exchange a b a0 c # | |
Profunctor (Market a b) Source # | |
Defined in Control.Lens.Internal.Prism dimap :: (a0 -> b0) -> (c -> d) -> Market a b b0 c -> Market a b a0 d # lmap :: (a0 -> b0) -> Market a b b0 c -> Market a b a0 c # rmap :: (b0 -> c) -> Market a b a0 b0 -> Market a b a0 c # (#.) :: forall a0 b0 c q. Coercible c b0 => q b0 c -> Market a b a0 b0 -> Market a b a0 c # (.#) :: forall a0 b0 c q. Coercible b0 a0 => Market a b b0 c -> q a0 b0 -> Market a b a0 c # | |
(Functor f, Profunctor p) => Profunctor (WrappedPafb f p) Source # | |
Defined in Control.Lens.Internal.Profunctor dimap :: (a -> b) -> (c -> d) -> WrappedPafb f p b c -> WrappedPafb f p a d # lmap :: (a -> b) -> WrappedPafb f p b c -> WrappedPafb f p a c # rmap :: (b -> c) -> WrappedPafb f p a b -> WrappedPafb f p a c # (#.) :: forall a b c q. Coercible c b => q b c -> WrappedPafb f p a b -> WrappedPafb f p a c # (.#) :: forall a b c q. Coercible b a => WrappedPafb f p b c -> q a b -> WrappedPafb f p a c # | |
Functor f => Profunctor (Joker f :: Type -> Type -> Type) | |
Defined in Data.Profunctor.Unsafe 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Joker f a b -> Joker f a c # (.#) :: forall a b c q. Coercible b a => Joker f b c -> q a b -> Joker f a c # | |
Contravariant f => Profunctor (Clown f :: Type -> Type -> Type) | |
Defined in Data.Profunctor.Unsafe 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Clown f a b -> Clown f a c # (.#) :: forall a b c q. Coercible b a => Clown f b c -> q a b -> Clown f a c # | |
Arrow p => Profunctor (WrappedArrow p) | |
Defined in Data.Profunctor.Types 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 # (#.) :: forall a b c q. Coercible c b => q b c -> WrappedArrow p a b -> WrappedArrow p a c # (.#) :: forall a b c q. Coercible b a => WrappedArrow p b c -> q a b -> WrappedArrow p a c # | |
(Profunctor p, Profunctor q) => Profunctor (Sum p q) | |
Defined in Data.Profunctor.Unsafe 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 # (#.) :: forall a b c q0. Coercible c b => q0 b c -> Sum p q a b -> Sum p q a c # (.#) :: forall a b c q0. Coercible b a => Sum p q b c -> q0 a b -> Sum p q a c # | |
(Profunctor p, Profunctor q) => Profunctor (Product p q) | |
Defined in Data.Profunctor.Unsafe 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 # (#.) :: forall a b c q0. Coercible c b => q0 b c -> Product p q a b -> Product p q a c # (.#) :: forall a b c q0. Coercible b a => Product p q b c -> q0 a b -> Product p q a c # | |
(Functor f, Profunctor p) => Profunctor (Tannen f p) | |
Defined in Data.Profunctor.Unsafe 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Tannen f p a b -> Tannen f p a c # (.#) :: forall a b c q. Coercible b a => Tannen f p b c -> q a b -> Tannen f p a c # | |
(Functor f, Profunctor p) => Profunctor (Cayley f p) | |
Defined in Data.Profunctor.Cayley 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Cayley f p a b -> Cayley f p a c # (.#) :: forall a b c q. Coercible b a => Cayley f p b c -> q a b -> Cayley f p a c # | |
(Profunctor p, Profunctor q) => Profunctor (Procompose p q) | |
Defined in Data.Profunctor.Composition 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 # (#.) :: forall a b c q0. Coercible c b => q0 b c -> Procompose p q a b -> Procompose p q a c # (.#) :: forall a b c q0. Coercible b a => Procompose p q b c -> q0 a b -> Procompose p q a c # | |
(Profunctor p, Profunctor q) => Profunctor (Rift p q) | |
Defined in Data.Profunctor.Composition 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 # (#.) :: forall a b c q0. Coercible c b => q0 b c -> Rift p q a b -> Rift p q a c # (.#) :: forall a b c q0. Coercible b a => Rift p q b c -> q0 a b -> Rift p q a c # | |
(Profunctor p, Functor f, Functor g) => Profunctor (Biff p f g) | |
Defined in Data.Profunctor.Unsafe 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 # (#.) :: forall a b c q. Coercible c b => q b c -> Biff p f g a b -> Biff p f g a c # (.#) :: forall a b c q. Coercible b a => Biff p f g b c -> q a b -> Biff p f g a c # |
dimapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> AnIso s' t' a' b' -> Iso (p a s') (q b t') (p s a') (q t b') Source #
Lift two Iso
s into both arguments of a Profunctor
simultaneously.
dimapping ::Profunctor
p =>Iso
s t a b ->Iso
s' t' a' b' ->Iso
(p a s') (p b t') (p s a') (p t b') dimapping ::Profunctor
p =>Iso'
s a ->Iso'
s' a' ->Iso'
(p a s') (p s a')
lmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p a x) (q b y) (p s x) (q t y) Source #
Lift an Iso
contravariantly into the left argument of a Profunctor
.
lmapping ::Profunctor
p =>Iso
s t a b ->Iso
(p a x) (p b y) (p s x) (p t y) lmapping ::Profunctor
p =>Iso'
s a ->Iso'
(p a x) (p s x)
rmapping :: (Profunctor p, Profunctor q) => AnIso s t a b -> Iso (p x s) (q y t) (p x a) (q y b) Source #
Lift an Iso
covariantly into the right argument of a Profunctor
.
rmapping ::Profunctor
p =>Iso
s t a b ->Iso
(p x s) (p y t) (p x a) (p y b) rmapping ::Profunctor
p =>Iso'
s a ->Iso'
(p x s) (p x a)
Bifunctors
bimapping :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> AnIso s' t' a' b' -> Iso (f s s') (g t t') (f a a') (g b b') Source #
firsting :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> Iso (f s x) (g t y) (f a x) (g b y) Source #
seconding :: (Bifunctor f, Bifunctor g) => AnIso s t a b -> Iso (f x s) (g y t) (f x a) (g y b) Source #
Lift an Iso
into the second argument of a Bifunctor
. This is
essentially the same as mapping
, but it takes a 'Bifunctor p'
constraint instead of a 'Functor (p a)' one.
seconding ::Bifunctor
p =>Iso
s t a b ->Iso
(p x s) (p y t) (p x a) (p y b) seconding ::Bifunctor
p =>Iso'
s a ->Iso'
(p x s) (p x a)