Safe Haskell | None |
---|---|
Language | Haskell2010 |
An Iso
morphism expresses the fact that two types have the
same structure, and hence can be converted from one to the other in
either direction.
Synopsis
- type Iso s t a b = Optic An_Iso NoIx s t a b
- type Iso' s a = Optic' An_Iso NoIx s a
- iso :: (s -> a) -> (b -> t) -> Iso s t a b
- equality :: (s ~ a, t ~ b) => Iso s t a b
- simple :: Iso' a a
- coerced :: (Coercible s a, Coercible t b) => Iso s t a b
- coercedTo :: forall a s. Coercible s a => Iso' s a
- coerced1 :: forall f s a. (Coercible s (f s), Coercible a (f a)) => Iso (f s) (f a) s 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')
- involuted :: (a -> a) -> Iso' a a
- class Bifunctor p => Swapped p where
- withIso :: Iso s t a b -> ((s -> a) -> (b -> t) -> r) -> r
- au :: Functor f => Iso s t a b -> ((b -> t) -> f s) -> f a
- under :: Iso s t a b -> (t -> s) -> b -> a
- mapping :: (Functor f, Functor g) => Iso s t a b -> Iso (f s) (g t) (f a) (g b)
- data An_Iso
Formation
Introduction
iso :: (s -> a) -> (b -> t) -> Iso s t a b Source #
Build an iso from a pair of inverse functions.
If you want to build an Iso
from the van Laarhoven representation, use
isoVL
from the optics-vl
package.
Elimination
An Iso
is in particular a Getter
, a
Review
and a Setter
, therefore you can
specialise types to obtain:
view
::Iso
s t a b -> s -> areview
::Iso
s t a b -> b -> t
over
::Iso
s t a b -> (a -> b) -> s -> tset
::Iso
s t a b -> b -> s -> t
Computation
Well-formedness
The functions translating back and forth must be mutually inverse:
view
i .review
i ≡id
review
i .view
i ≡id
Additional introduction forms
equality :: (s ~ a, t ~ b) => Iso s t a b Source #
Capture type constraints as an isomorphism.
Note: This is the identity optic:
>>>
:t view equality
view equality :: a -> a
coerced :: (Coercible s a, Coercible t b) => Iso s t a b Source #
Data types that are representationally equal are isomorphic.
>>>
view coerced 'x' :: Identity Char
Identity 'x'
coercedTo :: forall a s. Coercible s a => Iso' s a Source #
Type-preserving version of coerced
with type parameters rearranged for
TypeApplications.
>>>
newtype MkInt = MkInt Int deriving Show
>>>
over (coercedTo @Int) (*3) (MkInt 2)
MkInt 6
coerced1 :: forall f s a. (Coercible s (f s), Coercible a (f a)) => Iso (f s) (f a) s a Source #
Special case of coerced
for trivial newtype wrappers.
>>>
over (coerced1 @Identity) (++ "bar") (Identity "foo")
Identity "foobar"
flipped :: Iso (a -> b -> c) (a' -> b' -> c') (b -> a -> c) (b' -> a' -> c') Source #
The isomorphism for flipping a function.
>>>
(view flipped (,)) 1 2
(2,1)
Additional elimination forms
withIso :: Iso s t a b -> ((s -> a) -> (b -> t) -> r) -> r Source #
Extract the two components of an isomorphism.
Combinators
Subtyping
Tag for an iso.