lens-2.6: Lenses, Folds and Traversals

PortabilityRank2Types
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe-Infered

Control.Lens.Traversal

Contents

Description

A Traversal a b c d is a generalization of traverse 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 (Const m). Everything you know how to do with a Traversable container, you can with with a Traversal, and here we provide combinators that generalize the usual Traversable operations.

Synopsis

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 :: Traversable f => 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".

 t pure = pure
 fmap (t f) . t g = getCompose . t (Compose . fmap f . g)

One consequence of this requirement is that a Traversal needs to leave the same number of elements as a candidate for subsequent Traversal that it started with. Another testament to the strength of these laws is that the caveat expressed in section 5.5 of the "Essence of the Iterator Pattern" about exotic Traversable instances that traverse the same entry multiple times was actually already ruled out by the second law in that same paper!

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 = elementOf traverse

elementOf :: Functor f => LensLike (ElementOf f) a b c c -> Int -> LensLike f a b c cSource

A Lens to 'Control.Lens.Getter.view'/'Control.Lens.Setter.set' the nth element elementOf a Traversal, Lens or Iso.

Attempts to access beyond the range of the Traversal will cause an error.

>>> import Control.Lens
>>> [[1],[3,4]]^.elementOf (traverse.traverse) 1
3

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 = traverseOf traverse
 traverseOf :: Iso a b c d       -> (c -> f d) -> a -> f b
 traverseOf :: Lens a b c d      -> (c -> f d) -> a -> f b
 traverseOf :: Traversal a b c d -> (c -> f d) -> a -> f b

forOf :: LensLike f a b c d -> a -> (c -> f d) -> f bSource

forOf l = flip (traverseOf l)
 for = forOf traverse
 forOf = flip
 forOf :: Iso a b c d -> a -> (c -> f d) -> f b
 forOf :: Lens a b c d -> a -> (c -> f d) -> f b
 forOf :: Traversal a b c d -> a -> (c -> f d) -> 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 = sequenceAOf traverse = traverse id
 sequenceAOf l = traverseOf l id
 sequenceAOf l = l id
 sequenceAOf ::                  Iso a b (f c) c       -> a -> f b
 sequenceAOf ::                  Lens a b (f c) c      -> a -> f b
 sequenceAOf :: Applicative f => Traversal a 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 = mapMOf traverse
 mapMOf ::            Iso a b c d       -> (c -> m d) -> a -> m b
 mapMOf ::            Lens a b c d      -> (c -> m d) -> a -> m b
 mapMOf :: Monad m => Traversal a b c d -> (c -> m d) -> a -> m b

forMOf :: LensLike (WrappedMonad m) a b c d -> a -> (c -> m d) -> m bSource

 forM = forMOf traverse
 forMOf l = flip (mapMOf l)
 forMOf ::            Iso a b c d       -> a -> (c -> m d) -> m b
 forMOf ::            Lens a b c d      -> a -> (c -> m d) -> m b
 forMOf :: Monad m => Traversal a b c d -> a -> (c -> m d) -> m b

sequenceOf :: LensLike (WrappedMonad m) a b (m c) c -> a -> m bSource

 sequence = sequenceOf traverse
 sequenceOf l = mapMOf l id
 sequenceOf l = unwrapMonad . l WrapMonad
 sequenceOf ::            Iso a b (m c) c       -> a -> m b
 sequenceOf ::            Lens a b (m c) c      -> a -> m b
 sequenceOf :: Monad m => Traversal a 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 = transposeOf traverse
>>> 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 = mapAccumLOf traverse

mapAccumLOf accumulates state from left to right.

 mapAccumLOf :: Iso a b c d       -> (s -> c -> (s, d)) -> s -> a -> (s, b)
 mapAccumLOf :: Lens a b c d      -> (s -> c -> (s, d)) -> s -> a -> (s, b)
 mapAccumLOf :: Traversal 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)Source

Generalizes mapAccumR to an arbitrary Traversal.

mapAccumR = mapAccumROf traverse

mapAccumROf accumulates state from right to left.

 mapAccumROf :: Iso a b c d       -> (s -> c -> (s, d)) -> s -> a -> (s, b)
 mapAccumROf :: Lens a b c d      -> (s -> c -> (s, d)) -> s -> a -> (s, b)
 mapAccumROf :: Traversal 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 -> bSource

Permit the use of scanr1 over an arbitrary Traversal or Lens.

scanr1 = scanr1Of traverse
 scanr1Of :: Iso a b c c       -> (c -> c -> c) -> a -> b
 scanr1Of :: Lens a b c c      -> (c -> c -> c) -> a -> b
 scanr1Of :: Traversal a b c c -> (c -> c -> c) -> a -> b

scanl1Of :: LensLike (Backwards (State (Maybe c))) a b c c -> (c -> c -> c) -> a -> bSource

Permit the use of scanl1 over an arbitrary Traversal or Lens.

scanl1 = scanl1Of traverse
 scanr1Of :: Iso a b c c       -> (c -> c -> c) -> a -> b
 scanr1Of :: Lens a b c c      -> (c -> c -> c) -> a -> b
 scanr1Of :: Traversal a b c c -> (c -> c -> c) -> a -> 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:

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.

ignored :: Traversal a a c dSource

This is the traversal that just doesn't return anything

ignored :: Applicative f => (c -> f d) -> a -> f a
ignored = const pure

traverseLeft :: Traversal (Either a c) (Either b c) a bSource

A traversal for tweaking the left-hand value of an Either:

traverseLeft :: Applicative f => (a -> f b) -> Either a c -> f (Either b c)

traverseRight :: Traversal (Either c a) (Either c b) a bSource

traverse the right-hand value of an Either:

traverseRight = traverse

Unfortunately the instance for Traversable (Either c) is still missing from base, so this can't just be traverse

traverseRight :: Applicative f => (a -> f b) -> Either c a -> f (Either c a)

both :: Traversal (a, a) (b, b) a bSource

Traverse both parts of a tuple with matching types.

Cloning Traversals

cloneTraversal :: Applicative f => ((c -> Bazaar c d d) -> a -> Bazaar c d b) -> (c -> f d) -> a -> f bSource

A Traversal is completely characterized by its behavior on a Bazaar.

Cloning a Traversal is one way to make sure you arent given something weaker, such as a Fold and can be used as a way to pass around traversals that have to be monomorphic in f.

Note: This only accepts a proper Traversal (or Lens). To clone a Lens as such, use cloneLens

Note: It is usually better to ReifyTraversal and use reflectTraversal than to cloneTraversal. The former can execute at full speed, while the latter needs to round trip through the Bazaar.

data ReifiedTraversal a b c d Source

A form of Traversal that can be stored monomorphically in a container.

Constructors

ReifyTraversal 

Fields

reflectTraversal :: Traversal a b c d
 

Simple

type SimpleTraversal a b = Traversal a a b bSource

type SimpleTraversal = Simple Traversal

type SimpleReifiedTraversal a b = ReifiedTraversal a a b bSource

type SimpleReifiedTraversal = Simple ReifiedTraversal