lens-3.7.4: Lenses, Folds and Traversals

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

Control.Lens.IndexedLens

Contents

Description

 

Synopsis

Indexed Lenses

type IndexedLens i s t a b = forall f k. (Indexable i k, Functor f) => k (a -> f b) (s -> f t)Source

Every IndexedLens is a valid Lens and a valid IndexedTraversal.

Indexed Lens Combinators

(%%@~) :: Overloaded (Indexed i) f s t a b -> (i -> a -> f b) -> s -> f tSource

Adjust the target of an IndexedLens returning a supplementary result, or adjust all of the targets of an IndexedTraversal and return a monoidal summary of the supplementary results and the answer.

(%%@~) ≡ withIndex
 (%%@~) :: Functor f => IndexedLens i s t a b      -> (i -> a -> f b) -> s -> f t
 (%%@~) :: Functor f => IndexedTraversal i s t a b -> (i -> a -> f b) -> s -> f t

In particular, it is often useful to think of this function as having one of these even more restrictive type signatures

 (%%@~) ::             IndexedLens i s t a b      -> (i -> a -> (r, b)) -> s -> (r, t)
 (%%@~) :: Monoid r => IndexedTraversal i s t a b -> (i -> a -> (r, b)) -> s -> (r, t)

(<%@~) :: Overloaded (Indexed i) ((,) b) s t a b -> (i -> a -> b) -> s -> (b, t)Source

Adjust the target of an IndexedLens returning the intermediate result, or adjust all of the targets of an IndexedTraversal and return a monoidal summary along with the answer.

l <%~ f ≡ l <%@~ const f

When you do not need access to the index then (<%~) is more liberal in what it can accept.

If you do not need the intermediate result, you can use (%@~) or even (%~).

 (<%@~) ::             IndexedLens i s t a b -> (i -> a -> b) -> s -> (b, t)
 (<%@~) :: Monoid b => IndexedTraversal i s t a b -> (i -> a -> b) -> s -> (b, t)

(%%@=) :: MonadState s m => Overloaded (Indexed i) ((,) r) s s a b -> (i -> a -> (r, b)) -> m rSource

Adjust the target of an IndexedLens returning a supplementary result, or adjust all of the targets of an IndexedTraversal within the current state, and return a monoidal summary of the supplementary results.

l %%@= f ≡ state (l %%@~ f)
 (%%@=) :: MonadState s m                IndexedLens i s s a b      -> (i -> a -> (r, b)) -> s -> m r
 (%%@=) :: (MonadState s m, Monoid r) => IndexedTraversal i s s a b -> (i -> a -> (r, b)) -> s -> m r

(<%@=) :: MonadState s m => Overloaded (Indexed i) ((,) b) s s a b -> (i -> a -> b) -> m bSource

Adjust the target of an IndexedLens returning the intermediate result, or adjust all of the targets of an IndexedTraversal within the current state, and return a monoidal summary of the intermediate results.

 (<%@=) :: MonadState s m                IndexedLens i s s a b      -> (i -> a -> b) -> m b
 (<%@=) :: (MonadState s m, Monoid b) => IndexedTraversal i s s a b -> (i -> a -> b) -> m b

Storing Indexed Lenses

newtype ReifiedIndexedLens i s t a b Source

Useful for storage.

Constructors

ReifyIndexedLens 

Fields

reflectIndexedLens :: IndexedLens i s t a b
 

Common Indexed Lenses

class Contains k m | m -> k whereSource

Provides an IndexedLens that can be used to read, write or delete a member of a set-like container

Methods

contains :: k -> SimpleIndexedLens k m BoolSource

>>> contains 3 .~ False $ IntSet.fromList [1,2,3,4]
fromList [1,2,4]

Instances

Contains Int IntSet 
(Eq k, Hashable k) => Contains k (HashSet k) 
Ord k => Contains k (Set k) 

resultAt :: Eq e => e -> SimpleIndexedLens e (e -> a) aSource

This lens can be used to change the result of a function but only where the arguments match the key given.

>>> let f = (+1) & resultAt 3 .~ 8 in (f 2, f 3)
(3,8)

Simple