Portability | rank 2 types, MPTCs, TFs, flexible |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
- type IndexedLens i s t a b = forall f k. (Indexed i k, Functor f) => k (a -> f b) (s -> f t)
- class At k m | m -> k where
- at :: k -> SimpleIndexedLens k (m v) (Maybe v)
- class Contains k m | m -> k where
- contains :: k -> SimpleIndexedLens k m Bool
- resultAt :: Eq e => e -> SimpleIndexedLens e (e -> a) a
- (%%@~) :: Overloaded (Index i) f s t a b -> (i -> a -> f b) -> s -> f t
- (<%@~) :: Overloaded (Index i) ((,) b) s t a b -> (i -> a -> b) -> s -> (b, t)
- (%%@=) :: MonadState s m => Overloaded (Index i) ((,) r) s s a b -> (i -> a -> (r, b)) -> m r
- (<%@=) :: MonadState s m => Overloaded (Index i) ((,) b) s s a b -> (i -> a -> b) -> m b
- newtype ReifiedIndexedLens i s t a b = ReifyIndexedLens {
- reflectIndexedLens :: IndexedLens i s t a b
- type SimpleIndexedLens i s a = IndexedLens i s s a a
- type SimpleReifiedIndexedLens i s a = ReifiedIndexedLens i s s a a
Indexed Lenses
type IndexedLens i s t a b = forall f k. (Indexed i k, Functor f) => k (a -> f b) (s -> f t)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.
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")]
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
contains :: k -> SimpleIndexedLens k m BoolSource
>>>
contains 3 .~ False $ IntSet.fromList [1,2,3,4]
fromList [1,2,4]
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)
Indexed Lens Combinators
(%%@~) :: Overloaded (Index 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 (Index 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 (Index 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 mIndexedLens
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 (Index 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 mIndexedLens
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.
ReifyIndexedLens | |
|
Simple
type SimpleIndexedLens i s a = IndexedLens i s s a aSource
typeSimpleIndexedLens
i =Simple
(IndexedLens
i)
type SimpleReifiedIndexedLens i s a = ReifiedIndexedLens i s s a aSource
typeSimpleIndexedLens
i =Simple
(ReifiedIndexedLens
i)