optics-extra-0.3: Extra utilities and instances for optics-core

Safe HaskellNone
LanguageHaskell2010

Optics.Indexed

Contents

Description

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 for optic kinds that can be indexed

class IxOptic k s t a b where #

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 #

Convert an indexed optic to its unindexed equivalent.

Instances
IxOptic A_Lens s t a b 
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 #

IxOptic An_AffineTraversal s t a b 
Instance details

Defined in Optics.Indexed.Core

IxOptic A_Traversal s t a b 
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 #

IxOptic A_Setter s t a b 
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 #

(s ~ t, a ~ b) => IxOptic A_Getter s t a b 
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 #

(s ~ t, a ~ b) => IxOptic An_AffineFold s t a b 
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 #

(s ~ t, a ~ b) => IxOptic A_Fold s t a b 
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 #

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 #

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

(<%>) :: (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

Functors with index

class Functor f => FunctorWithIndex i (f :: Type -> Type) | f -> i where #

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

Minimal complete definition

Nothing

Methods

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

Instances
FunctorWithIndex Int [] 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex Int ZipList 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex Int NonEmpty 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex Int IntMap 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex Int Seq

The position in the Seq is available as the index.

Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex Int Vector Source # 
Instance details

Defined in Optics.Indexed

Methods

imap :: (Int -> a -> b) -> Vector a -> Vector b #

FunctorWithIndex () Maybe 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex () Par1 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex () Identity 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex k (HashMap k) Source # 
Instance details

Defined in Optics.Indexed

Methods

imap :: (k -> a -> b) -> HashMap k a -> HashMap k b #

FunctorWithIndex k (Map k) 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex k ((,) k) 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex Void (Const e :: Type -> Type)

Since: optics-core-0.3

Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

imap :: (Void -> a -> b) -> Const e a -> Const e b #

FunctorWithIndex Void (Constant e :: Type -> Type)

Since: optics-core-0.3

Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

imap :: (Void -> a -> b) -> Constant e a -> Constant e b #

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex [Int] Tree 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

Foldable with index

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

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 #

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

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

Instances
FoldableWithIndex Int [] 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

FoldableWithIndex Int ZipList 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

FoldableWithIndex Int NonEmpty 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

FoldableWithIndex Int IntMap 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

FoldableWithIndex Int Seq 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

FoldableWithIndex Int Vector Source # 
Instance details

Defined in Optics.Indexed

Methods

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

ifoldr :: (Int -> a -> b -> b) -> b -> Vector a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> Vector a -> b #

FoldableWithIndex () Maybe 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

FoldableWithIndex () Par1 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

FoldableWithIndex () Identity 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

FoldableWithIndex k (HashMap k) Source # 
Instance details

Defined in Optics.Indexed

Methods

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

ifoldr :: (k -> a -> b -> b) -> b -> HashMap k a -> b #

ifoldl' :: (k -> b -> a -> b) -> b -> HashMap k a -> b #

FoldableWithIndex k (Map k) 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

FoldableWithIndex k ((,) k) 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

FoldableWithIndex Void (Const e :: Type -> Type)

Since: optics-core-0.3

Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

ifoldMap :: Monoid m => (Void -> a -> m) -> Const e a -> m #

ifoldr :: (Void -> a -> b -> b) -> b -> Const e a -> b #

ifoldl' :: (Void -> b -> a -> b) -> b -> Const e a -> b #

FoldableWithIndex Void (Constant e :: Type -> Type)

Since: optics-core-0.3

Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

ifoldMap :: Monoid m => (Void -> a -> m) -> Constant e a -> m #

ifoldr :: (Void -> a -> b -> b) -> b -> Constant e a -> b #

ifoldl' :: (Void -> b -> a -> b) -> b -> Constant e a -> b #

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

FoldableWithIndex [Int] Tree 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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 Traversables that have an additional read-only index available.

Methods

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

Instances
TraversableWithIndex Int [] 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

TraversableWithIndex Int ZipList 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

TraversableWithIndex Int NonEmpty 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

TraversableWithIndex Int IntMap 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

TraversableWithIndex Int Seq 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

TraversableWithIndex Int Vector Source # 
Instance details

Defined in Optics.Indexed

Methods

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

TraversableWithIndex () Maybe 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

TraversableWithIndex () Par1 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

TraversableWithIndex () Identity 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

TraversableWithIndex k (HashMap k) Source # 
Instance details

Defined in Optics.Indexed

Methods

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

TraversableWithIndex k (Map k) 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

TraversableWithIndex k ((,) k) 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

TraversableWithIndex Void (Const e :: Type -> Type)

Since: optics-core-0.3

Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> Const e a -> f (Const e b) #

TraversableWithIndex Void (Constant e :: Type -> Type)

Since: optics-core-0.3

Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

itraverse :: Applicative f => (Void -> a -> f b) -> Constant e a -> f (Constant e b) #

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

TraversableWithIndex [Int] Tree 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Flipped itraverse

Orphan instances

FunctorWithIndex Int Vector Source # 
Instance details

Methods

imap :: (Int -> a -> b) -> Vector a -> Vector b #

FoldableWithIndex Int Vector Source # 
Instance details

Methods

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

ifoldr :: (Int -> a -> b -> b) -> b -> Vector a -> b #

ifoldl' :: (Int -> b -> a -> b) -> b -> Vector a -> b #

TraversableWithIndex Int Vector Source # 
Instance details

Methods

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

FunctorWithIndex k (HashMap k) Source # 
Instance details

Methods

imap :: (k -> a -> b) -> HashMap k a -> HashMap k b #

FoldableWithIndex k (HashMap k) Source # 
Instance details

Methods

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

ifoldr :: (k -> a -> b -> b) -> b -> HashMap k a -> b #

ifoldl' :: (k -> b -> a -> b) -> b -> HashMap k a -> b #

TraversableWithIndex k (HashMap k) Source # 
Instance details

Methods

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