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

Data.Foldable.WithIndex

Description

Indexed Foldables.

Synopsis

Indexed Foldables

class Foldable f => FoldableWithIndex i f | f -> i where Source #

A container that supports folding with an additional index.

Minimal complete definition

Nothing

Methods

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

Fold a container by mapping value to an arbitrary Monoid with access to the index i.

When you don't need access to the index then foldMap is more flexible in what it accepts.

foldMapifoldMap . const

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

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

A variant of ifoldMap that is strict in the accumulator.

When you don't need access to the index then foldMap' is more flexible in what it accepts.

foldMap'ifoldMap' . const

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

Right-associative fold of an indexed container with access to the index i.

When you don't need access to the index then foldr is more flexible in what it accepts.

foldrifoldr . const

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

Left-associative fold of an indexed container with access to the index i.

When you don't need access to the index then foldl is more flexible in what it accepts.

foldlifoldl . const

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

Strictly fold right over the elements of a structure with access to the index i.

When you don't need access to the index then foldr' is more flexible in what it accepts.

foldr'ifoldr' . const

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

Fold over the elements of a structure with an index, associating to the left, but strictly.

When you don't need access to the index then foldlOf' is more flexible in what it accepts.

foldl' l ≡ ifoldl' l . const

Instances

Instances details
FoldableWithIndex Int [] Source # 
Instance details

Defined in WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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

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

FoldableWithIndex k (Map k) Source # 
Instance details

Defined in WithIndex

Methods

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

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 #

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

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

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

Defined in WithIndex

Methods

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

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 #

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

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

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

Defined in WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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

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

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

Defined in WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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

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

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

Defined in WithIndex

Methods

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

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 #

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

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

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

Defined in WithIndex

Methods

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

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 #

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 # 
Instance details

Defined in WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 WithIndex

Methods

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

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 #

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 #

Indexed Foldable Combinators

iany :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool Source #

Return whether or not any element in a container satisfies a predicate, with access to the index i.

When you don't need access to the index then any is more flexible in what it accepts.

anyiany . const

iall :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool Source #

Return whether or not all elements in a container satisfy a predicate, with access to the index i.

When you don't need access to the index then all is more flexible in what it accepts.

alliall . const

inone :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Bool Source #

Return whether or not none of the elements in a container satisfy a predicate, with access to the index i.

When you don't need access to the index then none is more flexible in what it accepts.

noneinone . const
inone f ≡ not . iany f

none :: Foldable f => (a -> Bool) -> f a -> Bool Source #

Determines whether no elements of the structure satisfy the predicate.

none f ≡ not . any f

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

Traverse elements with access to the index i, discarding the results.

When you don't need access to the index then traverse_ is more flexible in what it accepts.

traverse_ l = itraverse . const

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

Traverse elements with access to the index i, discarding the results (with the arguments flipped).

ifor_flip itraverse_

When you don't need access to the index then for_ is more flexible in what it accepts.

for_ a ≡ ifor_ a . const

imapM_ :: (FoldableWithIndex i t, Monad m) => (i -> a -> m b) -> t a -> m () Source #

Run monadic actions for each target of an IndexedFold or IndexedTraversal with access to the index, discarding the results.

When you don't need access to the index then mapMOf_ is more flexible in what it accepts.

mapM_imapM . const

iforM_ :: (FoldableWithIndex i t, Monad m) => t a -> (i -> a -> m b) -> m () Source #

Run monadic actions for each target of an IndexedFold or IndexedTraversal with access to the index, discarding the results (with the arguments flipped).

iforM_flip imapM_

When you don't need access to the index then forM_ is more flexible in what it accepts.

forM_ a ≡ iforM a . const

iconcatMap :: FoldableWithIndex i f => (i -> a -> [b]) -> f a -> [b] Source #

Concatenate the results of a function of the elements of an indexed container with access to the index.

When you don't need access to the index then concatMap is more flexible in what it accepts.

concatMapiconcatMap . const
iconcatMapifoldMap

ifind :: FoldableWithIndex i f => (i -> a -> Bool) -> f a -> Maybe (i, a) Source #

Searches a container with a predicate that is also supplied the index, returning the left-most element of the structure matching the predicate, or Nothing if there is no such element.

When you don't need access to the index then find is more flexible in what it accepts.

findifind . const

ifoldrM :: (FoldableWithIndex i f, Monad m) => (i -> a -> b -> m b) -> b -> f a -> m b Source #

Monadic fold right over the elements of a structure with an index.

When you don't need access to the index then foldrM is more flexible in what it accepts.

foldrMifoldrM . const

ifoldlM :: (FoldableWithIndex i f, Monad m) => (i -> b -> a -> m b) -> b -> f a -> m b Source #

Monadic fold over the elements of a structure with an index, associating to the left.

When you don't need access to the index then foldlM is more flexible in what it accepts.

foldlMifoldlM . const

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

Extract the key-value pairs from a structure.

When you don't need access to the indices in the result, then toList is more flexible in what it accepts.

toListmap snd . itoList