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

Safe HaskellNone
LanguageHaskell2010

Optics.Internal.Indexed.Classes

Description

Internal implementation details of indexed optics.

This module is intended for internal use only, and may change without warning in subsequent releases.

Synopsis

Documentation

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.Classes

Methods

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

FunctorWithIndex Int ZipList Source # 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex Int NonEmpty Source # 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex Int IntMap Source # 
Instance details

Defined in Optics.Internal.Indexed.Classes

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.Classes

Methods

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

FunctorWithIndex () Maybe Source # 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex () Par1 Source # 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex () Identity Source # 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

FunctorWithIndex k (Map k) Source # 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

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.Classes

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.Classes

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.Classes

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.Classes

Methods

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

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

Since: 0.3

Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Since: 0.3

Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

Defined in Optics.Internal.Indexed.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

Methods

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

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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 (Const e :: Type -> Type) Source #

Since: 0.3

Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Since: 0.3

Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

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

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

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

Defined in Optics.Internal.Indexed.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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_.

itoList :: FoldableWithIndex i f => f a -> [(i, a)] Source #

List of elements of a structure with an index, from left to right.

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.Classes

Methods

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

TraversableWithIndex Int ZipList Source # 
Instance details

Defined in Optics.Internal.Indexed.Classes

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.Classes

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.Classes

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.Classes

Methods

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

TraversableWithIndex () Maybe Source # 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

TraversableWithIndex () Par1 Source # 
Instance details

Defined in Optics.Internal.Indexed.Classes

Methods

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

TraversableWithIndex () Identity Source # 
Instance details

Defined in Optics.Internal.Indexed.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

Methods

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

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

Since: 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) Source #

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

Since: 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) Source #

TraversableWithIndex Void (K1 i c :: Type -> Type) Source # 
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) Source #

TraversableWithIndex [Int] Tree Source # 
Instance details

Defined in Optics.Internal.Indexed.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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.Classes

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