lens-3.0.6: 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 a b c d = forall f k. (Indexed i k, Functor f) => k (c -> f d) (a -> f b)Source

Every IndexedLens is a valid Lens and a valid IndexedTraversal.

Common Indexed Lenses

class At k m | m -> k whereSource

Provides an IndexedLens that can be used to read, write or delete the value associated with a key in a map-like container.

Methods

at :: k -> SimpleIndexedLens k (m v) (Maybe v)Source

>>> Map.fromList [(1,"hello")] ^.at 1
Just "hello"
>>> at 1 ?~ "hello" $ Map.empty
fromList [(1,"hello")]

Instances

At Int IntMap 
(Eq k, Hashable k) => At k (HashMap k) 
Ord k => At k (Map k) 

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) 

Indexed Lens Combinators

(%%@~) :: Overloaded (Index i) f a b c d -> (i -> c -> f d) -> a -> f bSource

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 a b c d      -> (i -> c -> f d) -> a -> f b
 (%%@~) :: Functor f => IndexedTraversal i a b c d -> (i -> c -> f d) -> a -> f b

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

 (%%@~) ::             IndexedLens i a b c d      -> (i -> c -> (e, d)) -> a -> (e, b)
 (%%@~) :: Monoid e => IndexedTraversal i a b c d -> (i -> c -> (e, d)) -> a -> (e, b)

(<%@~) :: Overloaded (Index i) ((,) d) a b c d -> (i -> c -> d) -> a -> (d, b)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 a b c d -> (i -> c -> d) -> a -> (d, b)
 (<%@~) :: Monoid d => IndexedTraversal i a b c d -> (i -> c -> d) -> a -> (d, b)

(%%@=) :: MonadState a m => Overloaded (Index i) ((,) e) a a c d -> (i -> c -> (e, d)) -> m eSource

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 a m                IndexedLens i a a c d      -> (i -> c -> (e, d)) -> a -> m e
 (%%@=) :: (MonadState a m, Monoid e) => IndexedTraversal i a a c d -> (i -> c -> (e, d)) -> a -> m e

(<%@=) :: MonadState a m => Overloaded (Index i) ((,) d) a a c d -> (i -> c -> d) -> m dSource

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 a m                IndexedLens i a a c d      -> (i -> c -> d) -> a -> m d
 (<%@=) :: (MonadState a m, Monoid e) => IndexedTraversal i a a c d -> (i -> c -> d) -> a -> m d

Storing Indexed Lenses

newtype ReifiedIndexedLens i a b c d Source

Useful for storage.

Constructors

ReifyIndexedLens 

Fields

reflectIndexedLens :: IndexedLens i a b c d
 

Simple