lens-3.6: Lenses, Folds and Traversals

PortabilityRank2Types
Stabilityexperimental
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellTrustworthy

Data.Data.Lens

Contents

Description

Smart and naïve generic traversals given Data instances.

template, uniplate, and biplate each build up information about what types can be contained within another type to speed up Traversal.

Synopsis

Generic Traversal

template :: forall s a. (Data s, Typeable a) => Simple Traversal s aSource

Find every occurence of a given type a recursively that doesn't require passing through something of type a using Data, while avoiding traversal of areas that cannot contain a value of type a.

This is uniplate with a more liberal signature.

tinplate :: (Data s, Typeable a) => Simple Traversal s aSource

Naïve Traversal using Data. This does not attempt to optimize the traversal.

This is primarily useful when the children are immediately obvious, and for benchmarking.

uniplate :: Data a => Simple Traversal a aSource

Find descendants of type a non-transitively, while avoiding computation of areas that cannot contain values of type a using Data.

uniplate is a useful default definition for plate

biplate :: forall s a. (Data s, Typeable a) => Simple Traversal s aSource

biplate performs like template, except when s ~ a, it returns itself and nothing else.

Field Accessor Traversal

upon :: forall s a. (Data s, Typeable a) => (s -> a) -> SimpleIndexedTraversal Int s aSource

This automatically constructs a Simple Traversal from a field accessor.

>>> (2,4) & upon fst *~ 5
(10,4)

There are however, a few caveats on how this function can be used:

First, the user supplied function must access one of the "immediate descendants" of the structure as attempts to access deeper structures or use non-field accessor functions will generate an empty Traversal.

A more rigorous way to say "immediate descendants" is that the function must only inspect one value that would be visited by template.

Note: this even permits some functions to be used directly.

>>> [1,2,3,4] & upon head .~ 0
[0,2,3,4]
>>> [1,2,3,4] & upon last .~ 5
[1,2,3,5]
>>> [1,2,3,4] ^? upon tail
Just [2,3,4]
>>> "" ^? upon tail
Nothing

Second, the structure must not contain strict or unboxed fields of the same type that will be visited by Data

If the supplied function is not a descendant that would be visible to template, the resulting Traversal will traverse no elements.

If the field you name isn't visible to template, but is a descendant of a field visible to template, then upon will return the *ancestor* it can visit, not the field you asked for! Be careful.

>>> upon (tail.tail) .~ [10,20] $ [1,2,3,4] -- BAD
[1,10,20]

To resolve this when you need deep self-similar recursion, use uponTheDeep. However, upon terminates for more inputs, while uponTheDeep can get lost in structures that are infinitely depth-recursive through a.

>>> uponTheDeep (tail.tail) .~ [10,20] $ [1,2,3,4] -- GOOD
[1,2,10,20]

The index of the Traversal can be used as an offset into elementOf (indexed template) or into the list returned by holesOf template.

upon' :: forall s a. (Data s, Typeable a) => (s -> a) -> SimpleIndexedLens Int s aSource

This more trusting version of upon uses your function directly as the getter for a Lens.

This means that reading from upon' is considerably faster than upon.

However, you pay for faster access in two ways:

  1. When passed an illegal field accessor, upon' will give you a Lens that quietly violates the laws unlike upon will will give you a legal Traversal, that avoids modifying the target.
  2. Modifying with the lens is slightly slower, since it has to go back and calculate the index after the fact.

When given a legal field accessor, the index of the Lens can be used as an offset into elementOf (indexed template) or into the list returned by holesOf template.

uponTheDeep :: forall k f s a. (Indexed [Int] k, Applicative f, Data s, Data a) => (s -> a) -> k (a -> f a) (s -> f s)Source

The design of upon doesn't allow it to search inside of values of type a for other values of type a. uponTheDeep provides this additional recursion.

>>> uponTheDeep (tail.tail) .~ [10,20] $ [1,2,3,4]
[1,2,10,20]
uponTheDeep :: (Data s, Data a) => (s -> a) -> SimpleIndexedTraversal [Int] s a

uponTheDeep' :: forall s a. (Data s, Data a) => (s -> a) -> SimpleIndexedLens [Int] s aSource

The design of upon' doesn't allow it to search inside of values of type a for other values of type a. uponTheDeep' provides this additional recursion.

Like upon', uponTheDeep' trusts the user supplied function more than uponTheDeep using it directly as the accessor. This enables reading from the resulting Lens to be considerably faster at the risk of generating an illegal lens.

>>> uponTheDeep' (tail.tail) .~ [10,20] $ [1,2,3,4]
[1,2,10,20]

Data Traversal

gtraverse :: (Applicative f, Data a) => (forall d. Data d => d -> f d) -> a -> f aSource

A generic applicative transformation that maps over the immediate subterms.

gtraverse is to traverse what gmapM is to mapM

This really belongs in Data.Data.