optics-core-0.2: Optics as an abstract interface: core definitions

Safe HaskellNone
LanguageHaskell2010

Optics.Indexed.Core

Contents

Description

This module defines basic 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.

Synopsis

Class for optic kinds that can be indexed

class IxOptic k s t a b where Source #

Class for optic kinds that can have indices.

Methods

noIx :: NonEmptyIndices is => Optic k is s t a b -> Optic k NoIx s t a b Source #

Convert an indexed optic to its unindexed equivalent.

Instances
(s ~ t, a ~ b) => IxOptic A_Fold s t a b Source # 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: NonEmptyIndices is => Optic A_Fold is s t a b -> Optic A_Fold NoIx s t a b Source #

(s ~ t, a ~ b) => IxOptic An_AffineFold s t a b Source # 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: NonEmptyIndices is => Optic An_AffineFold is s t a b -> Optic An_AffineFold NoIx s t a b Source #

(s ~ t, a ~ b) => IxOptic A_Getter s t a b Source # 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: NonEmptyIndices is => Optic A_Getter is s t a b -> Optic A_Getter NoIx s t a b Source #

IxOptic A_Setter s t a b Source # 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: NonEmptyIndices is => Optic A_Setter is s t a b -> Optic A_Setter NoIx s t a b Source #

IxOptic A_Traversal s t a b Source # 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: NonEmptyIndices is => Optic A_Traversal is s t a b -> Optic A_Traversal NoIx s t a b Source #

IxOptic An_AffineTraversal s t a b Source # 
Instance details

Defined in Optics.Indexed.Core

IxOptic A_Lens s t a b Source # 
Instance details

Defined in Optics.Indexed.Core

Methods

noIx :: NonEmptyIndices is => Optic A_Lens is s t a b -> Optic A_Lens NoIx s t a b Source #

conjoined :: is `HasSingleIndex` i => Optic k NoIx s t a b -> Optic k is s t a b -> Optic k is s t a b Source #

Construct a conjoined indexed optic that provides a separate code path when used without indices. Useful for defining indexed optics that are as efficient as their unindexed equivalents when used without indices.

Note: conjoined f g is well-defined if and only if f ≡ noIx g.

Composition of indexed optics

(%) :: (Is k m, Is l m, m ~ Join k l, ks ~ Append is js) => Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b infixl 9 Source #

Compose two optics of compatible flavours.

Returns an optic of the appropriate supertype. If either or both optics are indexed, the composition preserves all the indices.

(<%>) :: (m ~ Join k l, Is k m, Is l m, IxOptic m s t a b, is `HasSingleIndex` i, js `HasSingleIndex` 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 Source #

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 Source #

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 Source #

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 :: is `HasSingleIndex` i => (i -> j) -> Optic k is s t a b -> Optic k (WithIx j) s t a b Source #

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] s t a b -> Optic k (WithIx ix) s t a b Source #

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] s t a b -> Optic k (WithIx ix) s t a b Source #

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] s t a b -> Optic k (WithIx ix) s t a b Source #

Flatten indices obtained from four indexed optics.

icompose5 :: (i1 -> i2 -> i3 -> i4 -> i5 -> ix) -> Optic k '[i1, i2, i3, i4, i5] s t a b -> Optic k (WithIx ix) s t a b Source #

Flatten indices obtained from five indexed optics.

icomposeN :: forall k i is s t a b. (CurryCompose is, NonEmptyIndices is) => Curry is i -> Optic k is s t a b -> Optic k (WithIx i) s t a b Source #

Flatten indices obtained from arbitrary number of indexed optics.

Indexed optic flavours

Functors with index

class Functor f => FunctorWithIndex i f | f -> i where Source #

Class for Functors that have an additional read-only index available.

Minimal complete definition

Nothing

Methods

imap :: (i -> a -> b) -> f a -> f b Source #

imap :: TraversableWithIndex i f => (i -> a -> b) -> f a -> f b Source #

Instances
FunctorWithIndex Int [] Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (Int -> a -> b) -> [a] -> [b] Source #

FunctorWithIndex Int ZipList Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (Int -> a -> b) -> ZipList a -> ZipList b Source #

FunctorWithIndex Int NonEmpty Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (Int -> a -> b) -> NonEmpty a -> NonEmpty b Source #

FunctorWithIndex Int IntMap Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (Int -> a -> b) -> IntMap a -> IntMap b Source #

FunctorWithIndex Int Seq Source #

The position in the Seq is available as the index.

Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (Int -> a -> b) -> Seq a -> Seq b Source #

FunctorWithIndex () Maybe Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (() -> a -> b) -> Maybe a -> Maybe b Source #

FunctorWithIndex () Par1 Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (() -> a -> b) -> Par1 a -> Par1 b Source #

FunctorWithIndex () Identity Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (() -> a -> b) -> Identity a -> Identity b Source #

Ix i => FunctorWithIndex i (Array i) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (i -> a -> b) -> Array i a -> Array i b Source #

FunctorWithIndex k (Map k) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (k -> a -> b) -> Map k a -> Map k b Source #

FunctorWithIndex k ((,) k) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (k -> a -> b) -> (k, a) -> (k, b) Source #

FunctorWithIndex Void (V1 :: Type -> Type) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (Void -> a -> b) -> V1 a -> V1 b Source #

FunctorWithIndex Void (U1 :: Type -> Type) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (Void -> a -> b) -> U1 a -> U1 b Source #

FunctorWithIndex Void (Proxy :: Type -> Type) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (Void -> a -> b) -> Proxy a -> Proxy b Source #

FunctorWithIndex i f => FunctorWithIndex i (Rec1 f) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (i -> a -> b) -> Rec1 f a -> Rec1 f b Source #

FunctorWithIndex i m => FunctorWithIndex i (IdentityT m) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (i -> a -> b) -> IdentityT m a -> IdentityT m b Source #

FunctorWithIndex i f => FunctorWithIndex i (Reverse f) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (i -> a -> b) -> Reverse f a -> Reverse f b Source #

FunctorWithIndex i f => FunctorWithIndex i (Backwards f) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (i -> a -> b) -> Backwards f a -> Backwards f b Source #

FunctorWithIndex r ((->) r :: Type -> Type) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (r -> a -> b) -> (r -> a) -> r -> b Source #

FunctorWithIndex Void (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (Void -> a -> b) -> K1 i c a -> K1 i c b Source #

FunctorWithIndex [Int] Tree Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: ([Int] -> a -> b) -> Tree a -> Tree b Source #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (f :+: g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (Either i j -> a -> b) -> (f :+: g) a -> (f :+: g) b Source #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (f :*: g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (Either i j -> a -> b) -> (f :*: g) a -> (f :*: g) b Source #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (Product f g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (Either i j -> a -> b) -> Product f g a -> Product f g b Source #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (Either i j) (Sum f g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: (Either i j -> a -> b) -> Sum f g a -> Sum f g b Source #

FunctorWithIndex i m => FunctorWithIndex (e, i) (ReaderT e m) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: ((e, i) -> a -> b) -> ReaderT e m a -> ReaderT e m b Source #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (i, j) (f :.: g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: ((i, j) -> a -> b) -> (f :.: g) a -> (f :.: g) b Source #

(FunctorWithIndex i f, FunctorWithIndex j g) => FunctorWithIndex (i, j) (Compose f g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

imap :: ((i, j) -> a -> b) -> Compose f g a -> Compose f g b Source #

Foldable with index

class (FunctorWithIndex i f, Foldable f) => FoldableWithIndex i f | f -> i where Source #

Class for Foldables that have an additional read-only index available.

Minimal complete definition

Nothing

Methods

ifoldMap :: Monoid m => (i -> a -> m) -> f a -> m Source #

ifoldMap :: (TraversableWithIndex i f, Monoid m) => (i -> a -> m) -> f a -> m Source #

ifoldr :: (i -> a -> b -> b) -> b -> f a -> b Source #

ifoldl' :: (i -> b -> a -> b) -> b -> f a -> b Source #

Instances
FoldableWithIndex Int [] Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> [a] -> m Source #

ifoldr :: (Int -> a -> b -> b) -> b -> [a] -> b Source #

ifoldl' :: (Int -> b -> a -> b) -> b -> [a] -> b Source #

FoldableWithIndex Int ZipList Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> ZipList a -> m Source #

ifoldr :: (Int -> a -> b -> b) -> b -> ZipList a -> b Source #

ifoldl' :: (Int -> b -> a -> b) -> b -> ZipList a -> b Source #

FoldableWithIndex Int NonEmpty Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> NonEmpty a -> m Source #

ifoldr :: (Int -> a -> b -> b) -> b -> NonEmpty a -> b Source #

ifoldl' :: (Int -> b -> a -> b) -> b -> NonEmpty a -> b Source #

FoldableWithIndex Int IntMap Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> IntMap a -> m Source #

ifoldr :: (Int -> a -> b -> b) -> b -> IntMap a -> b Source #

ifoldl' :: (Int -> b -> a -> b) -> b -> IntMap a -> b Source #

FoldableWithIndex Int Seq Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (Int -> a -> m) -> Seq a -> m Source #

ifoldr :: (Int -> a -> b -> b) -> b -> Seq a -> b Source #

ifoldl' :: (Int -> b -> a -> b) -> b -> Seq a -> b Source #

FoldableWithIndex () Maybe Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (() -> a -> m) -> Maybe a -> m Source #

ifoldr :: (() -> a -> b -> b) -> b -> Maybe a -> b Source #

ifoldl' :: (() -> b -> a -> b) -> b -> Maybe a -> b Source #

FoldableWithIndex () Par1 Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (() -> a -> m) -> Par1 a -> m Source #

ifoldr :: (() -> a -> b -> b) -> b -> Par1 a -> b Source #

ifoldl' :: (() -> b -> a -> b) -> b -> Par1 a -> b Source #

FoldableWithIndex () Identity Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (() -> a -> m) -> Identity a -> m Source #

ifoldr :: (() -> a -> b -> b) -> b -> Identity a -> b Source #

ifoldl' :: (() -> b -> a -> b) -> b -> Identity a -> b Source #

Ix i => FoldableWithIndex i (Array i) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (i -> a -> m) -> Array i a -> m Source #

ifoldr :: (i -> a -> b -> b) -> b -> Array i a -> b Source #

ifoldl' :: (i -> b -> a -> b) -> b -> Array i a -> b Source #

FoldableWithIndex k (Map k) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (k -> a -> m) -> Map k a -> m Source #

ifoldr :: (k -> a -> b -> b) -> b -> Map k a -> b Source #

ifoldl' :: (k -> b -> a -> b) -> b -> Map k a -> b Source #

FoldableWithIndex k ((,) k) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (k -> a -> m) -> (k, a) -> m Source #

ifoldr :: (k -> a -> b -> b) -> b -> (k, a) -> b Source #

ifoldl' :: (k -> b -> a -> b) -> b -> (k, a) -> b Source #

FoldableWithIndex Void (V1 :: Type -> Type) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (Void -> a -> m) -> V1 a -> m Source #

ifoldr :: (Void -> a -> b -> b) -> b -> V1 a -> b Source #

ifoldl' :: (Void -> b -> a -> b) -> b -> V1 a -> b Source #

FoldableWithIndex Void (U1 :: Type -> Type) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (Void -> a -> m) -> U1 a -> m Source #

ifoldr :: (Void -> a -> b -> b) -> b -> U1 a -> b Source #

ifoldl' :: (Void -> b -> a -> b) -> b -> U1 a -> b Source #

FoldableWithIndex Void (Proxy :: Type -> Type) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (Void -> a -> m) -> Proxy a -> m Source #

ifoldr :: (Void -> a -> b -> b) -> b -> Proxy a -> b Source #

ifoldl' :: (Void -> b -> a -> b) -> b -> Proxy a -> b Source #

FoldableWithIndex i f => FoldableWithIndex i (Rec1 f) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (i -> a -> m) -> Rec1 f a -> m Source #

ifoldr :: (i -> a -> b -> b) -> b -> Rec1 f a -> b Source #

ifoldl' :: (i -> b -> a -> b) -> b -> Rec1 f a -> b Source #

FoldableWithIndex i m => FoldableWithIndex i (IdentityT m) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m0 => (i -> a -> m0) -> IdentityT m a -> m0 Source #

ifoldr :: (i -> a -> b -> b) -> b -> IdentityT m a -> b Source #

ifoldl' :: (i -> b -> a -> b) -> b -> IdentityT m a -> b Source #

FoldableWithIndex i f => FoldableWithIndex i (Reverse f) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (i -> a -> m) -> Reverse f a -> m Source #

ifoldr :: (i -> a -> b -> b) -> b -> Reverse f a -> b Source #

ifoldl' :: (i -> b -> a -> b) -> b -> Reverse f a -> b Source #

FoldableWithIndex i f => FoldableWithIndex i (Backwards f) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (i -> a -> m) -> Backwards f a -> m Source #

ifoldr :: (i -> a -> b -> b) -> b -> Backwards f a -> b Source #

ifoldl' :: (i -> b -> a -> b) -> b -> Backwards f a -> b Source #

FoldableWithIndex Void (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (Void -> a -> m) -> K1 i c a -> m Source #

ifoldr :: (Void -> a -> b -> b) -> b -> K1 i c a -> b Source #

ifoldl' :: (Void -> b -> a -> b) -> b -> K1 i c a -> b Source #

FoldableWithIndex [Int] Tree Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => ([Int] -> a -> m) -> Tree a -> m Source #

ifoldr :: ([Int] -> a -> b -> b) -> b -> Tree a -> b Source #

ifoldl' :: ([Int] -> b -> a -> b) -> b -> Tree a -> b Source #

(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (f :+: g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (Either i j -> a -> m) -> (f :+: g) a -> m Source #

ifoldr :: (Either i j -> a -> b -> b) -> b -> (f :+: g) a -> b Source #

ifoldl' :: (Either i j -> b -> a -> b) -> b -> (f :+: g) a -> b Source #

(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (f :*: g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (Either i j -> a -> m) -> (f :*: g) a -> m Source #

ifoldr :: (Either i j -> a -> b -> b) -> b -> (f :*: g) a -> b Source #

ifoldl' :: (Either i j -> b -> a -> b) -> b -> (f :*: g) a -> b Source #

(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (Product f g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (Either i j -> a -> m) -> Product f g a -> m Source #

ifoldr :: (Either i j -> a -> b -> b) -> b -> Product f g a -> b Source #

ifoldl' :: (Either i j -> b -> a -> b) -> b -> Product f g a -> b Source #

(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (Either i j) (Sum f g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => (Either i j -> a -> m) -> Sum f g a -> m Source #

ifoldr :: (Either i j -> a -> b -> b) -> b -> Sum f g a -> b Source #

ifoldl' :: (Either i j -> b -> a -> b) -> b -> Sum f g a -> b Source #

(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (i, j) (f :.: g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => ((i, j) -> a -> m) -> (f :.: g) a -> m Source #

ifoldr :: ((i, j) -> a -> b -> b) -> b -> (f :.: g) a -> b Source #

ifoldl' :: ((i, j) -> b -> a -> b) -> b -> (f :.: g) a -> b Source #

(FoldableWithIndex i f, FoldableWithIndex j g) => FoldableWithIndex (i, j) (Compose f g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

ifoldMap :: Monoid m => ((i, j) -> a -> m) -> Compose f g a -> m Source #

ifoldr :: ((i, j) -> a -> b -> b) -> b -> Compose f g a -> b Source #

ifoldl' :: ((i, j) -> b -> a -> b) -> b -> Compose f g a -> b Source #

itraverse_ :: (FoldableWithIndex i t, Applicative f) => (i -> a -> f b) -> t a -> f () Source #

Traverse FoldableWithIndex ignoring the results.

ifor_ :: (FoldableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f () Source #

Flipped itraverse_.

Traversable with index

class (FoldableWithIndex i t, Traversable t) => TraversableWithIndex i t | t -> i where Source #

Class for Traversables that have an additional read-only index available.

Methods

itraverse :: Applicative f => (i -> a -> f b) -> t a -> f (t b) Source #

Instances
TraversableWithIndex Int [] Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> [a] -> f [b] Source #

TraversableWithIndex Int ZipList Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> ZipList a -> f (ZipList b) Source #

TraversableWithIndex Int NonEmpty Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> NonEmpty a -> f (NonEmpty b) Source #

TraversableWithIndex Int IntMap Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> IntMap a -> f (IntMap b) Source #

TraversableWithIndex Int Seq Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (Int -> a -> f b) -> Seq a -> f (Seq b) Source #

TraversableWithIndex () Maybe Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (() -> a -> f b) -> Maybe a -> f (Maybe b) Source #

TraversableWithIndex () Par1 Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (() -> a -> f b) -> Par1 a -> f (Par1 b) Source #

TraversableWithIndex () Identity Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (() -> a -> f b) -> Identity a -> f (Identity b) Source #

Ix i => TraversableWithIndex i (Array i) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (i -> a -> f b) -> Array i a -> f (Array i b) Source #

TraversableWithIndex k (Map k) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (k -> a -> f b) -> Map k a -> f (Map k b) Source #

TraversableWithIndex k ((,) k) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (k -> a -> f b) -> (k, a) -> f (k, b) Source #

TraversableWithIndex Void (V1 :: Type -> Type) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> V1 a -> f (V1 b) Source #

TraversableWithIndex Void (U1 :: Type -> Type) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> U1 a -> f (U1 b) Source #

TraversableWithIndex Void (Proxy :: Type -> Type) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> Proxy a -> f (Proxy b) Source #

TraversableWithIndex i f => TraversableWithIndex i (Rec1 f) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f0 => (i -> a -> f0 b) -> Rec1 f a -> f0 (Rec1 f b) Source #

TraversableWithIndex i m => TraversableWithIndex i (IdentityT m) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (i -> a -> f b) -> IdentityT m a -> f (IdentityT m b) Source #

TraversableWithIndex i f => TraversableWithIndex i (Reverse f) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f0 => (i -> a -> f0 b) -> Reverse f a -> f0 (Reverse f b) Source #

TraversableWithIndex i f => TraversableWithIndex i (Backwards f) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f0 => (i -> a -> f0 b) -> Backwards f a -> f0 (Backwards f b) Source #

TraversableWithIndex Void (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> K1 i c a -> f (K1 i c b) Source #

TraversableWithIndex [Int] Tree Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f => ([Int] -> a -> f b) -> Tree a -> f (Tree b) Source #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (f :+: g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> (f :+: g) a -> f0 ((f :+: g) b) Source #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (f :*: g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> (f :*: g) a -> f0 ((f :*: g) b) Source #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (Product f g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> Product f g a -> f0 (Product f g b) Source #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (Either i j) (Sum f g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f0 => (Either i j -> a -> f0 b) -> Sum f g a -> f0 (Sum f g b) Source #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (i, j) (f :.: g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f0 => ((i, j) -> a -> f0 b) -> (f :.: g) a -> f0 ((f :.: g) b) Source #

(TraversableWithIndex i f, TraversableWithIndex j g) => TraversableWithIndex (i, j) (Compose f g) Source # 
Instance details

Defined in Optics.Internal.Indexed

Methods

itraverse :: Applicative f0 => ((i, j) -> a -> f0 b) -> Compose f g a -> f0 (Compose f g b) Source #

ifor :: (TraversableWithIndex i t, Applicative f) => t a -> (i -> a -> f b) -> f (t b) Source #

Flipped itraverse