lens-3.3: Lenses, Folds and Traversals

PortabilityRank2Types
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellTrustworthy

Control.Lens.WithIndex

Contents

Description

(These need to be defined together for DefaultSignatures to work.)

Synopsis

Indexed Functors

class Functor f => FunctorWithIndex i f | f -> i whereSource

A Functor with an additional index.

Instances must satisfy a modified form of the Functor laws:

 imap f . imap g ≡ imap (i -> f i . g i)
 imap (_ a -> a) ≡ id

Methods

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

Map with access to the index.

Instances

FunctorWithIndex Int []

The position in the list is available as the index.

FunctorWithIndex Int Seq

The position in the sequence is available as the index.

FunctorWithIndex Int IntMap 
FunctorWithIndex Int Vector 
(Functor (HashMap k), Eq k, Hashable k) => FunctorWithIndex k (HashMap k) 
(Functor (Map k), Ord k) => FunctorWithIndex k (Map k) 

imapped :: FunctorWithIndex i f => IndexedSetter i (f a) (f b) a bSource

The IndexedSetter for a FunctorWithIndex.

If you don't need access to the index, then mapped is more flexible in what it accepts.

Indexed Foldables

class Foldable f => FoldableWithIndex i f | f -> i whereSource

A container that supports folding with an additional index.

Methods

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

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

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

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 -> bSource

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 -> bSource

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 -> bSource

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.

foldlOf' l ≡ ifoldlOf' l . const
 ifoldlOf' :: IndexedGetter i a c            -> (i -> e -> c -> e) -> e -> a -> e
 ifoldlOf' :: IndexedFold i a c              -> (i -> e -> c -> e) -> e -> a -> e
 ifoldlOf' :: SimpleIndexedLens i a c        -> (i -> e -> c -> e) -> e -> a -> e
 ifoldlOf' :: SimpleIndexedTraversal i a c   -> (i -> e -> c -> e) -> e -> a -> e

ifolding :: FoldableWithIndex i f => (a -> f c) -> IndexedFold i a cSource

Obtain a Fold by lifting an operation that returns a foldable result.

This can be useful to lift operations from Data.List and elsewhere into a Fold.

Indexed Foldable Combinators

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

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.

any = iany . const

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

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

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 forMOf_ is more flexible in what it accepts.

forMOf_ l a ≡ iforMOf l 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 bSource

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 bSource

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 fst . itoList

Converting to Folds

withIndices :: FoldableWithIndex i f => Fold (f a) (i, a)Source

Fold a container with indices returning both the indices and the values.

indices :: FoldableWithIndex i f => Fold (f a) iSource

Fold a container with indices returning only the indices.

Indexed Traversables

class (FunctorWithIndex i t, FoldableWithIndex i t, Traversable t) => TraversableWithIndex i t | t -> i whereSource

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)

Methods

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

Traverse an indexed container.

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

iwhere :: TraversableWithIndex i t => (i -> Bool) -> SimpleIndexedTraversal i (t a) aSource

Access the element of an indexed container where the index matches a predicate.

>>> over (iwhere (>0)) Prelude.reverse $ ["He","was","stressed","o_O"]
["He","saw","desserts","O_o"]