Portability | rank 2 types, MPTCs, TFs, flexible |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
- type IndexedTraversal i s t a b = forall f k. (Indexable i k, Applicative f) => k (a -> f b) (s -> f t)
- iwhereOf :: (Indexable i k, Applicative f) => Overloaded (Indexed i) f s t a a -> (i -> Bool) -> Overloaded k f s t a a
- value :: (k -> Bool) -> SimpleIndexedTraversal k (k, v) v
- ignored :: forall k f i s a b. (Indexable i k, Applicative f) => Overloaded k f s s a b
- class At k m | m -> k where
- at :: k -> SimpleIndexedLens k (m v) (Maybe v)
- _at :: k -> SimpleIndexedTraversal k (m v) v
- class Ord k => TraverseMin k m | m -> k where
- traverseMin :: SimpleIndexedTraversal k (m v) v
- class Ord k => TraverseMax k m | m -> k where
- traverseMax :: SimpleIndexedTraversal k (m v) v
- traversed :: Traversable f => IndexedTraversal Int (f a) (f b) a b
- traversed64 :: Traversable f => IndexedTraversal Int64 (f a) (f b) a b
- elementOf :: (Applicative f, Indexable Int k) => LensLike (Indexing f) s t a a -> Int -> Overloaded k f s t a a
- element :: Traversable t => Int -> SimpleIndexedTraversal Int (t a) a
- elementsOf :: (Applicative f, Indexable Int k) => LensLike (Indexing f) s t a a -> (Int -> Bool) -> Overloaded k f s t a a
- elements :: Traversable t => (Int -> Bool) -> SimpleIndexedTraversal Int (t a) a
- itraverseOf :: Overloaded (Indexed i) f s t a b -> (i -> a -> f b) -> s -> f t
- iforOf :: Overloaded (Indexed i) f s t a b -> s -> (i -> a -> f b) -> f t
- imapMOf :: Overloaded (Indexed i) (WrappedMonad m) s t a b -> (i -> a -> m b) -> s -> m t
- iforMOf :: Overloaded (Indexed i) (WrappedMonad m) s t a b -> s -> (i -> a -> m b) -> m t
- imapAccumROf :: Overloaded (Indexed i) (State s) s t a b -> (i -> s -> a -> (s, b)) -> s -> s -> (s, t)
- imapAccumLOf :: Overloaded (Indexed i) (Backwards (State s)) s t a b -> (i -> s -> a -> (s, b)) -> s -> s -> (s, t)
- newtype ReifiedIndexedTraversal i s t a b = ReifyIndexedTraversal {
- reflectIndexedTraversal :: IndexedTraversal i s t a b
- type SimpleIndexedTraversal i s a = IndexedTraversal i s s a a
- type SimpleReifiedIndexedTraversal i s a = ReifiedIndexedTraversal i s s a a
Indexed Traversals
type IndexedTraversal i s t a b = forall f k. (Indexable i k, Applicative f) => k (a -> f b) (s -> f t)Source
Every indexed traversal is a valid Traversal
or
IndexedFold
.
The Indexed
constraint is used to allow an IndexedTraversal
to be used
directly as a Traversal
.
The Traversal
laws are still required to hold.
Common Indexed Traversals
iwhereOf :: (Indexable i k, Applicative f) => Overloaded (Indexed i) f s t a a -> (i -> Bool) -> Overloaded k f s t a aSource
Access the element of an IndexedTraversal
where the index matches a predicate.
>>>
over (iwhereOf traversed (>0)) reverse ["He","was","stressed","o_O"]
["He","saw","desserts","O_o"]
iwhereOf
::IndexedFold
i s a -> (i ->Bool
) ->IndexedFold
i s aiwhereOf
::IndexedGetter
i s a -> (i ->Bool
) ->IndexedFold
i s aiwhereOf
::SimpleIndexedLens
i s a -> (i ->Bool
) ->SimpleIndexedTraversal
i s aiwhereOf
::SimpleIndexedTraversal
i s a -> (i ->Bool
) ->SimpleIndexedTraversal
i s aiwhereOf
::SimpleIndexedSetter
i s a -> (i ->Bool
) ->SimpleIndexedSetter
i s a
value :: (k -> Bool) -> SimpleIndexedTraversal k (k, v) vSource
This provides a Traversal
that checks a predicate on a key before
allowing you to traverse into a value.
ignored :: forall k f i s a b. (Indexable i k, Applicative f) => Overloaded k f s s a bSource
class At k m | m -> k whereSource
At
provides a lens that can be used to read,
write or delete the value associated with a key in a map-like
container on an ad hoc basis.
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")]
Note: Map
-like containers form a reasonable instance, but not Array
-like ones, where
you cannot satisfy the Lens
laws.
_at :: k -> SimpleIndexedTraversal k (m v) vSource
class Ord k => TraverseMin k m | m -> k whereSource
Allows IndexedTraversal
the value at the smallest index.
traverseMin :: SimpleIndexedTraversal k (m v) vSource
IndexedTraversal
of the element with the smallest index.
TraverseMin Int IntMap | |
Ord k => TraverseMin k (Map k) |
class Ord k => TraverseMax k m | m -> k whereSource
Allows IndexedTraversal
of the value at the largest index.
traverseMax :: SimpleIndexedTraversal k (m v) vSource
IndexedTraversal
of the element at the largest index.
TraverseMax Int IntMap | |
Ord k => TraverseMax k (Map k) |
traversed :: Traversable f => IndexedTraversal Int (f a) (f b) a bSource
Traverse any Traversable
container. This is an IndexedTraversal
that is indexed by ordinal position.
traversed64 :: Traversable f => IndexedTraversal Int64 (f a) (f b) a bSource
Traverse any Traversable
container. This is an IndexedTraversal
that is indexed by ordinal position.
elementOf :: (Applicative f, Indexable Int k) => LensLike (Indexing f) s t a a -> Int -> Overloaded k f s t a aSource
Traverse the nth element elementOf
a Traversal
, Lens
or
Iso
if it exists.
>>>
[[1],[3,4]] & elementOf (traverse.traverse) 1 .~ 5
[[1],[5,4]]
>>>
[[1],[3,4]] ^? elementOf (folded.folded) 1
Just 3
>>>
[0..] ^?! elementOf folded 5
5
>>>
take 10 $ elementOf traverse 3 .~ 16 $ [0..]
[0,1,2,16,4,5,6,7,8,9]
elementOf
::Simple
Traversal
s a -> Int ->SimpleIndexedTraversal
Int
s aelementOf
::Fold
s a -> Int ->IndexedFold
Int
s a
element :: Traversable t => Int -> SimpleIndexedTraversal Int (t a) aSource
Traverse the nth element of a Traversable
container.
element
≡elementOf
traverse
elementsOf :: (Applicative f, Indexable Int k) => LensLike (Indexing f) s t a a -> (Int -> Bool) -> Overloaded k f s t a aSource
Traverse (or fold) selected elements of a Traversal
(or Fold
) where their ordinal positions match a predicate.
elementsOf
::Simple
Traversal
s a -> (Int
->Bool
) ->SimpleIndexedTraversal
Int
s aelementsOf
::Fold
s a -> (Int
->Bool
) ->IndexedFold
Int
s a
elements :: Traversable t => (Int -> Bool) -> SimpleIndexedTraversal Int (t a) aSource
Traverse elements of a Traversable
container where their ordinal positions matches a predicate.
elements
≡elementsOf
traverse
Indexed Traversal Combinators
itraverseOf :: Overloaded (Indexed i) f s t a b -> (i -> a -> f b) -> s -> f tSource
Traversal with an index.
NB: When you don't need access to the index then you can just apply your IndexedTraversal
directly as a function!
itraverseOf
≡withIndex
traverseOf
l =itraverseOf
l.
const
=id
itraverseOf
::IndexedLens
i s t a b -> (i -> a -> f b) -> s -> f titraverseOf
::IndexedTraversal
i s t a b -> (i -> a -> f b) -> s -> f t
iforOf :: Overloaded (Indexed i) f s t a b -> s -> (i -> a -> f b) -> f tSource
Traverse with an index (and the arguments flipped)
forOf
l a ≡iforOf
l a.
const
iforOf
≡flip
.itraverseOf
iforOf
::IndexedLens
i s t a b -> s -> (i -> a -> f b) -> f tiforOf
::IndexedTraversal
i s t a b -> s -> (i -> a -> f b) -> f t
imapMOf :: Overloaded (Indexed i) (WrappedMonad m) s t a b -> (i -> a -> m b) -> s -> m tSource
Map each element of a structure targeted by a lens to a monadic action, evaluate these actions from left to right, and collect the results, with access its position.
When you don't need access to the index mapMOf
is more liberal in what it can accept.
mapMOf
l ≡imapMOf
l.
const
imapMOf
::Monad
m =>IndexedLens
i s t a b -> (i -> a -> m b) -> s -> m timapMOf
::Monad
m =>IndexedTraversal
i s t a b -> (i -> a -> m b) -> s -> m t
iforMOf :: Overloaded (Indexed i) (WrappedMonad m) s t a b -> s -> (i -> a -> m b) -> m tSource
Map each element of a structure targeted by a lens to a monadic action, evaluate these actions from left to right, and collect the results, with access its position (and the arguments flipped).
forMOf
l a ≡iforMOf
l a.
const
iforMOf
≡flip
.
imapMOf
iforMOf
::Monad
m =>IndexedLens
i s t a b -> s -> (i -> a -> m b) -> m tiforMOf
::Monad
m =>IndexedTraversal
i s t a b -> s -> (i -> a -> m b) -> m t
imapAccumROf :: Overloaded (Indexed i) (State s) s t a b -> (i -> s -> a -> (s, b)) -> s -> s -> (s, t)Source
Generalizes mapAccumR
to an arbitrary IndexedTraversal
with access to the index.
imapAccumROf
accumulates state from right to left.
mapAccumROf
l ≡imapAccumROf
l.
const
imapAccumROf
::IndexedLens
i s t a b -> (i -> s -> a -> (s, b)) -> s -> s -> (s, t)imapAccumROf
::IndexedTraversal
i s t a b -> (i -> s -> a -> (s, b)) -> s -> s -> (s, t)
imapAccumLOf :: Overloaded (Indexed i) (Backwards (State s)) s t a b -> (i -> s -> a -> (s, b)) -> s -> s -> (s, t)Source
Generalizes mapAccumL
to an arbitrary IndexedTraversal
with access to the index.
imapAccumLOf
accumulates state from left to right.
mapAccumLOf
l ≡imapAccumLOf
l.
const
imapAccumLOf
::IndexedLens
i s t a b -> (i -> s -> a -> (s, b)) -> s -> s -> (s, t)imapAccumLOf
::IndexedTraversal
i s t a b -> (i -> s -> a -> (s, b)) -> s -> s -> (s, t)
Storing Indexed Traversals
newtype ReifiedIndexedTraversal i s t a b Source
Useful for storage.
ReifyIndexedTraversal | |
|
Simple
type SimpleIndexedTraversal i s a = IndexedTraversal i s s a aSource
typeSimpleIndexedTraversal
i =Simple
(IndexedTraversal
i)
type SimpleReifiedIndexedTraversal i s a = ReifiedIndexedTraversal i s s a aSource
typeSimpleIndexedTraversal
i =Simple
(ReifiedIndexedTraversal
i)