lens-2.6.1: Lenses, Folds and Traversals

Portabilityrank 2 types, MPTCs, TFs, flexible
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe-Infered

Control.Lens.IndexedTraversal

Contents

Description

 

Synopsis

Indexed Traversals

type IndexedTraversal i a b c d = forall f k. (Indexed i k, Applicative f) => k (c -> f d) (a -> f b)Source

Every indexed traversal is a valid Traversal or IndexedFold.

The Indexed constraint is used to allow an IndexedTraversal to be used directly as a Traversal.

The Traversal laws are still required to hold.

Common Indexed Traversals

traverseAt :: At k m => k -> SimpleIndexedTraversal k (m v) vSource

Traverse the value at a given key in a map

traverseAt k = at k <. traverse

iwhereOf :: (Indexed i k, Applicative f) => Overloaded (Index i) f a b c c -> (i -> Bool) -> Overloaded k f a b c cSource

Access the element of an IndexedTraversal where the index matches a predicate.

>>> :m + Control.Lens
>>> over (iwhereOf (indexed traverse) (>0)) reverse $ ["He","was","stressed","o_O"]
["He","saw","desserts","O_o"]
 iwhereOf :: IndexedFold i a b            -> (i -> Bool) -> IndexedFold i a b
 iwhereOf :: IndexedGetter i a b          -> (i -> Bool) -> IndexedFold i a b
 iwhereOf :: SimpleIndexedLens i a b      -> (i -> Bool) -> SimpleIndexedTraversal i a b
 iwhereOf :: SimpleIndexedTraversal i a b -> (i -> Bool) -> SimpleIndexedTraversal i a b
 iwhereOf :: SimpleIndexedSetter i a b    -> (i -> Bool) -> SimpleIndexedSetter i a b

value :: (k -> Bool) -> SimpleIndexedTraversal k (k, v) vSource

This provides a Traversal that checks a predicate on a key before allowing you to traverse into a value.

Indexed Traversal Combinators

itraverseOf :: Overloaded (Index i) f a b c d -> (i -> c -> f d) -> a -> f bSource

Traversal with an index.

NB: When you don't need access to the index then you can just apply your IndexedTraversal directly as a function!

 itraverseOf = withIndex
 traverseOf l = itraverseOf l . const = id
 itraverseOf :: IndexedLens i a b c d      -> (i -> c -> f d) -> a -> f b
 itraverseOf :: IndexedTraversal i a b c d -> (i -> c -> f d) -> a -> f b

iforOf :: Overloaded (Index i) f a b c d -> a -> (i -> c -> f d) -> f bSource

Traverse with an index (and the arguments flipped)

forOf l a = iforOf l a . const
iforOf = flip . itraverseOf
 iforOf :: IndexedLens i a b c d      -> a -> (i -> c -> f d) -> f b
 iforOf :: IndexedTraversal i a b c d -> a -> (i -> c -> f d) -> f b

imapMOf :: Overloaded (Index i) (WrappedMonad m) a b c d -> (i -> c -> m d) -> a -> m bSource

Map each element of a structure targeted by a lens to a monadic action, evaluate these actions from left to right, and collect the results, with access its position.

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

mapMOf l = imapMOf l . const
 imapMOf :: Monad m => IndexedLens      i a b c d -> (i -> c -> m d) -> a -> m b
 imapMOf :: Monad m => IndexedTraversal i a b c d -> (i -> c -> m d) -> a -> m b

iforMOf :: Overloaded (Index i) (WrappedMonad m) a b c d -> a -> (i -> c -> m d) -> m bSource

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

 forMOf l a = iforMOf l a . const
 iforMOf = flip . imapMOf
 iforMOf :: Monad m => IndexedLens i a b c d      -> a -> (i -> c -> m d) -> m b
 iforMOf :: Monad m => IndexedTraversal i a b c d -> a -> (i -> c -> m d) -> m b

imapAccumROf :: Overloaded (Index i) (State s) a b c d -> (i -> s -> c -> (s, d)) -> s -> a -> (s, b)Source

Generalizes mapAccumR to an arbitrary IndexedTraversal with access to the index.

imapAccumROf accumulates state from right to left.

mapAccumROf l = imapAccumROf l . const
 imapAccumROf :: IndexedLens i a b c d      -> (i -> s -> c -> (s, d)) -> s -> a -> (s, b)
 imapAccumROf :: IndexedTraversal i a b c d -> (i -> s -> c -> (s, d)) -> s -> a -> (s, b)

imapAccumLOf :: Overloaded (Index i) (Backwards (State s)) a b c d -> (i -> s -> c -> (s, d)) -> s -> a -> (s, b)Source

Generalizes mapAccumL to an arbitrary IndexedTraversal with access to the index.

imapAccumLOf accumulates state from left to right.

mapAccumLOf l = imapAccumLOf l . const
 imapAccumLOf :: IndexedLens i a b c d      -> (i -> s -> c -> (s, d)) -> s -> a -> (s, b)
 imapAccumLOf :: IndexedTraversal i a b c d -> (i -> s -> c -> (s, d)) -> s -> a -> (s, b)

Storing Indexed Traversals

newtype ReifiedIndexedTraversal i a b c d Source

Useful for storage.

Simple