lens-3.9.0.3: Lenses, Folds and Traversals

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

Control.Lens.Indexed

Contents

Description

(The classes in here need to be defined together for DefaultSignatures to work.)

Synopsis

Indexing

class Conjoined p => Indexable i p whereSource

This class permits overloading of function application for things that also admit a notion of a key or index.

Methods

indexed :: p a b -> i -> a -> bSource

Build a function from an indexed function.

Instances

Indexable i (->) 
~ * i j => Indexable i (Indexed j) 

class (Choice p, Corepresentable p, Comonad (Corep p), Traversable (Corep p), Strong p, Representable p, Monad (Rep p), MonadFix (Rep p), Distributive (Rep p), ArrowLoop p, ArrowApply p, ArrowChoice p) => Conjoined p whereSource

This is a Profunctor that is both Corepresentable by f and Representable by g such that f is left adjoint to g. From this you can derive a lot of structure due to the preservation of limits and colimits.

Methods

distrib :: Functor f => p a b -> p (f a) (f b)Source

Conjoined is strong enough to let us distribute every Conjoined Profunctor over every Haskell Functor. This is effectively a generalization of fmap.

conjoined :: (p ~ (->) => q (a -> b) r) -> q (p a b) r -> q (p a b) rSource

This permits us to make a decision at an outermost point about whether or not we use an index.

Ideally any use of this function should be done in such a way so that you compute the same answer, but this cannot be enforced at the type level.

Instances

newtype Indexed i a b Source

A function with access to a index. This constructor may be useful when you need to store an Indexable in a container to avoid ImpredicativeTypes.

index :: Indexed i a b -> i -> a -> b

Constructors

Indexed 

Fields

runIndexed :: i -> a -> b
 

(<.) :: Indexable i p => (Indexed i s t -> r) -> ((a -> b) -> s -> t) -> p a b -> rSource

Compose an Indexed function with a non-indexed function.

Mnemonically, the < points to the indexing we want to preserve.

(<.>) :: Indexable (i, j) p => (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> p a b -> rSource

Composition of Indexed functions.

Mnemonically, the < and > points to the fact that we want to preserve the indices.

(.>) :: (st -> r) -> (kab -> st) -> kab -> rSource

Compose a non-indexed function with an Indexed function.

Mnemonically, the > points to the indexing we want to preserve.

This is the same as (.).

f . g (and f .> g) gives you the index of g unless g is index-preserving, like a Prism, Iso or Equality, in which case it'll pass through the index of f.

reindexed :: Indexable j p => (i -> j) -> (Indexed i a b -> r) -> p a b -> rSource

Remap the index.

icompose :: Indexable p c => (i -> j -> p) -> (Indexed i s t -> r) -> (Indexed j a b -> s -> t) -> c a b -> rSource

Composition of Indexed functions with a user supplied function for combining indices.

indexing :: Indexable Int p => ((a -> Indexing f b) -> s -> Indexing f t) -> p a (f b) -> s -> f tSource

Transform a Traversal into an IndexedTraversal or a Fold into an IndexedFold, etc.

 indexing :: Traversal s t a b -> IndexedTraversal Int s t a b
 indexing :: Prism s t a b     -> IndexedTraversal Int s t a b
 indexing :: Lens s t a b      -> IndexedLens Int  s t a b
 indexing :: Iso s t a b       -> IndexedLens Int s t a b
 indexing :: Fold s a          -> IndexedFold Int s a
 indexing :: Getter s a        -> IndexedGetter Int s a
indexing :: Indexable Int p => LensLike (Indexing f) s t a b -> Overloading p (->) f s t a b

indexing64 :: Indexable Int64 p => ((a -> Indexing64 f b) -> s -> Indexing64 f t) -> p a (f b) -> s -> f tSource

Transform a Traversal into an IndexedTraversal or a Fold into an IndexedFold, etc.

This combinator is like indexing except that it handles large traversals and folds gracefully.

 indexing64 :: Traversal s t a b -> IndexedTraversal Int64 s t a b
 indexing64 :: Prism s t a b     -> IndexedTraversal Int64 s t a b
 indexing64 :: Lens s t a b      -> IndexedLens Int64 s t a b
 indexing64 :: Iso s t a b       -> IndexedLens Int64 s t a b
 indexing64 :: Fold s a          -> IndexedFold Int64 s a
 indexing64 :: Getter s a        -> IndexedGetter Int64 s a
indexing64 :: Indexable Int64 p => LensLike (Indexing64 f) s t a b -> Overloading p (->) f s t a b

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.

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

ifolded :: IndexedFold i (f a) aSource

The IndexedFold of a FoldableWithIndex container.

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

ifolding :: FoldableWithIndex i f => (s -> f a) -> IndexedFold i s aSource

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

This can be useful to lift operations from 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.

 anyiany . 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

withIndex :: (Indexable i p, Functor f) => Overloading p (Indexed i) f s t (i, s) (j, t)Source

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

The result is only valid to compose in a Traversal, if you don't edit the index as edits to the index have no effect.

asIndex :: (Indexable i p, Contravariant f, Functor f) => Overloading' p (Indexed i) f s iSource

When composed with an IndexedFold or IndexedTraversal this yields an (Indexed) Fold of the indices.

Restricting by Index

indices :: (Indexable i p, Applicative f) => (i -> Bool) -> Overloading' p (Indexed i) f a aSource

This allows you to filter an IndexedFold, IndexedGetter, IndexedTraversal or IndexedLens based on a predicate on the indices.

>>> ["hello","the","world","!!!"]^..traversed.indices even
["hello","world"]
>>> over (traversed.indices (>0)) Prelude.reverse $ ["He","was","stressed","o_O"]
["He","saw","desserts","O_o"]

index :: (Indexable i p, Eq i, Applicative f) => i -> Overloading' p (Indexed i) f a aSource

This allows you to filter an IndexedFold, IndexedGetter, IndexedTraversal or IndexedLens based on an index.

>>> ["hello","the","world","!!!"]^?traversed.index 2
Just "world"

Indexed Traversables

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