| Portability | Rank2Types | 
|---|---|
| Stability | experimental | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Safe Haskell | Trustworthy | 
Data.Data.Lens
Description
- template :: forall s a. (Data s, Typeable a) => Simple Traversal s a
 - tinplate :: (Data s, Typeable a) => Simple Traversal s a
 - uniplate :: Data a => Simple Traversal a a
 - biplate :: forall s a. (Data s, Typeable a) => Simple Traversal s a
 - upon :: forall s a. (Data s, Typeable a) => (s -> a) -> SimpleIndexedTraversal Int s a
 - upon' :: forall s a. (Data s, Typeable a) => (s -> a) -> SimpleIndexedLens Int s a
 - uponTheDeep :: forall k f s a. (Indexed [Int] k, Applicative f, Data s, Data a) => (s -> a) -> k (a -> f a) (s -> f s)
 - uponTheDeep' :: forall s a. (Data s, Data a) => (s -> a) -> SimpleIndexedLens [Int] s a
 - gtraverse :: (Applicative f, Data a) => (forall d. Data d => d -> f d) -> a -> f a
 
Generic Traversal
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 tailJust [2,3,4]
>>>"" ^? upon tailNothing
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  or into the list
 returned by elementOf (indexed template).
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:
-  When passed an illegal field accessor, 
upon'will give you aLensthat quietly violates the laws unlikeuponwill will give you a legalTraversal, that avoids modifying the target. - 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
  or into the list returned by elementOf (indexed template).
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:: (Datas,Dataa) => (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]