Portability | Rank2Types |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Safe-Inferred |
A
is a generalization of 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
:: (Traversable
t,Applicative
f) => (a -> f b) -> t a -> f (t b)
we monomorphize the contents and result to obtain
typeTraversal
s t a b = forall f.Applicative
f => (a -> f b) -> s -> f t
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 (
. Everything you know how to do with a Const
m)Traversable
container, you can with 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
- 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 (Backwards (State acc)) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
- mapAccumROf :: LensLike (State acc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
- scanr1Of :: LensLike (State (Maybe a)) s t a a -> (a -> a -> a) -> s -> t
- scanl1Of :: LensLike (Backwards (State (Maybe a))) s t a a -> (a -> a -> a) -> s -> t
- partsOf :: Functor f => LensLike (BazaarT a a f) s t a a -> LensLike f s t [a] [a]
- partsOf' :: LensLike (Bazaar a a) s t a a -> Lens s t [a] [a]
- unsafePartsOf :: Functor f => LensLike (BazaarT a b f) s t a b -> LensLike f s t [a] [b]
- unsafePartsOf' :: LensLike (Bazaar a b) s t a b -> Lens s t [a] [b]
- holesOf :: LensLike (Bazaar a a) s t a a -> s -> [Context a a t]
- class (Functor t, Foldable t) => Traversable t where
- traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
- _left :: Traversal (Either a c) (Either b c) a b
- _right :: Traversal (Either c a) (Either c b) a b
- both :: Traversal (a, a) (b, b) a b
- beside :: Applicative f => LensLike f s t a b -> LensLike f s' t' a b -> LensLike f (s, s') (t, t') a b
- taking :: Applicative f => Int -> SimpleLensLike (BazaarT a a f) s a -> SimpleLensLike f s a
- dropping :: Applicative f => Int -> SimpleLensLike (Indexing f) s a -> SimpleLensLike f s a
- cloneTraversal :: Applicative f => ((a -> Bazaar a b b) -> s -> Bazaar a b t) -> (a -> f b) -> s -> f t
- data ReifiedTraversal s t a b = ReifyTraversal {
- reflectTraversal :: Traversal s t a b
- type SimpleTraversal s a = Traversal s s a a
- type SimpleReifiedTraversal s a = ReifiedTraversal s s a a
- newtype Bazaar a b t = Bazaar {
- runBazaar :: forall f. Applicative f => (a -> f b) -> f t
Lenses
type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f tSource
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".
tpure
≡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!
Traversing and Lensing
traverseOf :: LensLike f s t a b -> (a -> f b) -> s -> f tSource
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
≡id
This yields the obvious law:
traverse
≡traverseOf
traverse
traverseOf
::Iso
s t a b -> (a -> f b) -> s -> f ttraverseOf
::Lens
s t a b -> (a -> f b) -> s -> f ttraverseOf
::Traversal
s t a b -> (a -> f b) -> s -> f t
forOf :: LensLike f s t a b -> s -> (a -> f b) -> f tSource
A version of traverseOf
with the arguments flipped, such that:
forOf
l ≡flip
(traverseOf
l)
for
≡forOf
traverse
This function is only provided for consistency, flip
is strictly more general.
forOf
≡flip
forOf
::Iso
s t a b -> s -> (a -> f b) -> f tforOf
::Lens
s t a b -> s -> (a -> f b) -> f tforOf
::Traversal
s t a b -> s -> (a -> f b) -> f t
sequenceAOf :: LensLike f s t (f b) b -> s -> f tSource
Evaluate each action in the structure from left to right, and collect the results.
sequenceA
≡sequenceAOf
traverse
≡traverse
id
sequenceAOf
l ≡traverseOf
l id ≡ l id
sequenceAOf
::Iso
s t (f b) b -> s -> f tsequenceAOf
::Lens
s t (f b) b -> s -> f tsequenceAOf
::Applicative
f =>Traversal
s t (f b) b -> s -> f t
mapMOf :: LensLike (WrappedMonad m) s t a b -> (a -> m b) -> s -> m tSource
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
s t a b -> (a -> m b) -> s -> m tmapMOf
::Lens
s t a b -> (a -> m b) -> s -> m tmapMOf
::Monad
m =>Traversal
s t a b -> (a -> m b) -> s -> m t
forMOf :: LensLike (WrappedMonad m) s t a b -> s -> (a -> m b) -> m tSource
sequenceOf :: LensLike (WrappedMonad m) s t (m b) b -> s -> m tSource
Sequence the (monadic) effects targeted by a lens in a container from left to right.
sequence
≡sequenceOf
traverse
sequenceOf
l ≡mapMOf
l idsequenceOf
l ≡unwrapMonad
. lWrapMonad
sequenceOf
::Iso
s t (m b) b -> s -> m tsequenceOf
::Lens
s t (m b) b -> s -> m tsequenceOf
::Monad
m =>Traversal
s 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:
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 acc)) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)Source
This generalizes mapAccumL
to an arbitrary Traversal
.
mapAccumL
≡mapAccumLOf
traverse
mapAccumLOf
accumulates state from left to right.
mapAccumLOf
::Iso
s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)mapAccumLOf
::Lens
s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)mapAccumLOf
::Traversal
s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
mapAccumROf :: LensLike (State acc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)Source
This generalizes mapAccumR
to an arbitrary Traversal
.
mapAccumR
≡mapAccumROf
traverse
mapAccumROf
accumulates state from right to left.
mapAccumROf
::Iso
s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)mapAccumROf
::Lens
s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)mapAccumROf
::Traversal
s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
Parts and Holes
partsOf :: Functor f => LensLike (BazaarT a a 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.
Any extras will be lost. If you do not supply enough, then the remainder will come from the original structure.
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
::Simple
Iso
s a ->Simple
Lens
s [a]partsOf
::Simple
Lens
s a ->Simple
Lens
s [a]partsOf
::Simple
Traversal
s a ->Simple
Lens
s [a]partsOf
::Fold
s a ->Getter
s [a]partsOf
::Getter
s a ->Getter
s [a]
unsafePartsOf :: Functor f => LensLike (BazaarT a b 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
::Iso
s t a b ->Lens
s t [a] [b]unsafePartsOf
::Lens
s t a b ->Lens
s t [a] [b]unsafePartsOf
::Traversal
s t a b ->Lens
s t [a] [b]unsafePartsOf
::Fold
s a ->Getter
s [a]unsafePartsOf
::Getter
s a ->Getter
s [a]
unsafePartsOf' :: LensLike (Bazaar a b) s t a b -> Lens s t [a] [b]Source
holesOf :: LensLike (Bazaar a a) s t a a -> s -> [Context 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==
map
pos
(holesOf
l x) propId l x =all
(==
x) [extract w | w <-holesOf
l x]
holesOf
::Simple
Iso
s a -> s -> [Context
a a s]holesOf
::Simple
Lens
s a -> s -> [Context
a a s]holesOf
::Simple
Traversal
s a -> s -> [Context
a a s]
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:
- In the
Functor
instance,fmap
should be equivalent to traversal with the identity applicative functor (fmapDefault
). - In the
Foldable
instance,foldMap
should be equivalent to traversal with a constant applicative functor (foldMapDefault
).
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.
_left :: Traversal (Either a c) (Either b c) a bSource
A traversal for tweaking the left-hand value of an Either
:
>>>
over _left (+1) (Left 2)
Left 3
>>>
over _left (+1) (Right 2)
Right 2
>>>
Right 42 ^._left :: String
""
>>>
Left "hello" ^._left
"hello"
_left ::Applicative
f => (a -> f b) ->Either
a c -> f (Either
b c)
_right :: Traversal (Either c a) (Either c b) a bSource
traverse the right-hand value of an Either
:
_right
≡traverse
Unfortunately the instance for
is still missing from base,
so this can't just be Traversable
(Either
c)traverse
>>>
over _right (+1) (Left 2)
Left 2
>>>
over _right (+1) (Right 2)
Right 3
>>>
Right "hello" ^._right
"hello"
>>>
Left "hello" ^._right :: [Double]
[]
_right ::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.
>>>
both *~ 10 $ (1,2)
(10,20)
>>>
over both length ("hello","world")
(5,5)
>>>
("hello","world")^.both
"helloworld"
beside :: Applicative f => LensLike f s t a b -> LensLike f s' t' a b -> LensLike f (s, s') (t, t') a bSource
taking :: Applicative f => Int -> SimpleLensLike (BazaarT a a f) s a -> SimpleLensLike f s aSource
dropping :: Applicative f => Int -> SimpleLensLike (Indexing f) s a -> SimpleLensLike f s aSource
Cloning Traversals
cloneTraversal :: Applicative f => ((a -> Bazaar a b b) -> s -> Bazaar a b t) -> (a -> f b) -> s -> f tSource
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 ReifyTraversal
and use reflectTraversal
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 (cloneTraversal l) a, set (cloneTraversal l) 10 a)
>>>
foo both ("hello","world")
("helloworld",(10,10))
cloneTraversal
::LensLike
(Bazaar
a b) s t a b ->Traversal
s t a b
data ReifiedTraversal s t a b Source
A form of Traversal
that can be stored monomorphically in a container.
ReifyTraversal | |
|
Simple
type SimpleTraversal s a = Traversal s s a aSource
type SimpleReifiedTraversal s a = ReifiedTraversal s s a aSource
type SimpleReifiedTraversal =Simple
ReifiedTraversal
Exposed Implementation Details
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
is isomorphic to Bazaar
a b tdata Bazaar a b t = Buy t | Trade (Bazaar a b (b -> t)) a
,
and to exists s. (s,
.
Traversal
s t a b)
A Bazaar
is like a Traversal
that has already been applied to some structure.
Where a
holds an Context
a b ta
and a function from b
to
t
, a
holds N Bazaar
a b ta
s and a function from N
b
s to t
.
Mnemonically, a Bazaar
holds many stores and you can easily add more.
This is a final encoding of Bazaar
.
Bazaar | |
|