Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module defines general functionality for indexed optics. See the
"Indexed optics" section of the overview documentation in the Optics
module
of the main optics
package for more details.
Unlike Optics.Indexed.Core, this includes the definitions from modules for
specific indexed optic flavours such as Optics.IxTraversal, and includes
additional instances for FunctorWithIndex
and similar classes.
Synopsis
- class IxOptic k s t a b where
- noIx :: NonEmptyIndices is => Optic k is s t a b -> Optic k NoIx s t a b
- conjoined :: HasSingleIndex is i => Optic k NoIx s t a b -> Optic k is s t a b -> Optic k is s t a b
- (<%>) :: (m ~ Join k l, Is k m, Is l m, IxOptic m s t a b, HasSingleIndex is i, HasSingleIndex js j) => Optic k is s t u v -> Optic l js u v a b -> Optic m (WithIx (i, j)) s t a b
- (%>) :: (m ~ Join k l, Is k m, Is l m, IxOptic k s t u v, NonEmptyIndices is) => Optic k is s t u v -> Optic l js u v a b -> Optic m js s t a b
- (<%) :: (m ~ Join k l, Is l m, Is k m, IxOptic l u v a b, NonEmptyIndices js) => Optic k is s t u v -> Optic l js u v a b -> Optic m is s t a b
- reindexed :: HasSingleIndex is i => (i -> j) -> Optic k is s t a b -> Optic k (WithIx j) s t a b
- icompose :: (i -> j -> ix) -> Optic k (i ': (j ': ([] :: [Type]))) s t a b -> Optic k (WithIx ix) s t a b
- icompose3 :: (i1 -> i2 -> i3 -> ix) -> Optic k (i1 ': (i2 ': (i3 ': ([] :: [Type])))) s t a b -> Optic k (WithIx ix) s t a b
- icompose4 :: (i1 -> i2 -> i3 -> i4 -> ix) -> Optic k (i1 ': (i2 ': (i3 ': (i4 ': ([] :: [Type]))))) s t a b -> Optic k (WithIx ix) s t a b
- icompose5 :: (i1 -> i2 -> i3 -> i4 -> i5 -> ix) -> Optic k (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': ([] :: [Type])))))) s t a b -> Optic k (WithIx ix) s t a b
- icomposeN :: (CurryCompose is, NonEmptyIndices is) => Curry is i -> Optic k is s t a b -> Optic k (WithIx i) s t a b
- module Optics.IxAffineFold
- module Optics.IxAffineTraversal
- module Optics.IxFold
- module Optics.IxGetter
- module Optics.IxLens
- module Optics.IxSetter
- module Optics.IxTraversal
- class Functor f => FunctorWithIndex i (f :: Type -> Type) | f -> i where
- imap :: (i -> a -> b) -> f a -> f b
- class (FunctorWithIndex i f, Foldable f) => FoldableWithIndex i (f :: Type -> Type) | f -> i where
- itraverse_ :: (FoldableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f ()
- ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f ()
- itoList :: FoldableWithIndex i f => f a -> [(i, a)]
- class (FoldableWithIndex i t, Traversable t) => TraversableWithIndex i (t :: Type -> Type) | t -> i where
- itraverse :: Applicative f => (i -> a -> f b) -> t a -> f (t b)
- ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b)
Class for optic kinds that can be indexed
class IxOptic k s t a b where #
Class for optic kinds that can have indices.
noIx :: NonEmptyIndices is => Optic k is s t a b -> Optic k NoIx s t a b #
Convert an indexed optic to its unindexed equivalent.
Instances
IxOptic A_Lens s t a b | |
Defined in Optics.Indexed.Core | |
IxOptic An_AffineTraversal s t a b | |
Defined in Optics.Indexed.Core noIx :: NonEmptyIndices is => Optic An_AffineTraversal is s t a b -> Optic An_AffineTraversal NoIx s t a b # | |
IxOptic A_Traversal s t a b | |
Defined in Optics.Indexed.Core noIx :: NonEmptyIndices is => Optic A_Traversal is s t a b -> Optic A_Traversal NoIx s t a b # | |
IxOptic A_Setter s t a b | |
Defined in Optics.Indexed.Core | |
(s ~ t, a ~ b) => IxOptic A_Getter s t a b | |
Defined in Optics.Indexed.Core | |
(s ~ t, a ~ b) => IxOptic An_AffineFold s t a b | |
Defined in Optics.Indexed.Core noIx :: NonEmptyIndices is => Optic An_AffineFold is s t a b -> Optic An_AffineFold NoIx s t a b # | |
(s ~ t, a ~ b) => IxOptic A_Fold s t a b | |
Defined in Optics.Indexed.Core |
conjoined :: HasSingleIndex is i => Optic k NoIx s t a b -> Optic k is s t a b -> Optic k is s t a b #
Composition of indexed optics
(<%>) :: (m ~ Join k l, Is k m, Is l m, IxOptic m s t a b, HasSingleIndex is i, HasSingleIndex js j) => Optic k is s t u v -> Optic l js u v a b -> Optic m (WithIx (i, j)) s t a b infixl 9 #
Compose two indexed optics. Their indices are composed as a pair.
>>>
itoListOf (ifolded <%> ifolded) ["foo", "bar"]
[((0,0),'f'),((0,1),'o'),((0,2),'o'),((1,0),'b'),((1,1),'a'),((1,2),'r')]
(%>) :: (m ~ Join k l, Is k m, Is l m, IxOptic k s t u v, NonEmptyIndices is) => Optic k is s t u v -> Optic l js u v a b -> Optic m js s t a b infixl 9 #
Compose two indexed optics and drop indices of the left one. (If you want
to compose a non-indexed and an indexed optic, you can just use (%
).)
>>>
itoListOf (ifolded %> ifolded) ["foo", "bar"]
[(0,'f'),(1,'o'),(2,'o'),(0,'b'),(1,'a'),(2,'r')]
(<%) :: (m ~ Join k l, Is l m, Is k m, IxOptic l u v a b, NonEmptyIndices js) => Optic k is s t u v -> Optic l js u v a b -> Optic m is s t a b infixl 9 #
Compose two indexed optics and drop indices of the right one. (If you want
to compose an indexed and a non-indexed optic, you can just use (%
).)
>>>
itoListOf (ifolded <% ifolded) ["foo", "bar"]
[(0,'f'),(0,'o'),(0,'o'),(1,'b'),(1,'a'),(1,'r')]
reindexed :: HasSingleIndex is i => (i -> j) -> Optic k is s t a b -> Optic k (WithIx j) s t a b #
Remap the index.
>>>
itoListOf (reindexed succ ifolded) "foo"
[(1,'f'),(2,'o'),(3,'o')]
>>>
itoListOf (ifolded %& reindexed succ) "foo"
[(1,'f'),(2,'o'),(3,'o')]
icompose :: (i -> j -> ix) -> Optic k (i ': (j ': ([] :: [Type]))) s t a b -> Optic k (WithIx ix) s t a b #
Flatten indices obtained from two indexed optics.
>>>
itoListOf (ifolded % ifolded %& icompose (,)) ["foo","bar"]
[((0,0),'f'),((0,1),'o'),((0,2),'o'),((1,0),'b'),((1,1),'a'),((1,2),'r')]
icompose3 :: (i1 -> i2 -> i3 -> ix) -> Optic k (i1 ': (i2 ': (i3 ': ([] :: [Type])))) s t a b -> Optic k (WithIx ix) s t a b #
Flatten indices obtained from three indexed optics.
>>>
itoListOf (ifolded % ifolded % ifolded %& icompose3 (,,)) [["foo","bar"],["xyz"]]
[((0,0,0),'f'),((0,0,1),'o'),((0,0,2),'o'),((0,1,0),'b'),((0,1,1),'a'),((0,1,2),'r'),((1,0,0),'x'),((1,0,1),'y'),((1,0,2),'z')]
icompose4 :: (i1 -> i2 -> i3 -> i4 -> ix) -> Optic k (i1 ': (i2 ': (i3 ': (i4 ': ([] :: [Type]))))) s t a b -> Optic k (WithIx ix) s t a b #
Flatten indices obtained from four indexed optics.
icompose5 :: (i1 -> i2 -> i3 -> i4 -> i5 -> ix) -> Optic k (i1 ': (i2 ': (i3 ': (i4 ': (i5 ': ([] :: [Type])))))) s t a b -> Optic k (WithIx ix) s t a b #
Flatten indices obtained from five indexed optics.
icomposeN :: (CurryCompose is, NonEmptyIndices is) => Curry is i -> Optic k is s t a b -> Optic k (WithIx i) s t a b #
Flatten indices obtained from arbitrary number of indexed optics.
Indexed optic flavours
module Optics.IxAffineFold
module Optics.IxAffineTraversal
module Optics.IxFold
module Optics.IxGetter
module Optics.IxLens
module Optics.IxSetter
module Optics.IxTraversal
Functors with index
class Functor f => FunctorWithIndex i (f :: Type -> Type) | f -> i where #
Class for Functor
s that have an additional read-only index available.
Nothing
Instances
Foldable with index
class (FunctorWithIndex i f, Foldable f) => FoldableWithIndex i (f :: Type -> Type) | f -> i where #
Class for Foldable
s that have an additional read-only index available.
Nothing
Instances
itraverse_ :: (FoldableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f () #
Traverse FoldableWithIndex
ignoring the results.
ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f () #
Flipped itraverse_
.
itoList :: FoldableWithIndex i f => f a -> [(i, a)] #
List of elements of a structure with an index, from left to right.
Traversable with index
class (FoldableWithIndex i t, Traversable t) => TraversableWithIndex i (t :: Type -> Type) | t -> i where #
Class for Traversable
s that have an additional read-only index available.
itraverse :: Applicative f => (i -> a -> f b) -> t a -> f (t b) #
Instances
ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b) #
Flipped itraverse
Orphan instances
FunctorWithIndex Int Vector Source # | |
FoldableWithIndex Int Vector Source # | |
TraversableWithIndex Int Vector Source # | |
FunctorWithIndex k (HashMap k) Source # | |
FoldableWithIndex k (HashMap k) Source # | |
TraversableWithIndex k (HashMap k) Source # | |
itraverse :: Applicative f => (k -> a -> f b) -> HashMap k a -> f (HashMap k b) # |