indexed-traversable-0.1.1: FunctorWithIndex, FoldableWithIndex, TraversableWithIndex
Safe HaskellSafe
LanguageHaskell2010

Data.Traversable.WithIndex

Description

Indexed Traversables

Synopsis

Indexed Traversables

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

A Traversable with an additional index.

An instance must satisfy a (modified) form of the Traversable laws:

itraverse (const Identity) ≡ Identity
fmap (itraverse f) . itraverse g ≡ getCompose . itraverse (\i -> Compose . fmap (f i) . g i)

Minimal complete definition

Nothing

Methods

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

Traverse an indexed container.

itraverseitraverseOf itraversed

default itraverse :: (i ~ Int, Applicative f) => (i -> a -> f b) -> t a -> f (t b) Source #

Instances

Instances details
TraversableWithIndex Int [] Source # 
Instance details

Defined in WithIndex

Methods

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

TraversableWithIndex Int ZipList Source # 
Instance details

Defined in WithIndex

Methods

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

TraversableWithIndex Int NonEmpty Source # 
Instance details

Defined in WithIndex

Methods

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

TraversableWithIndex Int IntMap Source # 
Instance details

Defined in WithIndex

Methods

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

TraversableWithIndex Int Seq Source # 
Instance details

Defined in WithIndex

Methods

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

TraversableWithIndex () Maybe Source # 
Instance details

Defined in WithIndex

Methods

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

TraversableWithIndex () Par1 Source # 
Instance details

Defined in WithIndex

Methods

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

TraversableWithIndex () Identity Source # 
Instance details

Defined in WithIndex

Methods

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

TraversableWithIndex k (Map k) Source # 
Instance details

Defined in WithIndex

Methods

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

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

Defined in WithIndex

Methods

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

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

Defined in WithIndex

Methods

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

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

Defined in WithIndex

Methods

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

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

Defined in WithIndex

Methods

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

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

Defined in WithIndex

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 WithIndex

Methods

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

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

Defined in WithIndex

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 WithIndex

Methods

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

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

Defined in WithIndex

Methods

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

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

Defined in WithIndex

Methods

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

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

Defined in WithIndex

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 WithIndex

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 WithIndex

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 WithIndex

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 WithIndex

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 WithIndex

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 WithIndex

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 WithIndex

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 WithIndex

Methods

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

Indexed Traversable Combinators

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

Traverse with an index (and the arguments flipped).

for a ≡ ifor a . const
iforflip itraverse

imapM :: (TraversableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m (t b) Source #

Map each element of a structure to a monadic action, evaluate these actions from left to right, and collect the results, with access the index.

When you don't need access to the index mapM is more liberal in what it can accept.

mapMimapM . const

iforM :: (TraversableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m (t b) Source #

Map each element of a structure to a monadic action, evaluate these actions from left to right, and collect the results, with access its position (and the arguments flipped).

forM a ≡ iforM a . const
iforMflip imapM

imapAccumR :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b) Source #

Generalizes mapAccumR to add access to the index.

imapAccumROf accumulates state from right to left.

mapAccumRimapAccumR . const

imapAccumL :: TraversableWithIndex i t => (i -> s -> a -> (s, b)) -> s -> t a -> (s, t b) Source #

Generalizes mapAccumL to add access to the index.

imapAccumLOf accumulates state from left to right.

mapAccumLOfimapAccumL . const

Default implementations

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

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