| Copyright | (C) 2012-16 Edward Kmett | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Stability | provisional | 
| Portability | Rank2Types | 
| Safe Haskell | Trustworthy | 
| Language | Haskell98 | 
Control.Lens.Traversal
Contents
Description
A Traversal s t a btraverse from
 Traversable. It allows you to traverse over a structure and change out
 its contents with monadic or Applicative side-effects. Starting from
traverse:: (Traversablet,Applicativef) => (a -> f b) -> t a -> f (t b)
we monomorphize the contents and result to obtain
typeTraversals t a b = forall f.Applicativef => (a -> f b) -> s -> f t
A Traversal can be used as a Fold.
 Any Traversal 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 a Traversal, and here we provide combinators that generalize
 the usual Traversable operations.
- type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t
- type Traversal' s a = Traversal s s a a
- type Traversal1 s t a b = forall f. Apply f => (a -> f b) -> s -> f t
- type Traversal1' s a = Traversal1 s s a a
- type IndexedTraversal i s t a b = forall p f. (Indexable i p, Applicative f) => p a (f b) -> s -> f t
- type IndexedTraversal' i s a = IndexedTraversal i s s a a
- type IndexedTraversal1 i s t a b = forall p f. (Indexable i p, Apply f) => p a (f b) -> s -> f t
- type IndexedTraversal1' i s a = IndexedTraversal1 i s s a a
- type ATraversal s t a b = LensLike (Bazaar (->) a b) s t a b
- type ATraversal' s a = ATraversal s s a a
- type ATraversal1 s t a b = LensLike (Bazaar1 (->) a b) s t a b
- type ATraversal1' s a = ATraversal1 s s a a
- type AnIndexedTraversal i s t a b = Over (Indexed i) (Bazaar (Indexed i) a b) s t a b
- type AnIndexedTraversal' i s a = AnIndexedTraversal i s s a a
- type AnIndexedTraversal1 i s t a b = Over (Indexed i) (Bazaar1 (Indexed i) a b) s t a b
- type AnIndexedTraversal1' i s a = AnIndexedTraversal1 i s s a a
- type Traversing p f s t a b = Over p (BazaarT p f a b) s t a b
- type Traversing' p f s a = Traversing p f s s a a
- type Traversing1 p f s t a b = Over p (BazaarT1 p f a b) s t a b
- type Traversing1' p f s a = Traversing1 p f s s a a
- traverseOf :: LensLike f s t a b -> (a -> f b) -> s -> f t
- forOf :: LensLike f s t a b -> s -> (a -> f b) -> f t
- sequenceAOf :: LensLike f s t (f b) b -> s -> f t
- mapMOf :: LensLike (WrappedMonad m) s t a b -> (a -> m b) -> s -> m t
- forMOf :: LensLike (WrappedMonad m) s t a b -> s -> (a -> m b) -> m t
- sequenceOf :: LensLike (WrappedMonad m) s t (m b) b -> s -> m t
- transposeOf :: LensLike ZipList s t [a] a -> s -> [t]
- mapAccumLOf :: LensLike (State acc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
- mapAccumROf :: LensLike (Backwards (State acc)) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
- scanr1Of :: LensLike (Backwards (State (Maybe a))) s t a a -> (a -> a -> a) -> s -> t
- scanl1Of :: LensLike (State (Maybe a)) s t a a -> (a -> a -> a) -> s -> t
- failover :: Alternative m => LensLike ((,) Any) s t a b -> (a -> b) -> s -> m t
- ifailover :: Alternative m => Over (Indexed i) ((,) Any) s t a b -> (i -> a -> b) -> s -> m t
- cloneTraversal :: ATraversal s t a b -> Traversal s t a b
- cloneIndexPreservingTraversal :: ATraversal s t a b -> IndexPreservingTraversal s t a b
- cloneIndexedTraversal :: AnIndexedTraversal i s t a b -> IndexedTraversal i s t a b
- cloneTraversal1 :: ATraversal1 s t a b -> Traversal1 s t a b
- cloneIndexPreservingTraversal1 :: ATraversal1 s t a b -> IndexPreservingTraversal1 s t a b
- cloneIndexedTraversal1 :: AnIndexedTraversal1 i s t a b -> IndexedTraversal1 i s t a b
- partsOf :: Functor f => Traversing (->) f s t a a -> LensLike f s t [a] [a]
- partsOf' :: ATraversal s t a a -> Lens s t [a] [a]
- unsafePartsOf :: Functor f => Traversing (->) f s t a b -> LensLike f s t [a] [b]
- unsafePartsOf' :: ATraversal s t a b -> Lens s t [a] [b]
- holesOf :: forall p s t a. Conjoined p => Over p (Bazaar p a a) s t a a -> s -> [Pretext p a a t]
- singular :: (Conjoined p, Functor f) => Traversing p f s t a a -> Over p f s t a a
- unsafeSingular :: (Conjoined p, Functor f) => Traversing p f s t a b -> Over p f s t a b
- class (Functor t, Foldable t) => Traversable t where- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
 
- class (Foldable1 t, Traversable t) => Traversable1 t where
- both :: Bitraversable r => Traversal (r a a) (r b b) a b
- beside :: (Representable q, Applicative (Rep q), Applicative f, Bitraversable r) => Optical p q f s t a b -> Optical p q f s' t' a b -> Optical p q f (r s s') (r t t') a b
- taking :: (Conjoined p, Applicative f) => Int -> Traversing p f s t a a -> Over p f s t a a
- dropping :: (Conjoined p, Applicative f) => Int -> Over p (Indexing f) s t a a -> Over p f s t a a
- failing :: (Conjoined p, Applicative f) => Traversing p f s t a b -> Over p f s t a b -> Over p f s t a b
- deepOf :: (Conjoined p, Applicative f) => LensLike f s t s t -> Traversing p f s t a b -> Over p f s t a b
- ignored :: Applicative f => pafb -> s -> f s
- class Ord k => TraverseMin k m | m -> k where
- class Ord k => TraverseMax k m | m -> k where
- traversed :: Traversable f => IndexedTraversal Int (f a) (f b) a b
- traversed1 :: Traversable1 f => IndexedTraversal1 Int (f a) (f b) a b
- traversed64 :: Traversable f => IndexedTraversal Int64 (f a) (f b) a b
- elementOf :: Applicative f => LensLike (Indexing f) s t a a -> Int -> IndexedLensLike Int f s t a a
- element :: Traversable t => Int -> IndexedTraversal' Int (t a) a
- elementsOf :: Applicative f => LensLike (Indexing f) s t a a -> (Int -> Bool) -> IndexedLensLike Int f s t a a
- elements :: Traversable t => (Int -> Bool) -> IndexedTraversal' Int (t a) a
- ipartsOf :: forall i p f s t a. (Indexable [i] p, Functor f) => Traversing (Indexed i) f s t a a -> Over p f s t [a] [a]
- ipartsOf' :: forall i p f s t a. (Indexable [i] p, Functor f) => Over (Indexed i) (Bazaar' (Indexed i) a) s t a a -> Over p f s t [a] [a]
- iunsafePartsOf :: forall i p f s t a b. (Indexable [i] p, Functor f) => Traversing (Indexed i) f s t a b -> Over p f s t [a] [b]
- iunsafePartsOf' :: forall i s t a b. Over (Indexed i) (Bazaar (Indexed i) a b) s t a b -> IndexedLens [i] s t [a] [b]
- itraverseOf :: (Indexed i a (f b) -> s -> f t) -> (i -> a -> f b) -> s -> f t
- iforOf :: (Indexed i a (f b) -> s -> f t) -> s -> (i -> a -> f b) -> f t
- imapMOf :: Over (Indexed i) (WrappedMonad m) s t a b -> (i -> a -> m b) -> s -> m t
- iforMOf :: (Indexed i a (WrappedMonad m b) -> s -> WrappedMonad m t) -> s -> (i -> a -> m b) -> m t
- imapAccumROf :: Over (Indexed i) (Backwards (State acc)) s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
- imapAccumLOf :: Over (Indexed i) (State acc) s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
- traverseBy :: Traversable t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (a -> f b) -> t a -> f (t b)
- traverseByOf :: Traversal s t a b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (a -> f b) -> s -> f t
- sequenceBy :: Traversable t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> t (f a) -> f (t a)
- sequenceByOf :: Traversal s t (f b) b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> s -> f t
- newtype Bazaar p a b t = Bazaar {- runBazaar :: forall f. Applicative f => p a (f b) -> f t
 
- type Bazaar' p a = Bazaar p a a
- newtype Bazaar1 p a b t = Bazaar1 {- runBazaar1 :: forall f. Apply f => p a (f b) -> f t
 
- type Bazaar1' p a = Bazaar1 p a a
- loci :: Traversal (Bazaar (->) a c s) (Bazaar (->) b c s) a b
- iloci :: IndexedTraversal i (Bazaar (Indexed i) a c s) (Bazaar (Indexed i) b c s) a b
- confusing :: Applicative f => LensLike (Curried (Yoneda f) (Yoneda f)) s t a b -> LensLike f s t a b
Traversals
type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t Source #
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".
tpure≡purefmap(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 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!
type Traversal' s a = Traversal s s a a Source #
typeTraversal'=SimpleTraversal
type Traversal1 s t a b = forall f. Apply f => (a -> f b) -> s -> f t Source #
type Traversal1' s a = Traversal1 s s a a Source #
type IndexedTraversal i s t a b = forall p f. (Indexable i p, Applicative f) => p a (f b) -> s -> f t Source #
Every IndexedTraversal is a valid Traversal or
 IndexedFold.
The Indexed constraint is used to allow an IndexedTraversal to be used
 directly as a Traversal.
The Traversal laws are still required to hold.
In addition, the index i should satisfy the requirement that it stays
 unchanged even when modifying the value a, otherwise traversals like
 indices break the Traversal laws.
type IndexedTraversal' i s a = IndexedTraversal i s s a a Source #
typeIndexedTraversal'i =Simple(IndexedTraversali)
type IndexedTraversal1 i s t a b = forall p f. (Indexable i p, Apply f) => p a (f b) -> s -> f t Source #
type IndexedTraversal1' i s a = IndexedTraversal1 i s s a a Source #
type ATraversal s t a b = LensLike (Bazaar (->) a b) s t a b Source #
When you see this as an argument to a function, it expects a Traversal.
type ATraversal' s a = ATraversal s s a a Source #
typeATraversal'=SimpleATraversal
type ATraversal1 s t a b = LensLike (Bazaar1 (->) a b) s t a b Source #
When you see this as an argument to a function, it expects a Traversal1.
type ATraversal1' s a = ATraversal1 s s a a Source #
typeATraversal1'=SimpleATraversal1
type AnIndexedTraversal i s t a b = Over (Indexed i) (Bazaar (Indexed i) a b) s t a b Source #
When you see this as an argument to a function, it expects an IndexedTraversal.
type AnIndexedTraversal' i s a = AnIndexedTraversal i s s a a Source #
typeAnIndexedTraversal'=Simple(AnIndexedTraversali)
type AnIndexedTraversal1 i s t a b = Over (Indexed i) (Bazaar1 (Indexed i) a b) s t a b Source #
When you see this as an argument to a function, it expects an IndexedTraversal1.
type AnIndexedTraversal1' i s a = AnIndexedTraversal1 i s s a a Source #
typeAnIndexedTraversal1'=Simple(AnIndexedTraversal1i)
type Traversing p f s t a b = Over p (BazaarT p f a b) s t a b Source #
When you see this as an argument to a function, it expects
- to be indexed if pis an instance ofIndexedi,
- to be unindexed if pis(->),
- a TraversaliffisApplicative,
- a Getteriffis only aFunctorandContravariant,
- a Lensifpis only aFunctor,
- a FoldiffisFunctor,ContravariantandApplicative.
type Traversing' p f s a = Traversing p f s s a a Source #
typeTraversing'f =Simple(Traversingf)
type Traversing1 p f s t a b = Over p (BazaarT1 p f a b) s t a b Source #
type Traversing1' p f s a = Traversing1 p f s s a a Source #
Traversing and Lensing
traverseOf :: LensLike f s t a b -> (a -> f b) -> s -> f t Source #
Map each element of a structure targeted by a Lens or Traversal,
 evaluate these actions from left to right, and collect the results.
This function is only provided for consistency, id is strictly more general.
>>>traverseOf each print (1,2,3)1 2 3 ((),(),())
traverseOf≡iditraverseOfl ≡traverseOfl.IndexeditraverseOfitraversed≡itraverse
This yields the obvious law:
traverse≡traverseOftraverse
traverseOf::Functorf =>Isos t a b -> (a -> f b) -> s -> f ttraverseOf::Functorf =>Lenss t a b -> (a -> f b) -> s -> f ttraverseOf::Applicativef =>Traversals t a b -> (a -> f b) -> s -> f t
forOf :: LensLike f s t a b -> s -> (a -> f b) -> f t Source #
A version of traverseOf with the arguments flipped, such that:
>>>forOf each (1,2,3) print1 2 3 ((),(),())
This function is only provided for consistency, flip is strictly more general.
forOf≡flipforOf≡flip.traverseOf
for≡forOftraverseiforl s ≡forl s.Indexed
forOf::Functorf =>Isos t a b -> s -> (a -> f b) -> f tforOf::Functorf =>Lenss t a b -> s -> (a -> f b) -> f tforOf::Applicativef =>Traversals t a b -> s -> (a -> f b) -> f t
sequenceAOf :: LensLike f s t (f b) b -> s -> f t Source #
Evaluate each action in the structure from left to right, and collect the results.
>>>sequenceAOf both ([1,2],[3,4])[(1,3),(1,4),(2,3),(2,4)]
sequenceA≡sequenceAOftraverse≡traverseidsequenceAOfl ≡traverseOflid≡ lid
sequenceAOf::Functorf =>Isos t (f b) b -> s -> f tsequenceAOf::Functorf =>Lenss t (f b) b -> s -> f tsequenceAOf::Applicativef =>Traversals t (f b) b -> s -> f t
mapMOf :: LensLike (WrappedMonad m) s t a b -> (a -> m b) -> s -> m t Source #
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.
>>>mapMOf both (\x -> [x, x + 1]) (1,3)[(1,3),(1,4),(2,3),(2,4)]
mapM≡mapMOftraverseimapMOfl ≡forMl.Indexed
mapMOf::Monadm =>Isos t a b -> (a -> m b) -> s -> m tmapMOf::Monadm =>Lenss t a b -> (a -> m b) -> s -> m tmapMOf::Monadm =>Traversals t a b -> (a -> m b) -> s -> m t
forMOf :: LensLike (WrappedMonad m) s t a b -> s -> (a -> m b) -> m t Source #
forMOf is a flipped version of mapMOf, consistent with the definition of forM.
>>>forMOf both (1,3) $ \x -> [x, x + 1][(1,3),(1,4),(2,3),(2,4)]
forM≡forMOftraverseforMOfl ≡flip(mapMOfl)iforMOfl s ≡forMl s.Indexed
forMOf::Monadm =>Isos t a b -> s -> (a -> m b) -> m tforMOf::Monadm =>Lenss t a b -> s -> (a -> m b) -> m tforMOf::Monadm =>Traversals t a b -> s -> (a -> m b) -> m t
sequenceOf :: LensLike (WrappedMonad m) s t (m b) b -> s -> m t Source #
Sequence the (monadic) effects targeted by a Lens in a container from left to right.
>>>sequenceOf each ([1,2],[3,4],[5,6])[(1,3,5),(1,3,6),(1,4,5),(1,4,6),(2,3,5),(2,3,6),(2,4,5),(2,4,6)]
sequence≡sequenceOftraversesequenceOfl ≡mapMOflidsequenceOfl ≡unwrapMonad.lWrapMonad
sequenceOf::Monadm =>Isos t (m b) b -> s -> m tsequenceOf::Monadm =>Lenss t (m b) b -> s -> m tsequenceOf::Monadm =>Traversals t (m b) b -> s -> m t
transposeOf :: LensLike ZipList s t [a] a -> s -> [t] Source #
This generalizes transpose to an arbitrary Traversal.
Note: transpose handles ragged inputs more intelligently, but for non-ragged inputs:
>>>transposeOf traverse [[1,2,3],[4,5,6]][[1,4],[2,5],[3,6]]
transpose≡transposeOftraverse
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 (State acc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) Source #
This generalizes mapAccumL to an arbitrary Traversal.
mapAccumL≡mapAccumLOftraverse
mapAccumLOf accumulates State from left to right.
mapAccumLOf::Isos t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)mapAccumLOf::Lenss t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)mapAccumLOf::Traversals t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
mapAccumLOf::LensLike(Stateacc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)mapAccumLOfl f acc0 s =swap(runState(l (a ->state(acc ->swap(f acc a))) s) acc0)
mapAccumROf :: LensLike (Backwards (State acc)) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t) Source #
This generalizes mapAccumR to an arbitrary Traversal.
mapAccumR≡mapAccumROftraverse
mapAccumROf accumulates State from right to left.
mapAccumROf::Isos t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)mapAccumROf::Lenss t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)mapAccumROf::Traversals t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
mapAccumROf::LensLike(Backwards(Stateacc)) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
failover :: Alternative m => LensLike ((,) Any) s t a b -> (a -> b) -> s -> m t Source #
Try to map a function over this Traversal, failing if the Traversal has no targets.
>>>failover (element 3) (*2) [1,2] :: Maybe [Int]Nothing
>>>failover _Left (*2) (Right 4) :: Maybe (Either Int Int)Nothing
>>>failover _Right (*2) (Right 4) :: Maybe (Either Int Int)Just (Right 8)
failover :: Alternative m => Traversal s t a b -> (a -> b) -> s -> m t
ifailover :: Alternative m => Over (Indexed i) ((,) Any) s t a b -> (i -> a -> b) -> s -> m t Source #
Try to map a function which uses the index over this IndexedTraversal, failing if the IndexedTraversal has no targets.
ifailover :: Alternative m => IndexedTraversal i s t a b -> (i -> a -> b) -> s -> m t
Monomorphic Traversals
cloneTraversal :: ATraversal s t a b -> Traversal s t a b Source #
A Traversal is completely characterized by its behavior on a Bazaar.
Cloning a Traversal is one way to make sure you aren't 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 use ReifiedTraversal and
 runTraversal than to cloneTraversal. The
 former can execute at full speed, while the latter needs to round trip through
 the Bazaar.
>>>let foo l a = (view (getting (cloneTraversal l)) a, set (cloneTraversal l) 10 a)>>>foo both ("hello","world")("helloworld",(10,10))
cloneTraversal::LensLike(Bazaar(->) a b) s t a b ->Traversals t a b
cloneIndexPreservingTraversal :: ATraversal s t a b -> IndexPreservingTraversal s t a b Source #
Clone a Traversal yielding an IndexPreservingTraversal that passes through
 whatever index it is composed with.
cloneIndexedTraversal :: AnIndexedTraversal i s t a b -> IndexedTraversal i s t a b Source #
Clone an IndexedTraversal yielding an IndexedTraversal with the same index.
cloneTraversal1 :: ATraversal1 s t a b -> Traversal1 s t a b Source #
A Traversal1 is completely characterized by its behavior on a Bazaar1.
cloneIndexPreservingTraversal1 :: ATraversal1 s t a b -> IndexPreservingTraversal1 s t a b Source #
Clone a Traversal1 yielding an IndexPreservingTraversal1 that passes through
 whatever index it is composed with.
cloneIndexedTraversal1 :: AnIndexedTraversal1 i s t a b -> IndexedTraversal1 i s t a b Source #
Clone an IndexedTraversal1 yielding an IndexedTraversal1 with the same index.
Parts and Holes
partsOf :: Functor f => Traversing (->) f s t a a -> LensLike f s t [a] [a] Source #
partsOf turns a Traversal into a Lens that resembles an early version of the uniplate (or biplate) type.
Note: You should really try to maintain the invariant of the number of children in the list.
>>>(a,b,c) & partsOf each .~ [x,y,z](x,y,z)
Any extras will be lost. If you do not supply enough, then the remainder will come from the original structure.
>>>(a,b,c) & partsOf each .~ [w,x,y,z](w,x,y)
>>>(a,b,c) & partsOf each .~ [x,y](x,y,c)
>>>('b', 'a', 'd', 'c') & partsOf each %~ sort('a','b','c','d')
So technically, this is only a Lens if you do not change the number of results it returns.
When applied to a Fold the result is merely a Getter.
partsOf::Iso's a ->Lens's [a]partsOf::Lens's a ->Lens's [a]partsOf::Traversal's a ->Lens's [a]partsOf::Folds a ->Getters [a]partsOf::Getters a ->Getters [a]
partsOf' :: ATraversal s t a a -> Lens s t [a] [a] Source #
unsafePartsOf :: Functor f => Traversing (->) f s t a b -> LensLike f s t [a] [b] Source #
unsafePartsOf turns a Traversal into a uniplate (or biplate) family.
If you do not need the types of s and t to be different, it is recommended that
 you use partsOf.
It is generally safer to traverse with the Bazaar rather than use this
 combinator. However, it is sometimes convenient.
This is unsafe because if you don't supply at least as many b's as you were
 given a's, then the reconstruction of t will result in an error!
When applied to a Fold the result is merely a Getter (and becomes safe).
unsafePartsOf::Isos t a b ->Lenss t [a] [b]unsafePartsOf::Lenss t a b ->Lenss t [a] [b]unsafePartsOf::Traversals t a b ->Lenss t [a] [b]unsafePartsOf::Folds a ->Getters [a]unsafePartsOf::Getters a ->Getters [a]
unsafePartsOf' :: ATraversal s t a b -> Lens s t [a] [b] Source #
holesOf :: forall p s t a. Conjoined p => Over p (Bazaar p a a) s t a a -> s -> [Pretext p a a t] Source #
The one-level version of contextsOf. This extracts a list of the immediate children according to a given Traversal as editable contexts.
Given a context you can use pos to see the values, peek at what the structure would be like with an edited result, or simply extract the original structure.
propChildren l x = childrenOf l x==mappos(holesOfl x) propId l x =all(==x) [extractw | w <-holesOfl x]
holesOf::Iso's a -> s -> [Pretext'(->) a s]holesOf::Lens's a -> s -> [Pretext'(->) a s]holesOf::Traversal's a -> s -> [Pretext'(->) a s]holesOf::IndexedLens'i s a -> s -> [Pretext'(Indexedi) a s]holesOf::IndexedTraversal'i s a -> s -> [Pretext'(Indexedi) a s]
singular :: (Conjoined p, Functor f) => Traversing p f s t a a -> Over p f s t a a Source #
This converts a Traversal that you "know" will target one or more elements to a Lens. It can
 also be used to transform a non-empty Fold into a Getter.
The resulting Lens or Getter will be partial if the supplied Traversal returns
 no results.
>>>[1,2,3] ^. singular _head1
>>>Left (ErrorCall "singular: empty traversal") <- try (evaluate ([] ^. singular _head)) :: IO (Either ErrorCall ())
>>>Left 4 ^. singular _Left4
>>>[1..10] ^. singular (ix 7)8
>>>[] & singular traverse .~ 0[]
singular::Traversals t a a ->Lenss t a asingular::Folds a ->Getters asingular::IndexedTraversali s t a a ->IndexedLensi s t a asingular::IndexedFoldi s a ->IndexedGetteri s a
unsafeSingular :: (Conjoined p, Functor f) => Traversing p f s t a b -> Over p f s t a b Source #
This converts a Traversal that you "know" will target only one element to a Lens. It can also be
 used to transform a Fold into a Getter.
The resulting Lens or Getter will be partial if the Traversal targets nothing
 or more than one element.
>>>Left (ErrorCall "unsafeSingular: empty traversal") <- try (evaluate ([] & unsafeSingular traverse .~ 0)) :: IO (Either ErrorCall [Integer])
unsafeSingular::Traversals t a b ->Lenss t a bunsafeSingular::Folds a ->Getters aunsafeSingular::IndexedTraversali s t a b ->IndexedLensi s t a bunsafeSingular::IndexedFoldi s a ->IndexedGetteri s a
Common Traversals
class (Functor t, Foldable t) => Traversable t where #
Functors representing data structures that can be traversed from left to right.
A definition of traverse must satisfy the following laws:
- naturality
- t .for every applicative transformation- traversef =- traverse(t . f)- t
- identity
- traverseIdentity = Identity
- composition
- traverse(Compose .- fmapg . f) = Compose .- fmap(- traverseg) .- traversef
A definition of sequenceA must satisfy the following laws:
- naturality
- t .for every applicative transformation- sequenceA=- sequenceA.- fmapt- t
- identity
- sequenceA.- fmapIdentity = Identity
- composition
- sequenceA.- fmapCompose = Compose .- fmap- sequenceA.- sequenceA
where an applicative transformation is a function
t :: (Applicative f, Applicative g) => f a -> g a
preserving the Applicative operations, i.e.
and the identity functor Identity and composition of functors Compose
 are defined as
  newtype Identity a = Identity a
  instance Functor Identity where
    fmap f (Identity x) = Identity (f x)
  instance Applicative Identity where
    pure x = Identity x
    Identity f <*> Identity x = Identity (f x)
  newtype Compose f g a = Compose (f (g a))
  instance (Functor f, Functor g) => Functor (Compose f g) where
    fmap f (Compose x) = Compose (fmap (fmap f) x)
  instance (Applicative f, Applicative g) => Applicative (Compose f g) where
    pure x = Compose (pure (pure x))
    Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)(The naturality law is implied by parametricity.)
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).
Instances
class (Foldable1 t, Traversable t) => Traversable1 t where #
Instances
| Traversable1 Identity | |
| Traversable1 NonEmpty | |
| Traversable1 Tree | |
| Traversable1 ((,) a) | |
| Traversable1 f => Traversable1 (Cofree f) | |
| Traversable1 f => Traversable1 (Free f) | |
| Traversable1 f => Traversable1 (Yoneda f) | |
| Traversable1 f => Traversable1 (Lift f) | |
| Bitraversable1 p => Traversable1 (Join * p) | |
| Traversable1 f => Traversable1 (IdentityT * f) | |
| Traversable1 f => Traversable1 (Reverse * f) | |
| Traversable1 f => Traversable1 (Backwards * f) | |
| Traversable1 f => Traversable1 (AlongsideRight f a) # | |
| Traversable1 f => Traversable1 (AlongsideLeft f b) # | |
| (Traversable1 f, Traversable1 g) => Traversable1 (Sum * f g) | |
| (Traversable1 f, Traversable1 g) => Traversable1 (Product * f g) | |
| (Traversable1 f, Traversable1 g) => Traversable1 (Compose * * f g) | |
| Traversable1 g => Traversable1 (Joker * * g a) | |
both :: Bitraversable r => Traversal (r a a) (r b b) a b Source #
Traverse both parts of a Bitraversable container with matching types.
Usually that type will be a pair.
>>>(1,2) & both *~ 10(10,20)
>>>over both length ("hello","world")(5,5)
>>>("hello","world")^.both"helloworld"
both::Traversal(a, a) (b, b) a bboth::Traversal(Eithera a) (Eitherb b) a b
beside :: (Representable q, Applicative (Rep q), Applicative f, Bitraversable r) => Optical p q f s t a b -> Optical p q f s' t' a b -> Optical p q f (r s s') (r t t') a b Source #
Apply a different Traversal or Fold to each side of a Bitraversable container.
beside::Traversals t a b ->Traversals' t' a b ->Traversal(r s s') (r t t') a bbeside::IndexedTraversali s t a b ->IndexedTraversali s' t' a b ->IndexedTraversali (r s s') (r t t') a bbeside::IndexPreservingTraversals t a b ->IndexPreservingTraversals' t' a b ->IndexPreservingTraversal(r s s') (r t t') a b
beside::Traversals t a b ->Traversals' t' a b ->Traversal(s,s') (t,t') a bbeside::Lenss t a b ->Lenss' t' a b ->Traversal(s,s') (t,t') a bbeside::Folds a ->Folds' a ->Fold(s,s') abeside::Getters a ->Getters' a ->Fold(s,s') a
beside::IndexedTraversali s t a b ->IndexedTraversali s' t' a b ->IndexedTraversali (s,s') (t,t') a bbeside::IndexedLensi s t a b ->IndexedLensi s' t' a b ->IndexedTraversali (s,s') (t,t') a bbeside::IndexedFoldi s a ->IndexedFoldi s' a ->IndexedFoldi (s,s') abeside::IndexedGetteri s a ->IndexedGetteri s' a ->IndexedFoldi (s,s') a
beside::IndexPreservingTraversals t a b ->IndexPreservingTraversals' t' a b ->IndexPreservingTraversal(s,s') (t,t') a bbeside::IndexPreservingLenss t a b ->IndexPreservingLenss' t' a b ->IndexPreservingTraversal(s,s') (t,t') a bbeside::IndexPreservingFolds a ->IndexPreservingFolds' a ->IndexPreservingFold(s,s') abeside::IndexPreservingGetters a ->IndexPreservingGetters' a ->IndexPreservingFold(s,s') a
>>>("hello",["world","!!!"])^..beside id traverse["hello","world","!!!"]
taking :: (Conjoined p, Applicative f) => Int -> Traversing p f s t a a -> Over p f s t a a Source #
Visit the first n targets of a Traversal, Fold, Getter or Lens.
>>>[("hello","world"),("!!!","!!!")]^.. taking 2 (traverse.both)["hello","world"]
>>>timingOut $ [1..] ^.. taking 3 traverse[1,2,3]
>>>over (taking 5 traverse) succ "hello world""ifmmp world"
taking::Int->Traversal's a ->Traversal's ataking::Int->Lens's a ->Traversal's ataking::Int->Iso's a ->Traversal's ataking::Int->Prism's a ->Traversal's ataking::Int->Getters a ->Folds ataking::Int->Folds a ->Folds ataking::Int->IndexedTraversal'i s a ->IndexedTraversal'i s ataking::Int->IndexedLens'i s a ->IndexedTraversal'i s ataking::Int->IndexedGetteri s a ->IndexedFoldi s ataking::Int->IndexedFoldi s a ->IndexedFoldi s a
dropping :: (Conjoined p, Applicative f) => Int -> Over p (Indexing f) s t a a -> Over p f s t a a Source #
Visit all but the first n targets of a Traversal, Fold, Getter or Lens.
>>>("hello","world") ^? dropping 1 bothJust "world"
Dropping works on infinite traversals as well:
>>>[1..] ^? dropping 1 foldedJust 2
dropping::Int->Traversal's a ->Traversal's adropping::Int->Lens's a ->Traversal's adropping::Int->Iso's a ->Traversal's adropping::Int->Prism's a ->Traversal's adropping::Int->Getters a ->Folds adropping::Int->Folds a ->Folds adropping::Int->IndexedTraversal'i s a ->IndexedTraversal'i s adropping::Int->IndexedLens'i s a ->IndexedTraversal'i s adropping::Int->IndexedGetteri s a ->IndexedFoldi s adropping::Int->IndexedFoldi s a ->IndexedFoldi s a
failing :: (Conjoined p, Applicative f) => Traversing p f s t a b -> Over p f s t a b -> Over p f s t a b infixl 5 Source #
Try the first Traversal (or Fold), falling back on the second Traversal (or Fold) if it returns no entries.
This is only a valid Traversal if the second Traversal is disjoint from the result of the first or returns
 exactly the same results. These conditions are trivially met when given a Lens, Iso, Getter, Prism or "affine" Traversal -- one that
 has 0 or 1 target.
Mutatis mutandis for Fold.
>>>[0,1,2,3] ^? failing (ix 1) (ix 2)Just 1
>>>[0,1,2,3] ^? failing (ix 42) (ix 2)Just 2
failing::Traversals t a b ->Traversals t a b ->Traversals t a bfailing::Prisms t a b ->Prisms t a b ->Traversals t a bfailing::Folds a ->Folds a ->Folds a
These cases are also supported, trivially, but are boring, because the left hand side always succeeds.
failing::Lenss t a b ->Traversals t a b ->Traversals t a bfailing::Isos t a b ->Traversals t a b ->Traversals t a bfailing::Equalitys t a b ->Traversals t a b ->Traversals t a bfailing::Getters a ->Folds a ->Folds a
If both of the inputs are indexed, the result is also indexed, so you can apply this to a pair of indexed traversals or indexed folds, obtaining an indexed traversal or indexed fold.
failing::IndexedTraversali s t a b ->IndexedTraversali s t a b ->IndexedTraversali s t a bfailing::IndexedFoldi s a ->IndexedFoldi s a ->IndexedFoldi s a
These cases are also supported, trivially, but are boring, because the left hand side always succeeds.
failing::IndexedLensi s t a b ->IndexedTraversali s t a b ->IndexedTraversali s t a bfailing::IndexedGetteri s a ->IndexedGetteri s a ->IndexedFoldi s a
deepOf :: (Conjoined p, Applicative f) => LensLike f s t s t -> Traversing p f s t a b -> Over p f s t a b Source #
Try the second traversal. If it returns no entries, try again with all entries from the first traversal, recursively.
deepOf::Folds s ->Folds a ->Folds adeepOf::Traversal's s ->Traversal's a ->Traversal's adeepOf::Traversals t s t ->Traversals t a b ->Traversals t a bdeepOf::Folds s ->IndexedFoldi s a ->IndexedFoldi s adeepOf::Traversals t s t ->IndexedTraversali s t a b ->IndexedTraversali s t a b
Indexed Traversals
Common
ignored :: Applicative f => pafb -> s -> f s Source #
class Ord k => TraverseMin k m | m -> k where Source #
Allows IndexedTraversal the value at the smallest index.
Minimal complete definition
Methods
traverseMin :: IndexedTraversal' k (m v) v Source #
IndexedTraversal of the element with the smallest index.
Instances
| TraverseMin Int IntMap Source # | |
| Ord k => TraverseMin k (Map k) Source # | |
class Ord k => TraverseMax k m | m -> k where Source #
Allows IndexedTraversal of the value at the largest index.
Minimal complete definition
Methods
traverseMax :: IndexedTraversal' k (m v) v Source #
IndexedTraversal of the element at the largest index.
Instances
| TraverseMax Int IntMap Source # | |
| Ord k => TraverseMax k (Map k) Source # | |
traversed :: Traversable f => IndexedTraversal Int (f a) (f b) a b Source #
Traverse any Traversable container. This is an IndexedTraversal that is indexed by ordinal position.
traversed1 :: Traversable1 f => IndexedTraversal1 Int (f a) (f b) a b Source #
Traverse any Traversable1 container. This is an IndexedTraversal1 that is indexed by ordinal position.
traversed64 :: Traversable f => IndexedTraversal Int64 (f a) (f b) a b Source #
Traverse any Traversable container. This is an IndexedTraversal that is indexed by ordinal position.
elementOf :: Applicative f => LensLike (Indexing f) s t a a -> Int -> IndexedLensLike Int f s t a a Source #
Traverse the nth elementOf a Traversal, Lens or
 Iso if it exists.
>>>[[1],[3,4]] & elementOf (traverse.traverse) 1 .~ 5[[1],[5,4]]
>>>[[1],[3,4]] ^? elementOf (folded.folded) 1Just 3
>>>timingOut $ ['a'..] ^?! elementOf folded 5'f'
>>>timingOut $ take 10 $ elementOf traverse 3 .~ 16 $ [0..][0,1,2,16,4,5,6,7,8,9]
elementOf::Traversal's a ->Int->IndexedTraversal'Ints aelementOf::Folds a ->Int->IndexedFoldInts a
element :: Traversable t => Int -> IndexedTraversal' Int (t a) a Source #
Traverse the nth element of a Traversable container.
element≡elementOftraverse
elementsOf :: Applicative f => LensLike (Indexing f) s t a a -> (Int -> Bool) -> IndexedLensLike Int f s t a a Source #
Traverse (or fold) selected elements of a Traversal (or Fold) where their ordinal positions match a predicate.
elementsOf::Traversal's a -> (Int->Bool) ->IndexedTraversal'Ints aelementsOf::Folds a -> (Int->Bool) ->IndexedFoldInts a
elements :: Traversable t => (Int -> Bool) -> IndexedTraversal' Int (t a) a Source #
Traverse elements of a Traversable container where their ordinal positions match a predicate.
elements≡elementsOftraverse
Combinators
ipartsOf :: forall i p f s t a. (Indexable [i] p, Functor f) => Traversing (Indexed i) f s t a a -> Over p f s t [a] [a] Source #
An indexed version of partsOf that receives the entire list of indices as its index.
ipartsOf' :: forall i p f s t a. (Indexable [i] p, Functor f) => Over (Indexed i) (Bazaar' (Indexed i) a) s t a a -> Over p f s t [a] [a] Source #
A type-restricted version of ipartsOf that can only be used with an IndexedTraversal.
iunsafePartsOf :: forall i p f s t a b. (Indexable [i] p, Functor f) => Traversing (Indexed i) f s t a b -> Over p f s t [a] [b] Source #
An indexed version of unsafePartsOf that receives the entire list of indices as its index.
iunsafePartsOf' :: forall i s t a b. Over (Indexed i) (Bazaar (Indexed i) a b) s t a b -> IndexedLens [i] s t [a] [b] Source #
itraverseOf :: (Indexed i a (f b) -> s -> f t) -> (i -> a -> f b) -> s -> f t Source #
Traversal with an index.
NB: When you don't need access to the index then you can just apply your IndexedTraversal
 directly as a function!
itraverseOf≡withIndextraverseOfl =itraverseOfl.const=id
itraverseOf::Functorf =>IndexedLensi s t a b -> (i -> a -> f b) -> s -> f titraverseOf::Applicativef =>IndexedTraversali s t a b -> (i -> a -> f b) -> s -> f titraverseOf::Applyf =>IndexedTraversal1i s t a b -> (i -> a -> f b) -> s -> f t
iforOf :: (Indexed i a (f b) -> s -> f t) -> s -> (i -> a -> f b) -> f t Source #
Traverse with an index (and the arguments flipped).
forOfl a ≡iforOfl a.constiforOf≡flip.itraverseOf
iforOf::Functorf =>IndexedLensi s t a b -> s -> (i -> a -> f b) -> f tiforOf::Applicativef =>IndexedTraversali s t a b -> s -> (i -> a -> f b) -> f tiforOf::Applyf =>IndexedTraversal1i s t a b -> s -> (i -> a -> f b) -> f t
imapMOf :: Over (Indexed i) (WrappedMonad m) s t a b -> (i -> a -> m b) -> s -> m t Source #
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, with access
 its position.
When you don't need access to the index mapMOf is more liberal in what it can accept.
mapMOfl ≡imapMOfl.const
imapMOf::Monadm =>IndexedLensi s t a b -> (i -> a -> m b) -> s -> m timapMOf::Monadm =>IndexedTraversali s t a b -> (i -> a -> m b) -> s -> m timapMOf::Bindm =>IndexedTraversal1i s t a b -> (i -> a -> m b) -> s -> m t
iforMOf :: (Indexed i a (WrappedMonad m b) -> s -> WrappedMonad m t) -> s -> (i -> a -> m b) -> m t Source #
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, with access
 its position (and the arguments flipped).
forMOfl a ≡iforMOfl a.constiforMOf≡flip.imapMOf
iforMOf::Monadm =>IndexedLensi s t a b -> s -> (i -> a -> m b) -> m tiforMOf::Monadm =>IndexedTraversali s t a b -> s -> (i -> a -> m b) -> m t
imapAccumROf :: Over (Indexed i) (Backwards (State acc)) s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t) Source #
Generalizes mapAccumR to an arbitrary IndexedTraversal with access to the index.
imapAccumROf accumulates state from right to left.
mapAccumROfl ≡imapAccumROfl.const
imapAccumROf::IndexedLensi s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)imapAccumROf::IndexedTraversali s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
imapAccumLOf :: Over (Indexed i) (State acc) s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t) Source #
Generalizes mapAccumL to an arbitrary IndexedTraversal with access to the index.
imapAccumLOf accumulates state from left to right.
mapAccumLOfl ≡imapAccumLOfl.const
imapAccumLOf::IndexedLensi s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)imapAccumLOf::IndexedTraversali s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
Reflection
traverseBy :: Traversable t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (a -> f b) -> t a -> f (t b) #
Traverse a container using its Traversable instance using
 explicitly provided Applicative operations. This is like traverse
 where the Applicative instance can be manually specified.
traverseByOf :: Traversal s t a b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> (a -> f b) -> s -> f t Source #
Traverse a container using a specified Applicative.
This is like traverseBy where the Traversable instance can be specified by any Traversal
traverseByOftraverse≡traverseBy
sequenceBy :: Traversable t => (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> t (f a) -> f (t a) #
Sequence a container using its Traversable instance using
 explicitly provided Applicative operations. This is like sequence
 where the Applicative instance can be manually specified.
sequenceByOf :: Traversal s t (f b) b -> (forall x. x -> f x) -> (forall x y. f (x -> y) -> f x -> f y) -> s -> f t Source #
Sequence a container using a specified Applicative.
This is like traverseBy where the Traversable instance can be specified by any Traversal
sequenceByOftraverse≡sequenceBy
Implementation Details
newtype Bazaar p a b t Source #
This is used to characterize a Traversal.
a.k.a. indexed Cartesian store comonad, indexed Kleene store comonad, or an indexed FunList.
http://twanvl.nl/blog/haskell/non-regular1
A Bazaar is like a Traversal that has already been applied to some structure.
Where a Context a b ta and a function from b to
 t, a Bazaar a b tN as and a function from N
 bs to t, (where N might be infinite).
Mnemonically, a Bazaar holds many stores and you can easily add more.
This is a final encoding of Bazaar.
Constructors
| Bazaar | |
| Fields 
 | |
Instances
| Corepresentable p => Sellable p (Bazaar p) Source # | |
| Profunctor p => Bizarre p (Bazaar p) Source # | |
| Conjoined p => IndexedComonad (Bazaar p) Source # | |
| IndexedFunctor (Bazaar p) Source # | |
| Functor (Bazaar p a b) Source # | |
| Applicative (Bazaar p a b) Source # | |
| ((~) * a b, Conjoined p) => Comonad (Bazaar p a b) Source # | |
| ((~) * a b, Conjoined p) => ComonadApply (Bazaar p a b) Source # | |
| Apply (Bazaar p a b) Source # | |
newtype Bazaar1 p a b t Source #
This is used to characterize a Traversal.
a.k.a. indexed Cartesian store comonad, indexed Kleene store comonad, or an indexed FunList.
http://twanvl.nl/blog/haskell/non-regular1
A Bazaar1 is like a Traversal that has already been applied to some structure.
Where a Context a b ta and a function from b to
 t, a Bazaar1 a b tN as and a function from N
 bs to t, (where N might be infinite).
Mnemonically, a Bazaar1 holds many stores and you can easily add more.
This is a final encoding of Bazaar1.
Constructors
| Bazaar1 | |
| Fields 
 | |
Instances
| Corepresentable p => Sellable p (Bazaar1 p) Source # | |
| Profunctor p => Bizarre1 p (Bazaar1 p) Source # | |
| Conjoined p => IndexedComonad (Bazaar1 p) Source # | |
| IndexedFunctor (Bazaar1 p) Source # | |
| Functor (Bazaar1 p a b) Source # | |
| ((~) * a b, Conjoined p) => Comonad (Bazaar1 p a b) Source # | |
| ((~) * a b, Conjoined p) => ComonadApply (Bazaar1 p a b) Source # | |
| Apply (Bazaar1 p a b) Source # | |
iloci :: IndexedTraversal i (Bazaar (Indexed i) a c s) (Bazaar (Indexed i) b c s) a b Source #
This IndexedTraversal allows you to traverse the individual stores in
 a Bazaar with access to their indices.
Fusion
confusing :: Applicative f => LensLike (Curried (Yoneda f) (Yoneda f)) s t a b -> LensLike f s t a b Source #
Fuse a Traversal by reassociating all of the \<*\> operations to the
 left and fusing all of the fmap calls into one. This is particularly
 useful when constructing a Traversal using operations from GHC.Generics.
Given a pair of Traversals foo and bar,
confusing (foo.bar) = foo.bar
However, foo and bar are each going to use the Applicative they are given.
confusing exploits the Yoneda lemma to merge their separate uses of fmap into a single fmap.
 and it further exploits an interesting property of the right Kan lift (or Curried) to left associate
 all of the uses of '(*)' to make it possible to fuse together more fmaps.
This is particularly effective when the choice of functor f is unknown at compile
 time or when the Traversal foo.bar in the above description is recursive or complex
 enough to prevent inlining.
fusing is a version of this combinator suitable for fusing lenses.
confusing::Traversals t a b ->Traversals t a b