Portability | Rank2Types |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Safe-Inferred |
- type Iso s t a b = forall k f. (Isomorphic k, Functor f) => k (a -> f b) (s -> f t)
- iso :: (Isomorphic k, Functor f) => (s -> a) -> (a -> s) -> k (a -> f a) (s -> f s)
- isos :: (Isomorphic k, Functor f) => (s -> a) -> (a -> s) -> (t -> b) -> (b -> t) -> k (a -> f b) (s -> f t)
- ala :: Simple Iso s a -> ((s -> a) -> e -> a) -> e -> s
- auf :: Simple Iso s a -> ((b -> a) -> e -> a) -> (b -> s) -> e -> s
- under :: Isomorphism (a -> Mutator b) (s -> Mutator t) -> (s -> t) -> a -> b
- mapping :: Functor f => SimpleIso s a -> SimpleIso (f s) (f a)
- review :: Overloaded Isomorphism (Accessor s) s t a b -> a -> s
- 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)
- simple :: Simple Iso a a
- non :: Eq a => a -> Simple Iso (Maybe a) a
- enum :: Enum a => Simple Iso Int a
- newtype ReifiedIso s t a b = ReifyIso {
- reflectIso :: Iso s t a b
- type SimpleIso s a = Iso s s a a
- type SimpleReifiedIso s a = ReifiedIso s s a a
Isomorphism Lenses
type Iso s t a b = forall k f. (Isomorphic k, Functor f) => k (a -> f b) (s -> f t)Source
Isomorphism 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
)
typeIso
s t a b = forall k f. (Isomorphic
k,Functor
f) =>Overloaded
k f s t a b
iso :: (Isomorphic k, Functor f) => (s -> a) -> (a -> s) -> k (a -> f a) (s -> f s)Source
isos :: (Isomorphic k, Functor f) => (s -> a) -> (a -> s) -> (t -> b) -> (b -> t) -> k (a -> f b) (s -> f t)Source
Working with isomorphisms
ala :: Simple Iso s a -> ((s -> a) -> e -> a) -> e -> sSource
Based on ala
from Conor McBride's work on Epigram.
>>>
:m + Data.Monoid.Lens Data.Foldable
>>>
ala _sum foldMap [1,2,3,4]
10
auf :: Simple Iso s a -> ((b -> a) -> e -> a) -> (b -> s) -> e -> sSource
Based on ala'
from Conor McBride's work on Epigram.
Mnemonically, the German auf plays a similar role to à la, and the combinator
is ala
with an extra function argument.
under :: Isomorphism (a -> Mutator b) (s -> Mutator t) -> (s -> t) -> a -> bSource
mapping :: Functor f => SimpleIso s a -> SimpleIso (f s) (f a)Source
This can be used to lift any SimpleIso
into an arbitrary functor.
review :: Overloaded Isomorphism (Accessor s) s t a b -> a -> sSource
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
.
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.
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.
Common Isomorphisms
non :: Eq a => a -> Simple Iso (Maybe a) aSource
If v
is an element of a type a
, and a'
is a
sans the element v
, then non v
is an isomorphism from
Maybe a'
to a
.
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:
>>>
fromList [("hello",fromList [("world","!!!")])] & at "hello" . non Map.empty . at "world" .~ Nothing
fromList []
enum :: Enum a => Simple Iso Int aSource
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.
Storing Isomorphisms
newtype ReifiedIso s t a b Source
Useful for storing isomorphisms in containers.
ReifyIso | |
|
Simplicity
type SimpleReifiedIso s a = ReifiedIso s s a aSource
typeSimpleReifiedIso
=Simple
ReifiedIso