lens-3.3: Lenses, Folds and Traversals

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

Control.Lens.IndexedFold

Contents

Description

 

Synopsis

Indexed Folds

type IndexedFold i s a = forall k f. (Indexed i k, Applicative f, Gettable f) => k (a -> f a) (s -> f s)Source

Every IndexedFold is a valid Fold.

Consuming Indexed Folds

ifoldMapOf :: IndexedGetting i m s t a b -> (i -> a -> m) -> s -> mSource

Fold an IndexedFold or IndexedTraversal by mapping indices and values to an arbitrary Monoid with access to the index i.

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

foldMapOf l ≡ ifoldMapOf l . const
 ifoldMapOf ::             IndexedGetter i a s          -> (i -> s -> m) -> a -> m
 ifoldMapOf :: Monoid m => IndexedFold i a s            -> (i -> s -> m) -> a -> m
 ifoldMapOf ::             SimpleIndexedLens i a s      -> (i -> s -> m) -> a -> m
 ifoldMapOf :: Monoid m => SimpleIndexedTraversal i a s -> (i -> s -> m) -> a -> m

ifoldrOf :: IndexedGetting i (Endo r) s t a b -> (i -> a -> r -> r) -> r -> s -> rSource

Right-associative fold of parts of a structure that are viewed through an IndexedFold or IndexedTraversal with access to the index i.

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

foldrOf l ≡ ifoldrOf l . const
 ifoldrOf :: IndexedGetter i s a          -> (i -> a -> r -> r) -> r -> s -> r
 ifoldrOf :: IndexedFold i s a            -> (i -> a -> r -> r) -> r -> s -> r
 ifoldrOf :: SimpleIndexedLens i s a      -> (i -> a -> r -> r) -> r -> s -> r
 ifoldrOf :: SimpleIndexedTraversal i s a -> (i -> a -> r -> r) -> r -> s -> r

ifoldlOf :: IndexedGetting i (Dual (Endo r)) s t a b -> (i -> r -> a -> r) -> r -> s -> rSource

Left-associative fold of the parts of a structure that are viewed through an IndexedFold or IndexedTraversal with access to the index i.

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 s a          -> (i -> r -> a -> r) -> r -> s -> r
 ifoldlOf :: IndexedFold i s a            -> (i -> r -> a -> r) -> r -> s -> r
 ifoldlOf :: SimpleIndexedLens i s a      -> (i -> r -> a -> r) -> r -> s -> r
 ifoldlOf :: SimpleIndexedTraversal i s a -> (i -> r -> a -> r) -> r -> s -> r

ianyOf :: IndexedGetting i Any s t a b -> (i -> a -> Bool) -> s -> BoolSource

Return whether or not any element viewed through an IndexedFold or IndexedTraversal satisfy a predicate, with access to the index i.

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

anyOf l ≡ ianyOf l . const
 ianyOf :: IndexedGetter i s a          -> (i -> a -> Bool) -> s -> Bool
 ianyOf :: IndexedFold i s a            -> (i -> a -> Bool) -> s -> Bool
 ianyOf :: SimpleIndexedLens i s a      -> (i -> a -> Bool) -> s -> Bool
 ianyOf :: SimpleIndexedTraversal i s a -> (i -> a -> Bool) -> s -> Bool

iallOf :: IndexedGetting i All s t a b -> (i -> a -> Bool) -> s -> BoolSource

Return whether or not all elements viewed through an IndexedFold or IndexedTraversal satisfy a predicate, with access to the index i.

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

allOf l ≡ iallOf l . const
 iallOf :: IndexedGetter i s a          -> (i -> a -> Bool) -> s -> Bool
 iallOf :: IndexedFold i s a            -> (i -> a -> Bool) -> s -> Bool
 iallOf :: SimpleIndexedLens i s a      -> (i -> a -> Bool) -> s -> Bool
 iallOf :: SimpleIndexedTraversal i s a -> (i -> a -> Bool) -> s -> Bool

itraverseOf_ :: Functor f => IndexedGetting i (Traversed f) s t a b -> (i -> a -> f r) -> s -> f ()Source

Traverse the targets of an IndexedFold or IndexedTraversal with access to the index i, discarding the results.

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

traverseOf_ l ≡ itraverseOf l . const
 itraverseOf_ :: Functor f     => IndexedGetter i s a          -> (i -> a -> f r) -> s -> f ()
 itraverseOf_ :: Applicative f => IndexedFold i s a            -> (i -> a -> f r) -> s -> f ()
 itraverseOf_ :: Functor f     => SimpleIndexedLens i s a      -> (i -> a -> f r) -> s -> f ()
 itraverseOf_ :: Applicative f => SimpleIndexedTraversal i s a -> (i -> a -> f r) -> s -> f ()

iforOf_ :: Functor f => IndexedGetting i (Traversed f) s t a b -> s -> (i -> a -> f r) -> f ()Source

Traverse the targets of an IndexedFold or IndexedTraversal with access to the index, discarding the results (with the arguments flipped).

iforOf_flip . itraverseOf_

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

forOf_ l a ≡ iforOf_ l a . const
 iforOf_ :: Functor f     => IndexedGetter i s a          -> s -> (i -> a -> f r) -> f ()
 iforOf_ :: Applicative f => IndexedFold i s a            -> s -> (i -> a -> f r) -> f ()
 iforOf_ :: Functor f     => SimpleIndexedLens i s a      -> s -> (i -> a -> f r) -> f ()
 iforOf_ :: Applicative f => SimpleIndexedTraversal i s a -> s -> (i -> a -> f r) -> f ()

imapMOf_ :: Monad m => IndexedGetting i (Sequenced m) s t a b -> (i -> a -> m r) -> s -> 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.

mapMOf_ l ≡ imapMOf l . const
 imapMOf_ :: Monad m => IndexedGetter i s a          -> (i -> a -> m r) -> s -> m ()
 imapMOf_ :: Monad m => IndexedFold i s a            -> (i -> a -> m r) -> s -> m ()
 imapMOf_ :: Monad m => SimpleIndexedLens i s a      -> (i -> a -> m r) -> s -> m ()
 imapMOf_ :: Monad m => SimpleIndexedTraversal i s a -> (i -> a -> m r) -> s -> m ()

iforMOf_ :: Monad m => IndexedGetting i (Sequenced m) s t a b -> s -> (i -> a -> m r) -> 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).

iforMOf_flip . imapMOf_

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
 iforMOf_ :: Monad m => IndexedGetter i s a          -> s -> (i -> a -> m r) -> m ()
 iforMOf_ :: Monad m => IndexedFold i s a            -> s -> (i -> a -> m r) -> m ()
 iforMOf_ :: Monad m => SimpleIndexedLens i s a      -> s -> (i -> a -> m r) -> m ()
 iforMOf_ :: Monad m => SimpleIndexedTraversal i s a -> s -> (i -> a -> m r) -> m ()

iconcatMapOf :: IndexedGetting i [r] s t a b -> (i -> a -> [r]) -> s -> [r]Source

Concatenate the results of a function of the elements of an IndexedFold or IndexedTraversal with access to the index.

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

 concatMapOf l ≡ iconcatMapOf l . const
 iconcatMapOfifoldMapOf
 iconcatMapOf :: IndexedGetter i s a          -> (i -> a -> [r]) -> s -> [r]
 iconcatMapOf :: IndexedFold i s a            -> (i -> a -> [r]) -> s -> [r]
 iconcatMapOf :: SimpleIndexedLens i s a      -> (i -> a -> [r]) -> s -> [r]
 iconcatMapOf :: SimpleIndexedTraversal i s a -> (i -> a -> [r]) -> s -> [r]

ifindOf :: IndexedGetting i (First (i, a)) s t a b -> (i -> a -> Bool) -> s -> Maybe (i, a)Source

The findOf function takes an IndexedFold or IndexedTraversal, a predicate that is also supplied the index, a structure and returns 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 findOf is more flexible in what it accepts.

findOf l ≡ ifindOf l . const
 ifindOf :: IndexedGetter s a          -> (i -> a -> Bool) -> s -> Maybe (i, a)
 ifindOf :: IndexedFold s a            -> (i -> a -> Bool) -> s -> Maybe (i, a)
 ifindOf :: SimpleIndexedLens s a      -> (i -> a -> Bool) -> s -> Maybe (i, a)
 ifindOf :: SimpleIndexedTraversal s a -> (i -> a -> Bool) -> s -> Maybe (i, a)

ifoldrOf' :: IndexedGetting i (Dual (Endo (r -> r))) s t a b -> (i -> a -> r -> r) -> r -> s -> rSource

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

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

foldrOf' l ≡ ifoldrOf' l . const
 ifoldrOf' :: IndexedGetter i s a          -> (i -> a -> r -> r) -> r -> s -> r
 ifoldrOf' :: IndexedFold i s a            -> (i -> a -> r -> r) -> r -> s -> r
 ifoldrOf' :: SimpleIndexedLens i s a      -> (i -> a -> r -> r) -> r -> s -> r
 ifoldrOf' :: SimpleIndexedTraversal i s a -> (i -> a -> r -> r) -> r -> s -> r

ifoldlOf' :: IndexedGetting i (Endo (r -> r)) s t a b -> (i -> r -> a -> r) -> r -> s -> rSource

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 s a            -> (i -> r -> a -> r) -> r -> s -> r
 ifoldlOf' :: IndexedFold i s a              -> (i -> r -> a -> r) -> r -> s -> r
 ifoldlOf' :: SimpleIndexedLens i s a        -> (i -> r -> a -> r) -> r -> s -> r
 ifoldlOf' :: SimpleIndexedTraversal i s a   -> (i -> r -> a -> r) -> r -> s -> r

ifoldrMOf :: Monad m => IndexedGetting i (Dual (Endo (r -> m r))) s t a b -> (i -> a -> r -> m r) -> r -> s -> m rSource

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

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

foldrMOf l ≡ ifoldrMOf l . const
 ifoldrMOf :: Monad m => IndexedGetter i s a          -> (i -> a -> r -> m r) -> r -> s -> r
 ifoldrMOf :: Monad m => IndexedFold i s a            -> (i -> a -> r -> m r) -> r -> s -> r
 ifoldrMOf :: Monad m => SimpleIndexedLens i s a      -> (i -> a -> r -> m r) -> r -> s -> r
 ifoldrMOf :: Monad m => SimpleIndexedTraversal i s a -> (i -> a -> r -> m r) -> r -> s -> r

ifoldlMOf :: Monad m => IndexedGetting i (Endo (r -> m r)) s t a b -> (i -> r -> a -> m r) -> r -> s -> m rSource

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

foldlMOf l ≡ ifoldlMOf l . const
 ifoldlOf' :: Monad m => IndexedGetter i s a            -> (i -> r -> a -> m r) -> r -> s -> r
 ifoldlOf' :: Monad m => IndexedFold i s a              -> (i -> r -> a -> m r) -> r -> s -> r
 ifoldlOf' :: Monad m => SimpleIndexedLens i s a        -> (i -> r -> a -> m r) -> r -> s -> r
 ifoldlOf' :: Monad m => SimpleIndexedTraversal i s a   -> (i -> r -> a -> m r) -> r -> s -> r

itoListOf :: IndexedGetting i [(i, a)] s t a b -> s -> [(i, a)]Source

Extract the key-value pairs from a structure.

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

toListOf l ≡ map fst . itoListOf l
 itoListOf :: IndexedGetter i s a          -> s -> [(i,a)]
 itoListOf :: IndexedFold i s a            -> s -> [(i,a)]
 itoListOf :: SimpleIndexedLens i s a      -> s -> [(i,a)]
 itoListOf :: SimpleIndexedTraversal i s a -> s -> [(i,a)]

Converting to Folds

withIndicesOf :: Functor f => Overloaded (Index i) f s t a b -> LensLike f s t (i, a) (j, b)Source

Transform an indexed fold into a fold of both the indices and the values.

 withIndicesOf :: IndexedFold i s a             -> Fold s (i, a)
 withIndicesOf :: SimpleIndexedLens i s a      -> Getter s (i, a)
 withIndicesOf :: SimpleIndexedTraversal i s a -> Fold s (i, a)

All Fold operations are safe, and comply with the laws. However:

Passing this an IndexedTraversal will still allow many Traversal combinators to type check on the result, but the result can only be legally traversed by operations that do not edit the indices.

 withIndicesOf :: IndexedTraversal i s t a b -> Traversal s t (i, a) (j, b)

Change made to the indices will be discarded.

indicesOf :: Gettable f => Overloaded (Index i) f s t a a -> LensLike f s t i jSource

Transform an indexed fold into a fold of the indices.

 indicesOf :: IndexedFold i s a             -> Fold s i
 indicesOf :: SimpleIndexedLens i s a      -> Getter s i
 indicesOf :: SimpleIndexedTraversal i s a -> Fold s i

Building Indexed Folds

ifiltering :: (Applicative f, Indexed i k) => (i -> a -> Bool) -> Index i (a -> f a) (s -> f t) -> k (a -> f a) (s -> f t)Source

Obtain an IndexedFold by filtering an IndexedLens, IndexedGetter, or IndexedFold.

When passed an IndexedTraversal, sadly the result is not a legal IndexedTraversal.

See filtered for a related counter-example.

ibackwards :: Indexed i k => Index i (a -> Backwards f b) (s -> Backwards f t) -> k (a -> f b) (s -> f t)Source

Reverse the order of the elements of an IndexedFold or IndexedTraversal. This has no effect on an IndexedLens, IndexedGetter, or IndexedSetter.

itakingWhile :: (Gettable f, Applicative f, Indexed i k) => (i -> a -> Bool) -> IndexedGetting i (Endo (f s)) s s a a -> k (a -> f a) (s -> f s)Source

Obtain an IndexedFold by taking elements from another IndexedFold, IndexedLens, IndexedGetter or IndexedTraversal while a predicate holds.

idroppingWhile :: (Gettable f, Applicative f, Indexed i k) => (i -> a -> Bool) -> IndexedGetting i (Endo (f s, f s)) s s a a -> k (a -> f a) (s -> f s)Source

Obtain an IndexedFold by dropping elements from another IndexedFold, IndexedLens, IndexedGetter or IndexedTraversal while a predicate holds.

isplitting :: (Applicative f, Gettable f, Indexed [i] k) => Splitter (i, a) -> IndexedGetting i [(i, a)] s s a a -> k ([a] -> f [a]) (s -> f s)Source

Obtain an IndexedFold by splitting another IndexedFold, IndexedLens, IndexedGetter or IndexedTraversal according to the given splitting strategy.

 isplitting :: Splitter (i, a) -> IndexedFold i s a -> IndexedFold [i] s [a]

isplittingOn :: (Applicative f, Gettable f, Indexed [i] k, Eq i, Eq a) => [(i, a)] -> IndexedGetting i [(i, a)] s s a a -> k ([a] -> f [a]) (s -> f s)Source

Obtain an IndexedFold by splitting another IndexedFold, IndexedLens, IndexedGetter or IndexedTraversal on the given delimiter.

Equivalent to isplitting . dropDelims . onSublist.

 isplittingOn :: (Eq i, Eq a) => [(i, a)] -> IndexedFold i s a -> IndexedFold [i] s [a]

isplittingOneOf :: (Applicative f, Gettable f, Indexed [i] k, Eq i, Eq a) => [(i, a)] -> IndexedGetting i [(i, a)] s s a a -> k ([a] -> f [a]) (s -> f s)Source

Obtain an IndexedFold by splitting another IndexedFold, IndexedLens, IndexedGetter or IndexedTraversal on any of the given elements.

Equivalent to isplitting . dropDelims . oneOf.

 isplittingOneOf :: (Eq i, Eq a) => [(i, a)] -> IndexedFold i s a -> IndexedFold [i] s [a]

isplittingWhen :: (Applicative f, Gettable f, Indexed [i] k) => (i -> a -> Bool) -> IndexedGetting i [(i, a)] s s a a -> k ([a] -> f [a]) (s -> f s)Source

Obtain an IndexedFold by splitting another IndexedFold, IndexedLens, IndexedGetter or IndexedTraversal on elements satisfying the given predicate.

Equivalent to isplitting . dropDelims . whenElt . uncurry.

 isplittingWhen :: (i -> a -> Bool) -> IndexedFold i s a -> IndexedFold [i] s [a]

iendingBy :: (Applicative f, Gettable f, Indexed [i] k, Eq i, Eq a) => [(i, a)] -> IndexedGetting i [(i, a)] s s a a -> k ([a] -> f [a]) (s -> f s)Source

Obtain an IndexedFold by splitting another IndexedFold, IndexedLens, IndexedGetter or IndexedTraversal into chunks terminated by the given delimiter.

Equivalent to isplitting . dropDelims . onSublist.

 iendingBy :: (Eq i, Eq a) => [(i, a)] -> IndexedFold i s a -> IndexedFold [i] s [a]

iendingByOneOf :: (Applicative f, Gettable f, Indexed [i] k, Eq i, Eq a) => [(i, a)] -> IndexedGetting i [(i, a)] s s a a -> k ([a] -> f [a]) (s -> f s)Source

Obtain an IndexedFold by splitting another IndexedFold, IndexedLens, IndexedGetter or IndexedTraversal into chunks terminated by any of the given elements.

Equivalent to isplitting . dropFinalBlank . dropDelims . oneOf.

 iendingByOneOf :: (Eq i, Eq a) => [(i, a)] -> IndexedFold i s a -> IndexedFold [i] s [a]

iwordingBy :: (Applicative f, Gettable f, Indexed [i] k) => (i -> a -> Bool) -> IndexedGetting i [(i, a)] s s a a -> k ([a] -> f [a]) (s -> f s)Source

Obtain an IndexedFold by splitting another IndexedFold, IndexedLens, IndexedGetter or IndexedTraversal into words, with word boundaries indicated by the given predicate.

Equivalent to isplitting . dropBlanks . dropDelims . whenElt . uncurry.

 iwordingBy :: (i -> a -> Bool) -> IndexedFold i s a -> IndexedFold [i] s [a]

iliningBy :: (Applicative f, Gettable f, Indexed [i] k) => (i -> a -> Bool) -> IndexedGetting i [(i, a)] s s a a -> k ([a] -> f [a]) (s -> f s)Source

Obtain an IndexedFold by splitting another IndexedFold, IndexedLens, IndexedGetter or IndexedTraversal into lines, with line boundaries indicated by the given predicate.

Equivalent to isplitting . dropFinalBlank . dropDelims . whenElt . uncurry.

 iliningBy :: (i -> a -> Bool) -> IndexedFold i s a -> IndexedFold [i] s [a]

ichunkingOfSource

Arguments

:: (Applicative f, Gettable f, Indexed [i] k) 
=> Int
n
-> IndexedGetting i [(i, a)] s s a a 
-> k ([a] -> f [a]) (s -> f s) 

Obtain an IndexedFold by splitting another IndexedFold, IndexedLens, IndexedGetter or IndexedTraversal into length-n pieces.

 ichunkingOf :: Int -> IndexedFold i s a -> IndexedFold [i] s [a]

isplittingPlaces :: (Applicative f, Gettable f, Indexed [i] k, Integral n) => [n] -> IndexedGetting i [(i, a)] s s a a -> k ([a] -> f [a]) (s -> f s)Source

Obtain an IndexedFold by splitting another IndexedFold, IndexedLens, IndexedGetter or IndexedTraversal into chunks of the given lengths.

 isplittingPlaces :: Integral n => [n] -> IndexedFold i s a -> IndexedFold [i] s [a]

isplittingPlacesBlanks :: (Applicative f, Gettable f, Indexed [i] k, Integral n) => [n] -> IndexedGetting i [(i, a)] s s a a -> k ([a] -> f [a]) (s -> f s)Source

Obtain an IndexedFold by splitting another IndexedFold, IndexedLens, IndexedGetter or IndexedTraversal into chunks of the given lengths. Unlike isplittingPlaces, the output IndexedFold will always be the same length as the first input argument.

 isplittingPlacesBlanks :: Integral n => [n] -> IndexedFold i s a -> IndexedFold [i] s [a]

Storing Indexed Folds

newtype ReifiedIndexedFold i s a Source

Useful for storage.

Constructors

ReifyIndexedFold