| Portability | Rank2Types |
|---|---|
| Stability | provisional |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Safe Haskell | None |
Control.Lens.Iso
Contents
Description
- type Iso a b c d = forall k f. (Isomorphic k, Functor f) => k (c -> f d) (a -> f b)
- iso :: (Isomorphic k, Functor f) => (a -> b) -> (b -> a) -> k (b -> f b) (a -> f a)
- isos :: (Isomorphic k, Functor f) => (a -> c) -> (c -> a) -> (b -> d) -> (d -> b) -> k (c -> f d) (a -> f b)
- ala :: Simple Iso a b -> ((a -> b) -> c -> b) -> c -> a
- auf :: Simple Iso a b -> ((d -> b) -> c -> b) -> (d -> a) -> c -> a
- under :: Isomorphism (c -> Mutator d) (a -> Mutator b) -> (a -> b) -> c -> d
- from :: Isomorphic k => Isomorphism a b -> k b a
- via :: Isomorphic k => Isomorphism a b -> k a b
- data Isomorphism a b = Isomorphism (a -> b) (b -> a)
- class Category k => Isomorphic k where
- isomorphic :: (a -> b) -> (b -> a) -> k a b
- isomap :: ((a -> b) -> c -> d) -> ((b -> a) -> d -> c) -> k a b -> k c d
- _const :: Iso a b (Const a c) (Const b d)
- identity :: Iso a b (Identity a) (Identity b)
- newtype ReifiedIso a b c d = ReifyIso {
- reflectIso :: Iso a b c d
- type SimpleIso a b = Iso a a b b
- type SimpleReifiedIso a b = ReifiedIso a a b b
Isomorphism Lenses
type Iso a b c d = forall k f. (Isomorphic k, Functor f) => k (c -> f d) (a -> f b)Source
Isomorphim families can be composed with other lenses using either (.) and id
from the Prelude or from Control.Category. However, if you compose them
with each other using (.) from the Prelude, they will be dumbed down to a
mere Lens.
import Control.Category import Prelude hiding ((.),id)
type Iso a b c d = forall k f. (Isomorphick,Functorf) =>Overloadedk f a b c d
iso :: (Isomorphic k, Functor f) => (a -> b) -> (b -> a) -> k (b -> f b) (a -> f a)Source
isos :: (Isomorphic k, Functor f) => (a -> c) -> (c -> a) -> (b -> d) -> (d -> b) -> k (c -> f d) (a -> f b)Source
ala :: Simple Iso a b -> ((a -> b) -> c -> b) -> c -> aSource
Based on ala from Conor McBride's work on Epigram.
>>>:m + Control.Lens Data.Monoid.Lens Data.Foldable>>>ala _sum foldMap [1,2,3,4]10
auf :: Simple Iso a b -> ((d -> b) -> c -> b) -> (d -> a) -> c -> aSource
Based on ala' from Conor McBride's work on Epigram.
Mnemonically, the German auf plays a similar role to à la, and the combinator is au with an extra function argument.
under :: Isomorphism (c -> Mutator d) (a -> Mutator b) -> (a -> b) -> c -> dSource
Primitive isomorphisms
from :: Isomorphic k => Isomorphism a b -> k b aSource
via :: Isomorphic k => Isomorphism a b -> k a bSource
Convert from an Isomorphism back to any Isomorphic value.
This is useful when you need to store an isomoprhism as a data type inside a container and later reconstitute it as an overloaded function.
data Isomorphism a b Source
A concrete data type for isomorphisms.
This lets you place an isomorphism inside a container without using ImpredicativeTypes.
Constructors
| Isomorphism (a -> b) (b -> a) |
class Category k => Isomorphic k whereSource
Used to provide overloading of isomorphism application
This is a Category with a canonical mapping to it from the
category of isomorphisms over Haskell types.
Methods
isomorphic :: (a -> b) -> (b -> a) -> k a bSource
Build this morphism out of an isomorphism
The intention is that by using isomorphic, you can supply both halves of an
isomorphism, but k can be instantiated to (->), so you can freely use
the resulting isomorphism as a function.
isomap :: ((a -> b) -> c -> d) -> ((b -> a) -> d -> c) -> k a b -> k c dSource
Map a morphism in the target category using an isomorphism between morphisms in Hask.
Instances
Common Isomorphisms
Storing Isomorphisms
newtype ReifiedIso a b c d Source
Useful for storing isomorphisms in containers.
Constructors
| ReifyIso | |
Fields
| |
Simplicity
type SimpleReifiedIso a b = ReifiedIso a a b bSource
type SimpleReifiedIso =SimpleReifiedIso