Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides compatibility layer for converting from/to van Laarhoven
encoding of Iso
s, Prism
s, Lens
es, IxLens
es, AffineTraversal
s,
IxAffineTraversal
s, Traversal
s and IxTraversal
s to their optics
equivalents.
Synopsis
- type IsoVL s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t)
- type IsoVL' s a = IsoVL s s a a
- isoVL :: forall s t a b. IsoVL s t a b -> Iso s t a b
- toIsoVL :: Is k An_Iso => Optic k is s t a b -> IsoVL s t a b
- withIsoVL :: Is k An_Iso => Optic k is s t a b -> (IsoVL s t a b -> r) -> r
- type PrismVL s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t)
- type PrismVL' s a = PrismVL s s a a
- prismVL :: forall s t a b. PrismVL s t a b -> Prism s t a b
- toPrismVL :: Is k A_Prism => Optic k is s t a b -> PrismVL s t a b
- withPrismVL :: Is k A_Prism => Optic k is s t a b -> (PrismVL s t a b -> r) -> r
- type LensVL s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t
- type LensVL' s a = LensVL s s a a
- lensVL :: LensVL s t a b -> Lens s t a b
- toLensVL :: Is k A_Lens => Optic k is s t a b -> LensVL s t a b
- withLensVL :: Is k A_Lens => Optic k is s t a b -> (LensVL s t a b -> r) -> r
- type IxLensVL i s t a b = forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t
- type IxLensVL' i s a = IxLensVL i s s a a
- ilensVL :: IxLensVL i s t a b -> IxLens i s t a b
- toIxLensVL :: (Is k A_Lens, HasSingleIndex is i) => Optic k is s t a b -> IxLensVL i s t a b
- withIxLensVL :: (Is k A_Lens, HasSingleIndex is i) => Optic k is s t a b -> (IxLensVL i s t a b -> r) -> r
- type AffineTraversalVL s t a b = forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (a -> f b) -> s -> f t
- type AffineTraversalVL' s a = AffineTraversalVL s s a a
- atraversalVL :: AffineTraversalVL s t a b -> AffineTraversal s t a b
- atraverseOf :: (Is k An_AffineTraversal, Functor f) => Optic k is s t a b -> (forall r. r -> f r) -> (a -> f b) -> s -> f t
- type IxAffineTraversalVL i s t a b = forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (i -> a -> f b) -> s -> f t
- type IxAffineTraversalVL' i s a = IxAffineTraversalVL i s s a a
- iatraversalVL :: IxAffineTraversalVL i s t a b -> IxAffineTraversal i s t a b
- iatraverseOf :: (Is k An_AffineTraversal, Functor f, HasSingleIndex is i) => Optic k is s t a b -> (forall r. r -> f r) -> (i -> a -> f b) -> s -> f t
- type TraversalVL s t a b = forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t
- type TraversalVL' s a = TraversalVL s s a a
- traversalVL :: TraversalVL s t a b -> Traversal s t a b
- traverseOf :: (Is k A_Traversal, Applicative f) => Optic k is s t a b -> (a -> f b) -> s -> f t
- type IxTraversalVL i s t a b = forall (f :: Type -> Type). Applicative f => (i -> a -> f b) -> s -> f t
- type IxTraversalVL' i s a = IxTraversalVL i s s a a
- itraversalVL :: IxTraversalVL i s t a b -> IxTraversal i s t a b
- itraverseOf :: (Is k A_Traversal, Applicative f, HasSingleIndex is i) => Optic k is s t a b -> (i -> a -> f b) -> s -> f t
Iso
type IsoVL s t a b = forall p f. (Profunctor p, Functor f) => p a (f b) -> p s (f t) Source #
Type synonym for a type-modifying van Laarhoven iso.
isoVL :: forall s t a b. IsoVL s t a b -> Iso s t a b Source #
Build an Iso
from the van Laarhoven representation.
toIsoVL :: Is k An_Iso => Optic k is s t a b -> IsoVL s t a b Source #
Convert an Iso
to the van Laarhoven representation.
withIsoVL :: Is k An_Iso => Optic k is s t a b -> (IsoVL s t a b -> r) -> r Source #
Work with an Iso
in the van Laarhoven representation.
Prism
type PrismVL s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t) Source #
Type synonym for a type-modifying van Laarhoven prism.
prismVL :: forall s t a b. PrismVL s t a b -> Prism s t a b Source #
Build a Prism
from the van Laarhoven representation.
toPrismVL :: Is k A_Prism => Optic k is s t a b -> PrismVL s t a b Source #
Convert a Prism
to the van Laarhoven representation.
withPrismVL :: Is k A_Prism => Optic k is s t a b -> (PrismVL s t a b -> r) -> r Source #
Work with a Prism
in the van Laarhoven representation.
Lens
type LensVL s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t #
Type synonym for a type-modifying van Laarhoven lens.
toLensVL :: Is k A_Lens => Optic k is s t a b -> LensVL s t a b #
Convert a lens to the van Laarhoven representation.
withLensVL :: Is k A_Lens => Optic k is s t a b -> (LensVL s t a b -> r) -> r #
Work with a lens in the van Laarhoven representation.
IxLens
type IxLensVL i s t a b = forall (f :: Type -> Type). Functor f => (i -> a -> f b) -> s -> f t #
Type synonym for a type-modifying van Laarhoven indexed lens.
type IxLensVL' i s a = IxLensVL i s s a a #
Type synonym for a type-preserving van Laarhoven indexed lens.
ilensVL :: IxLensVL i s t a b -> IxLens i s t a b #
Build an indexed lens from the van Laarhoven representation.
toIxLensVL :: (Is k A_Lens, HasSingleIndex is i) => Optic k is s t a b -> IxLensVL i s t a b #
Convert an indexed lens to its van Laarhoven representation.
withIxLensVL :: (Is k A_Lens, HasSingleIndex is i) => Optic k is s t a b -> (IxLensVL i s t a b -> r) -> r #
Work with an indexed lens in the van Laarhoven representation.
AffineTraversal
type AffineTraversalVL s t a b = forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (a -> f b) -> s -> f t #
Type synonym for a type-modifying van Laarhoven affine traversal.
Note: this isn't exactly van Laarhoven representation as there is
no Pointed
class (which would be a superclass of Applicative
that contains pure
but not <*>
). You can interpret the first
argument as a dictionary of Pointed
that supplies the point
function (i.e. the implementation of pure
).
A TraversalVL
has Applicative
available and
hence can combine the effects arising from multiple elements using
<*>
. In contrast, an AffineTraversalVL
has no way to combine
effects from multiple elements, so it must act on at most one
element. (It can act on none at all thanks to the availability of
point
.)
type AffineTraversalVL' s a = AffineTraversalVL s s a a #
Type synonym for a type-preserving van Laarhoven affine traversal.
atraversalVL :: AffineTraversalVL s t a b -> AffineTraversal s t a b #
Build an affine traversal from the van Laarhoven representation.
Example:
>>>
:{
azSnd = atraversalVL $ \point f ab@(a, b) -> if a >= 'a' && a <= 'z' then (a, ) <$> f b else point ab :}
>>>
preview azSnd ('a', "Hi")
Just "Hi"
>>>
preview azSnd ('@', "Hi")
Nothing
>>>
over azSnd (++ "!!!") ('f', "Hi")
('f',"Hi!!!")
>>>
set azSnd "Bye" ('Y', "Hi")
('Y',"Hi")
atraverseOf :: (Is k An_AffineTraversal, Functor f) => Optic k is s t a b -> (forall r. r -> f r) -> (a -> f b) -> s -> f t #
Traverse over the target of an AffineTraversal
and compute a
Functor
-based answer.
Since: optics-core-0.3
IxAffineTraversal
type IxAffineTraversalVL i s t a b = forall (f :: Type -> Type). Functor f => (forall r. r -> f r) -> (i -> a -> f b) -> s -> f t #
Type synonym for a type-modifying van Laarhoven indexed affine traversal.
Note: this isn't exactly van Laarhoven representation as there is no
Pointed
class (which would be a superclass of Applicative
that contains
pure
but not <*>
). You can interpret the first argument as a dictionary
of Pointed
that supplies the point
function (i.e. the implementation of
pure
).
type IxAffineTraversalVL' i s a = IxAffineTraversalVL i s s a a #
Type synonym for a type-preserving van Laarhoven indexed affine traversal.
iatraversalVL :: IxAffineTraversalVL i s t a b -> IxAffineTraversal i s t a b #
Build an indexed affine traversal from the van Laarhoven representation.
iatraverseOf :: (Is k An_AffineTraversal, Functor f, HasSingleIndex is i) => Optic k is s t a b -> (forall r. r -> f r) -> (i -> a -> f b) -> s -> f t #
Traverse over the target of an IxAffineTraversal
and compute a
Functor
-based answer.
Since: optics-core-0.3
Traversal
type TraversalVL s t a b = forall (f :: Type -> Type). Applicative f => (a -> f b) -> s -> f t #
Type synonym for a type-modifying van Laarhoven traversal.
type TraversalVL' s a = TraversalVL s s a a #
Type synonym for a type-preserving van Laarhoven traversal.
traversalVL :: TraversalVL s t a b -> Traversal s t a b #
Build a traversal from the van Laarhoven representation.
traversalVL
.
traverseOf
≡id
traverseOf
.
traversalVL
≡id
traverseOf :: (Is k A_Traversal, Applicative f) => Optic k is s t a b -> (a -> f b) -> s -> f t #
Map each element of a structure targeted by a Traversal
, evaluate these
actions from left to right, and collect the results.
IxTraversal
type IxTraversalVL i s t a b = forall (f :: Type -> Type). Applicative f => (i -> a -> f b) -> s -> f t #
Type synonym for a type-modifying van Laarhoven indexed traversal.
type IxTraversalVL' i s a = IxTraversalVL i s s a a #
Type synonym for a type-preserving van Laarhoven indexed traversal.
itraversalVL :: IxTraversalVL i s t a b -> IxTraversal i s t a b #
Build an indexed traversal from the van Laarhoven representation.
itraversalVL
.
itraverseOf
≡id
itraverseOf
.
itraversalVL
≡id
itraverseOf :: (Is k A_Traversal, Applicative f, HasSingleIndex is i) => Optic k is s t a b -> (i -> a -> f b) -> s -> f t #
Map each element of a structure targeted by an IxTraversal
(supplying the
index), evaluate these actions from left to right, and collect the results.
This yields the van Laarhoven representation of an indexed traversal.