lens-5.1: Lenses, Folds and Traversals
Copyright(C) 2012-2016 Edward Kmett (C) 2006-2012 Neil Mitchell
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
PortabilityRank2Types
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Data.Lens

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) => Traversal' s a Source #

Find every occurrence 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) => Traversal' s a Source #

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 => Traversal' a a Source #

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) => Traversal' s a Source #

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

Field Accessor Traversal

upon :: forall p f s a. (Indexable [Int] p, Applicative f, Data s, Data a) => (s -> a) -> p a (f a) -> s -> f s Source #

This automatically constructs a Traversal' from an function.

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

There are however, caveats on how this function can be used!

First, the user supplied function must access only one field of the specified type. That is to say the target must be a single element that would be visited by holesOnOf template uniplate

Note: this even permits a number of 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

Accessing parents on the way down to children is okay:

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

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

upon :: (Data s, Data a) => (s -> a) -> IndexedTraversal' [Int] s a

upon' :: forall s a. (Data s, Data a) => (s -> a) -> IndexedLens' [Int] s a Source #

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

Like onceUpon', upon' trusts the user supplied function more than upon 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.

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

onceUpon :: forall s a. (Data s, Typeable a) => (s -> a) -> IndexedTraversal' Int s a Source #

This automatically constructs a Traversal' from a field accessor.

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

The design of onceUpon doesn't allow it to search inside of values of type a for other values of type a. upon provides this additional recursion, but at the expense of performance.

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

When in doubt, use upon instead.

onceUpon' :: forall s a. (Data s, Typeable a) => (s -> a) -> IndexedLens' Int s a Source #

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, which 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.

When in doubt, use upon' instead.

Data Traversal

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

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.