| Portability | Rank2Types | 
|---|---|
| Stability | provisional | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Safe Haskell | Safe-Infered | 
Control.Lens.Traversal
Description
A Traversal a b c dtraverse from
 Traversable. It allows you to traverse over a structure and change out
 its contents with monadic or applicative side-effects. Starting from
traverse :: (Traversable t, Applicative f) => (c -> f d) -> t c -> f (t d)
we monomorphize the contents and result to obtain
type Traversal a b c d = forall f. Applicative f => (c -> f d) -> a -> f b
While a Traversal isn't quite a Fold, it _can_ be used for Getting
 like a Fold, because given a Monoid m, we have an Applicative
 for (. Everything you know how to do with a Const m)Traversable
 container, you can with with a Traversal, and here we provide
 combinators that generalize the usual Traversable operations.
- type Traversal a b c d = forall f. Applicative f => (c -> f d) -> a -> f b
- element :: Traversable t => Int -> Simple Lens (t a) a
- elementOf :: Functor f => LensLike (ElementOf f) a b c c -> Int -> LensLike f a b c c
- traverseOf :: LensLike f a b c d -> (c -> f d) -> a -> f b
- forOf :: LensLike f a b c d -> a -> (c -> f d) -> f b
- sequenceAOf :: LensLike f a b (f c) c -> a -> f b
- mapMOf :: LensLike (WrappedMonad m) a b c d -> (c -> m d) -> a -> m b
- forMOf :: LensLike (WrappedMonad m) a b c d -> a -> (c -> m d) -> m b
- sequenceOf :: LensLike (WrappedMonad m) a b (m c) c -> a -> m b
- transposeOf :: LensLike ZipList a b [c] c -> a -> [b]
- mapAccumLOf :: LensLike (Backwards (State s)) a b c d -> (s -> c -> (s, d)) -> s -> a -> (s, b)
- mapAccumROf :: LensLike (State s) a b c d -> (s -> c -> (s, d)) -> s -> a -> (s, b)
- scanr1Of :: LensLike (State (Maybe c)) a b c c -> (c -> c -> c) -> a -> b
- scanl1Of :: LensLike (Backwards (State (Maybe c))) a b c c -> (c -> c -> c) -> a -> b
- class (Functor t, Foldable t) => Traversable t  where- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
 
- traverseNothing :: Traversal a a c d
- type SimpleTraversal a b = Traversal a a b b
Lenses
type Traversal a b c d = forall f. Applicative f => (c -> f d) -> a -> f bSource
A Traversal can be used directly as a Setter or a Fold (but not as a Lens) and provides
 the ability to both read and update multiple fields, subject to some relatively weak Traversal laws.
These have also been known as multilenses, but they have the signature and spirit of
traverse::Traversablef =>Traversal(f a) (f b) a b
and the more evocative name suggests their application.
Most of the time the Traversal you will want to use is just traverse, but you can also pass any
 Lens or Iso as a Traversal, and composition of a Traversal (or Lens or Iso) with a Traversal (or Lens or Iso)
 using (.) forms a valid Traversal.
The laws for a Traversal t follow from the laws for Traversable as stated in "The Essence of the Iterator Pattern".
1) Idiomatic naturality:
tpure=pure
2) Sequential composition:
fmap(t f) . t g =getCompose. t (Compose.fmapf . g)
One consequence of this requirement is that a traversal needs to leave the same number of elements as a candidate for subsequent traversal as it started with.
3) No duplication of elements (as defined in "The Essence of the Iterator Pattern" section 5.5), which states that you should incur no effect caused by visiting the same element of the container twice.
Lensing Traversals
element :: Traversable t => Int -> Simple Lens (t a) aSource
Access the nth element of a Traversable container.
Attempts to access beyond the range of the Traversal will cause an error.
element=elementOftraverse
Traversing and Lensing
traverseOf :: LensLike f a b c d -> (c -> f d) -> a -> f bSource
Map each element of a structure targeted by a Lens or Traversal, evaluate these actions from left to right, and collect the results.
traverseOf=id
traverse=traverseOftraverse
traverseOf::Isoa b c d -> (c -> f d) -> a -> f btraverseOf::Lensa b c d -> (c -> f d) -> a -> f btraverseOf::Traversala b c d -> (c -> f d) -> a -> f b
sequenceAOf :: LensLike f a b (f c) c -> a -> f bSource
Evaluate each action in the structure from left to right, and collect the results.
sequenceA=sequenceAOftraverse=traverseidsequenceAOfl =traverseOfl idsequenceAOfl = l id
sequenceAOf::Isoa b (f c) c -> a -> f bsequenceAOf::Lensa b (f c) c -> a -> f bsequenceAOf::Applicativef =>Traversala b (f c) c -> a -> f b
mapMOf :: LensLike (WrappedMonad m) a b c d -> (c -> m d) -> a -> m bSource
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.
mapM=mapMOftraverse
'mapMOf ::Isoa b c d -> (c -> m d) -> a -> m b 'mapMOf ::Lensa b c d -> (c -> m d) -> a -> m b 'mapMOf ::Monadm =>Traversala b c d -> (c -> m d) -> a -> m b
forMOf :: LensLike (WrappedMonad m) a b c d -> a -> (c -> m d) -> m bSource
sequenceOf :: LensLike (WrappedMonad m) a b (m c) c -> a -> m bSource
sequence=sequenceOftraversesequenceOf l =mapMOfl id sequenceOf l =unwrapMonad. lWrapMonad
sequenceOf ::Isoa b (m c) c -> a -> m b sequenceOf ::Lensa b (m c) c -> a -> m b sequenceOf ::Monadm =>Traversala b (m c) c -> a -> m b
transposeOf :: LensLike ZipList a b [c] c -> a -> [b]Source
This generalizes transpose to an arbitrary Traversal.
Note: transpose handles ragged inputs more intelligently, but for non-ragged inputs:
transpose=transposeOftraverse
>>>transposeOf traverse [[1,2,3],[4,5,6]][[1,4],[2,5],[3,6]]
Since every Lens is a Traversal, we can use this as a form of
 monadic strength as well:
transposeOf_2:: (b, [a]) -> [(b, a)]
mapAccumLOf :: LensLike (Backwards (State s)) a b c d -> (s -> c -> (s, d)) -> s -> a -> (s, b)Source
Generalized mapAccumL to an arbitrary Traversal.
mapAccumL=mapAccumLOftraverse
mapAccumLOf accumulates state from left to right.
mapAccumLOf ::Isoa b c d -> (s -> c -> (s, d)) -> s -> a -> (s, b) mapAccumLOf ::Lensa b c d -> (s -> c -> (s, d)) -> s -> a -> (s, b) mapAccumLOf ::Traversala b c d -> (s -> c -> (s, d)) -> s -> a -> (s, b)
mapAccumROf :: LensLike (State s) a b c d -> (s -> c -> (s, d)) -> s -> a -> (s, b)Source
Generalizes mapAccumR to an arbitrary Traversal.
mapAccumR=mapAccumROftraverse
mapAccumROf accumulates state from right to left.
mapAccumROf ::Isoa b c d -> (s -> c -> (s, d)) -> s -> a -> (s, b) mapAccumROf ::Lensa b c d -> (s -> c -> (s, d)) -> s -> a -> (s, b) mapAccumROf ::Traversala b c d -> (s -> c -> (s, d)) -> s -> a -> (s, b)
Common Traversals
class (Functor t, Foldable t) => Traversable t where
Functors representing data structures that can be traversed from left to right.
Minimal complete definition: traverse or sequenceA.
Instances are similar to Functor, e.g. given a data type
data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
a suitable instance would be
 instance Traversable Tree where
    traverse f Empty = pure Empty
    traverse f (Leaf x) = Leaf <$> f x
    traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
This is suitable even for abstract types, as the laws for <*>
 imply a form of associativity.
The superclass instances should satisfy the following:
-  In the Functorinstance,fmapshould be equivalent to traversal with the identity applicative functor (fmapDefault).
-  In the Foldableinstance,foldMapshould be equivalent to traversal with a constant applicative functor (foldMapDefault).
Methods
traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
Map each element of a structure to an action, evaluate these actions from left to right, and collect the results.
Instances
| Traversable [] | |
| Traversable Maybe | |
| Traversable Tree | |
| Traversable Seq | |
| Traversable ViewL | |
| Traversable ViewR | |
| Traversable IntMap | |
| Traversable Identity | |
| Traversable Node | |
| Traversable Digit | |
| Traversable FingerTree | |
| Traversable Elem | |
| Ix i => Traversable (Array i) | |
| Traversable (Map k) | |
| Traversable f => Traversable (ListT f) | |
| Traversable f => Traversable (Backwards f) | Derived instance. | 
| Traversable f => Traversable (MaybeT f) | |
| Traversable f => Traversable (IdentityT f) | |
| Traversable f => Traversable (ErrorT e f) | |
| Traversable f => Traversable (WriterT w f) | |
| Traversable f => Traversable (WriterT w f) | |
| (Traversable f, Traversable g) => Traversable (Compose f g) | 
traverseNothing :: Traversal a a c dSource
This is the traversal that just doesn't return anything
traverseNothing::Applicativef => (c -> f d) -> a -> f a
Simple
type SimpleTraversal a b = Traversal a a b bSource