| Copyright | (C) 2012-15 Edward Kmett | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | provisional | 
| Portability | Rank2Types | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell98 | 
Control.Lens.Iso
Contents
Description
- 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 :: AnIso s t a b -> ((s -> a) -> (b -> t) -> r) -> r
- au :: AnIso s t a b -> ((b -> t) -> e -> s) -> e -> a
- auf :: Profunctor p => AnIso s t a b -> (p r a -> e -> b) -> p r s -> e -> 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')
- class Bifunctor p => Swapped p where
- class Strict lazy strict | lazy -> strict, strict -> lazy where
- lazy :: Strict lazy strict => Iso' strict lazy
- class Reversing t where- reversing :: t -> t
 
- reversed :: Reversing a => Iso' a a
- involuted :: (a -> a) -> Iso' a a
- 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 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')
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 :: 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
auf :: Profunctor p => AnIso s t a b -> (p r a -> e -> b) -> p r s -> e -> t 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.
Mnemonically, the German auf plays a similar role to à la, and the combinator
 is au with an extra function argument.
>>>auf (_Unwrapping Sum) (foldMapOf both) Prelude.length ("hello","world")10
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 non vMaybe 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 +~ 2fromList [("hello",3)]
>>>Map.fromList [("hello",1)] & at "hello" . non 0 -~ 1fromList []
>>>Map.fromList [("hello",1)] ^. at "hello" . non 01
>>>Map.fromList [] ^. at "hello" . non 00
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:
>>>fromList [("hello",fromList [("world","!!!")])] & at "hello" . non Map.empty . at "world" .~ NothingfromList []
It can also be used in reverse to exclude a given value:
>>>non 0 # rem 10 4Just 2
>>>non 0 # rem 10 5Nothing
non' :: APrism' a () -> Iso' (Maybe a) a Source
non' pnon (p # ())Prism
This function generates an isomorphism between Maybe (a | isn't p a)a.
>>>Map.singleton "hello" Map.empty & at "hello" . non' _Empty . at "world" ?~ "!!!"fromList [("hello",fromList [("world","!!!")])]
>>>fromList [("hello",fromList [("world","!!!")])] & at "hello" . non' _Empty . at "world" .~ NothingfromList []
anon :: a -> (a -> Bool) -> Iso' (Maybe a) a Source
anon a pnon a
This function assumes that p a holds TrueMaybe (a | not (p a))a.
>>>Map.empty & at "hello" . anon Map.empty Map.null . at "world" ?~ "!!!"fromList [("hello",fromList [("world","!!!")])]
>>>fromList [("hello",fromList [("world","!!!")])] & at "hello" . anon Map.empty Map.null . at "world" .~ NothingfromList []
enum :: Enum a => Iso' Int a Source
This isomorphism can be used to convert to or from an instance of Enum.
>>>LT^.from enum0
>>>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 Strict lazy strict | lazy -> strict, strict -> lazy where Source
Ad hoc conversion between "strict" and "lazy" versions of a structure,
 such as Text or ByteString.
lazy :: Strict lazy strict => Iso' strict lazy Source
An Iso between the strict variant of a structure and its lazy
 counterpart.
lazy=fromstrict
See http://hackage.haskell.org/package/strict-base-types for an example use.
class Reversing t where Source
This class provides a generalized notion of list reversal extended to other containers.
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
| TraversableWithIndex i (Magma i t b) | |
| FoldableWithIndex i (Magma i t b) | |
| FunctorWithIndex i (Magma i t b) | |
| Functor (Magma i t b) | |
| Foldable (Magma i t b) | |
| Traversable (Magma i t b) | |
| (Show i, Show a) => Show (Magma i t b a) | 
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 ::Contravariantf =>Isos t a b ->Iso(f a) (f b) (f s) (f t) contramapping ::Contravariantf =>Iso's a ->Iso'(f a) (f s)
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:
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
lmap :: (a -> b) -> p b c -> p a c
rmap :: (b -> c) -> p a b -> p a c
Instances
| Profunctor (->) | |
| Profunctor ReifiedFold | |
| Profunctor ReifiedGetter | |
| Monad m => Profunctor (Kleisli m) | |
| Functor w => Profunctor (Cokleisli w) | |
| Functor f => Profunctor (UpStar f) | |
| Functor f => Profunctor (DownStar f) | |
| Arrow p => Profunctor (WrappedArrow p) | |
| Profunctor (Forget r) | |
| Profunctor (Tagged *) | |
| Profunctor (Indexed i) | |
| Profunctor (ReifiedIndexedFold i) | |
| Profunctor (ReifiedIndexedGetter i) | |
| Profunctor (Market a b) | |
| Profunctor (Exchange a b) | 
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 Isos into both arguments of a Profunctor simultaneously.
dimapping ::Profunctorp =>Isos t a b ->Isos' t' a' b' ->Iso(p a s') (p b t') (p s a') (p t b') dimapping ::Profunctorp =>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 ::Profunctorp =>Isos t a b ->Iso(p a x) (p b y) (p s x) (p t y) lmapping ::Profunctorp =>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 ::Profunctorp =>Isos t a b ->Iso(p x s) (p y t) (p x a) (p y b) rmapping ::Profunctorp =>Iso's a ->Iso'(p x s) (p x a)