Portability | Rank2Types |
---|---|
Stability | provisional |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Safe Haskell | Trustworthy |
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
- type Traversal' s a = Traversal 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 ATraversal s t a b = LensLike (Bazaar (->) a b) s t a b
- type ATraversal' s a = ATraversal 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 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
- traverseOf :: Over p f s t a b -> p a (f b) -> s -> f t
- forOf :: Over p f s t a b -> s -> p a (f b) -> f t
- sequenceAOf :: LensLike f s t (f b) b -> s -> f t
- mapMOf :: Profunctor p => Over p (WrappedMonad m) s t a b -> p a (m b) -> s -> m t
- forMOf :: Profunctor p => Over p (WrappedMonad m) s t a b -> s -> p 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 :: Conjoined p => Over p (State acc) s t a b -> p acc (a -> (acc, b)) -> acc -> s -> (acc, t)
- mapAccumROf :: Conjoined p => Over p (Backwards (State acc)) s t a b -> p 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 :: MonadPlus m => LensLike ((,) Any) s t a b -> (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
- 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) => Over p (BazaarT p f a a) s t a a -> Over p f s t a a
- unsafeSingular :: (Conjoined p, Functor f) => Over p (BazaarT p f a b) 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)
- both :: Traversal (a, a) (b, b) a b
- beside :: (Representable q, Applicative (Rep q), Applicative f) => Overloading p q f s t a b -> Overloading p q f s' t' a b -> Overloading p q f (s, s') (t, t') a b
- taking :: (Conjoined p, Applicative f) => Int -> Over p (BazaarT p f a a) 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
- ignored :: Applicative f => pafb -> s -> f s
- class Ord k => TraverseMin k m | m -> k where
- traverseMin :: IndexedTraversal' k (m v) v
- class Ord k => TraverseMax k m | m -> k where
- traverseMax :: IndexedTraversal' k (m v) v
- traversed :: Traversable f => IndexedTraversal 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 :: (Indexed i a (WrappedMonad m b) -> s -> WrappedMonad m t) -> (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)
- 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
- 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
Traversals
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!
type Traversal' s a = Traversal s s a aSource
typeTraversal'
=Simple
Traversal
type IndexedTraversal i s t a b = forall p f. (Indexable i p, Applicative f) => p a (f b) -> s -> f tSource
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.
type IndexedTraversal' i s a = IndexedTraversal i s s a aSource
typeIndexedTraversal'
i =Simple
(IndexedTraversal
i)
type ATraversal s t a b = LensLike (Bazaar (->) a b) s t a bSource
When you see this as an argument to a function, it expects a Traversal
.
type ATraversal' s a = ATraversal s s a aSource
typeATraversal'
=Simple
ATraversal
type AnIndexedTraversal i s t a b = Over (Indexed i) (Bazaar (Indexed i) a b) s t a bSource
When you see this as an argument to a function, it expects an IndexedTraversal
.
type AnIndexedTraversal' i s a = AnIndexedTraversal i s s a aSource
typeAnIndexedTraversal'
=Simple
(AnIndexedTraversal
i)
type Traversing p f s t a b = Over p (BazaarT p f a b) s t a bSource
type Traversing' p f s a = Traversing p f s s a aSource
typeTraversing'
f =Simple
(Traversing
f)
Traversing and Lensing
traverseOf :: Over p f s t a b -> p 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 each print (1,2,3)
1 2 3 ((),(),())
traverseOf
≡id
itraverseOf
l ≡traverseOf
l.
Indexed
This yields the obvious law:
traverse
≡traverseOf
traverse
traverseOf
::Functor
f =>Iso
s t a b -> (a -> f b) -> s -> f ttraverseOf
::Functor
f =>Lens
s t a b -> (a -> f b) -> s -> f ttraverseOf
::Applicative
f =>Traversal
s t a b -> (a -> f b) -> s -> f t
forOf :: Over p f s t a b -> s -> p a (f b) -> f tSource
A version of traverseOf
with the arguments flipped, such that:
>>>
forOf each (1,2,3) print
1 2 3 ((),(),())
This function is only provided for consistency, flip
is strictly more general.
forOf
≡flip
forOf
≡flip
.traverseOf
for
≡forOf
traverse
ifor
l s ≡for
l s.
Indexed
forOf
::Functor
f =>Iso
s t a b -> s -> (a -> f b) -> f tforOf
::Functor
f =>Lens
s t a b -> s -> (a -> f b) -> f tforOf
::Applicative
f =>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.
>>>
sequenceAOf both ([1,2],[3,4])
[(1,3),(1,4),(2,3),(2,4)]
sequenceA
≡sequenceAOf
traverse
≡traverse
id
sequenceAOf
l ≡traverseOf
lid
≡ lid
sequenceAOf
::Functor
f =>Iso
s t (f b) b -> s -> f tsequenceAOf
::Functor
f =>Lens
s t (f b) b -> s -> f tsequenceAOf
::Applicative
f =>Traversal
s t (f b) b -> s -> f t
mapMOf :: Profunctor p => Over p (WrappedMonad m) s t a b -> p 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.
>>>
mapMOf both (\x -> [x, x + 1]) (1,3)
[(1,3),(1,4),(2,3),(2,4)]
mapM
≡mapMOf
traverse
imapMOf
l ≡forM
l.
Indexed
mapMOf
::Monad
m =>Iso
s t a b -> (a -> m b) -> s -> m tmapMOf
::Monad
m =>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 :: Profunctor p => Over p (WrappedMonad m) s t a b -> s -> p a (m b) -> m tSource
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
≡forMOf
traverse
forMOf
l ≡flip
(mapMOf
l)iforMOf
l s ≡forM
l s.
Indexed
forMOf
::Monad
m =>Iso
s t a b -> s -> (a -> m b) -> m tforMOf
::Monad
m =>Lens
s t a b -> s -> (a -> m b) -> m tforMOf
::Monad
m =>Traversal
s t a b -> s -> (a -> m b) -> m t
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.
>>>
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
≡sequenceOf
traverse
sequenceOf
l ≡mapMOf
lid
sequenceOf
l ≡unwrapMonad
.
lWrapMonad
sequenceOf
::Monad
m =>Iso
s t (m b) b -> s -> m tsequenceOf
::Monad
m =>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:
>>>
transposeOf traverse [[1,2,3],[4,5,6]]
[[1,4],[2,5],[3,6]]
transpose
≡transposeOf
traverse
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 :: Conjoined p => Over p (State acc) s t a b -> p 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)
mapAccumLOf
::LensLike
(State
acc) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)mapAccumLOf
l f acc0 s =swap
(runState
(l (a ->state
(acc ->swap
(f acc a))) s) acc0)
mapAccumROf :: Conjoined p => Over p (Backwards (State acc)) s t a b -> p 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)
mapAccumROf
::LensLike
(Backwards
(State
acc)) s t a b -> (acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
Monomorphic Traversals
cloneTraversal :: ATraversal s t a b -> Traversal s t a bSource
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
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 (coerced (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
cloneIndexPreservingTraversal :: ATraversal s t a b -> IndexPreservingTraversal s t a bSource
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 bSource
Clone an IndexedTraversal
yielding an IndexedTraversal
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.
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
::Iso'
s a ->Lens'
s [a]partsOf
::Lens'
s a ->Lens'
s [a]partsOf
::Traversal'
s a ->Lens'
s [a]partsOf
::Fold
s a ->Getter
s [a]partsOf
::Getter
s a ->Getter
s [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
::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' :: 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==
map
pos
(holesOf
l x) propId l x =all
(==
x) [extract
w | w <-holesOf
l 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'
(Indexed
i) a s]holesOf
::IndexedTraversal'
i s a -> s -> [Pretext'
(Indexed
i) a s]
singular :: (Conjoined p, Functor f) => Over p (BazaarT p f a a) s t a a -> Over p f s t a aSource
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
or a non-empty MonadicFold
into an
Action
.
The resulting Lens
, Getter
, or Action
will be partial if the supplied Traversal
returns
no results.
singular
::Traversal
s t a a ->Lens
s t a asingular
::Fold
s a ->Getter
s asingular
::MonadicFold
m s a ->Action
m s asingular
::IndexedTraversal
i s t a a ->IndexedLens
i s t a asingular
::IndexedFold
i s a ->IndexedGetter
i s asingular
::IndexedMonadicFold
i m s a ->IndexedAction
i m s a
unsafeSingular :: (Conjoined p, Functor f) => Over p (BazaarT p f a b) s t a b -> Over p f s t a bSource
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
or a MonadicFold
into an Action
.
The resulting Lens
, Getter
, or Action
will be partial if the Traversal
targets nothing
or more than one element.
unsafeSingular
::Traversal
s t a b ->Lens
s t a bunsafeSingular
::Fold
s a ->Getter
s aunsafeSingular
::MonadicFold
m s a ->Action
m s aunsafeSingular
::IndexedTraversal
i s t a b ->IndexedLens
i s t a bunsafeSingular
::IndexedFold
i s a ->IndexedGetter
i s aunsafeSingular
::IndexedMonadicFold
i m s a ->IndexedAction
i m s a
Common Traversals
class (Functor t, Foldable t) => Traversable t where
traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
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 :: (Representable q, Applicative (Rep q), Applicative f) => Overloading p q f s t a b -> Overloading p q f s' t' a b -> Overloading p q f (s, s') (t, t') a bSource
Apply a different Traversal
or Fold
to each side of a tuple.
beside
::Traversal
s t a b ->Traversal
s' t' a b ->Traversal
(s,s') (t,t') a bbeside
::Lens
s t a b ->Lens
s' t' a b ->Traversal
(s,s') (t,t') a bbeside
::Fold
s a ->Fold
s' a ->Fold
(s,s') abeside
::Getter
s a ->Getter
s' a ->Fold
(s,s') abeside
::Action
m s a ->Action
m s' a ->MonadicFold
m (s,s') abeside
::MonadicFold
m s a ->MonadicFold
m s' a ->MonadicFold
m (s,s') a
beside
::IndexedTraversal
i s t a b ->IndexedTraversal
i s' t' a b ->IndexedTraversal
i (s,s') (t,t') a bbeside
::IndexedLens
i s t a b ->IndexedLens
i s' t' a b ->IndexedTraversal
i (s,s') (t,t') a bbeside
::IndexedFold
i s a ->IndexedFold
i s' a ->IndexedFold
i (s,s') abeside
::IndexedGetter
i s a ->IndexedGetter
i s' a ->IndexedFold
i (s,s') abeside
::IndexedAction
i m s a ->IndexedAction
i m s' a ->IndexedMonadicFold
i m (s,s') abeside
::IndexedMonadicFold
i m s a ->IndexedMonadicFold
i m s' a ->IndexedMonadicFold
i m (s,s') a
beside
::IndexPreservingTraversal
s t a b ->IndexPreservingTraversal
s' t' a b ->IndexPreservingTraversal
(s,s') (t,t') a bbeside
::IndexPreservingLens
s t a b ->IndexPreservingLens
s' t' a b ->IndexPreservingTraversal
(s,s') (t,t') a bbeside
::IndexPreservingFold
s a ->IndexPreservingFold
s' a ->IndexPreservingFold
(s,s') abeside
::IndexPreservingGetter
s a ->IndexPreservingGetter
s' a ->IndexPreservingFold
(s,s') abeside
::IndexPreservingAction
m s a ->IndexPreservingAction
m s' a ->IndexPreservingMonadicFold
m (s,s') abeside
::IndexPreservingMonadicFold
m s a ->IndexPreservingMonadicFold
m s' a ->IndexPreservingMonadicFold
m (s,s') a
>>>
("hello",["world","!!!"])^..beside id traverse
["hello","world","!!!"]
taking :: (Conjoined p, Applicative f) => Int -> Over p (BazaarT p f a a) s t a a -> Over p f s t a aSource
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
->Getter
s a ->Fold
s ataking
::Int
->Fold
s a ->Fold
s ataking
::Int
->Action
m s a ->MonadicFold
m s ataking
::Int
->MonadicFold
m s a ->MonadicFold
m s ataking
::Int
->IndexedTraversal'
i s a ->IndexedTraversal'
i s ataking
::Int
->IndexedLens'
i s a ->IndexedTraversal'
i s ataking
::Int
->IndexedGetter
i s a ->IndexedFold
i s ataking
::Int
->IndexedFold
i s a ->IndexedFold
i s ataking
::Int
->IndexedAction
i m s a ->IndexedMonadicFold
i m s ataking
::Int
->IndexedMonadicFold
i m s a ->IndexedMonadicFold
i m s a
dropping :: (Conjoined p, Applicative f) => Int -> Over p (Indexing f) s t a a -> Over p f s t a aSource
Visit all but the first n targets of a Traversal
, Fold
, Getter
or Lens
.
>>>
("hello","world") ^? dropping 1 both
Just "world"
Dropping works on infinite traversals as well:
>>>
[1..] ^? dropping 1 folded
Just 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
->Getter
s a ->Fold
s adropping
::Int
->Fold
s a ->Fold
s adropping
::Int
->Action
m s a ->MonadicFold
m s adropping
::Int
->MonadicFold
m s a ->MonadicFold
m s adropping
::Int
->IndexedTraversal'
i s a ->IndexedTraversal'
i s adropping
::Int
->IndexedLens'
i s a ->IndexedTraversal'
i s adropping
::Int
->IndexedGetter
i s a ->IndexedFold
i s adropping
::Int
->IndexedFold
i s a ->IndexedFold
i s adropping
::Int
->IndexedAction
i m s a ->IndexedMonadicFold
i m s adropping
::Int
->IndexedMonadicFold
i m s a ->IndexedMonadicFold
i m s a
Indexed Traversals
Common
ignored :: Applicative f => pafb -> s -> f sSource
This is the trivial empty Traversal
.
ignored
::IndexedTraversal
i s s a b
ignored
≡const
pure
>>>
6 & ignored %~ absurd
6
class Ord k => TraverseMin k m | m -> k whereSource
Allows IndexedTraversal
the value at the smallest index.
traverseMin :: IndexedTraversal' k (m v) vSource
IndexedTraversal
of the element with the smallest index.
TraverseMin Int IntMap | |
Ord k => TraverseMin k (Map k) |
class Ord k => TraverseMax k m | m -> k whereSource
Allows IndexedTraversal
of the value at the largest index.
traverseMax :: IndexedTraversal' k (m v) vSource
IndexedTraversal
of the element at the largest index.
TraverseMax Int IntMap | |
Ord k => TraverseMax k (Map k) |
traversed :: Traversable f => IndexedTraversal Int (f a) (f b) a bSource
Traverse any Traversable
container. This is an IndexedTraversal
that is indexed by ordinal position.
traversed64 :: Traversable f => IndexedTraversal Int64 (f a) (f b) a bSource
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 aSource
Traverse the nth element 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) 1
Just 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'
Int
s aelementOf
::Fold
s a ->Int
->IndexedFold
Int
s a
element :: Traversable t => Int -> IndexedTraversal' Int (t a) aSource
Traverse the nth element of a Traversable
container.
element
≡elementOf
traverse
elementsOf :: Applicative f => LensLike (Indexing f) s t a a -> (Int -> Bool) -> IndexedLensLike Int f s t a aSource
Traverse (or fold) selected elements of a Traversal
(or Fold
) where their ordinal positions match a predicate.
elementsOf
::Traversal'
s a -> (Int
->Bool
) ->IndexedTraversal'
Int
s aelementsOf
::Fold
s a -> (Int
->Bool
) ->IndexedFold
Int
s a
elements :: Traversable t => (Int -> Bool) -> IndexedTraversal' Int (t a) aSource
Traverse elements of a Traversable
container where their ordinal positions matches a predicate.
elements
≡elementsOf
traverse
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 tSource
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
≡withIndex
traverseOf
l =itraverseOf
l.
const
=id
itraverseOf
::Functor
f =>IndexedLens
i s t a b -> (i -> a -> f b) -> s -> f titraverseOf
::Applicative
f =>IndexedTraversal
i 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 tSource
Traverse with an index (and the arguments flipped).
forOf
l a ≡iforOf
l a.
const
iforOf
≡flip
.
itraverseOf
iforOf
::Functor
f =>IndexedLens
i s t a b -> s -> (i -> a -> f b) -> f tiforOf
::Applicative
f =>IndexedTraversal
i s t a b -> s -> (i -> a -> f b) -> f t
imapMOf :: (Indexed i a (WrappedMonad m b) -> s -> WrappedMonad m t) -> (i -> 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, with access
its position.
When you don't need access to the index mapMOf
is more liberal in what it can accept.
mapMOf
l ≡imapMOf
l.
const
imapMOf
::Monad
m =>IndexedLens
i s t a b -> (i -> a -> m b) -> s -> m timapMOf
::Monad
m =>IndexedTraversal
i 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 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, with access
its position (and the arguments flipped).
forMOf
l a ≡iforMOf
l a.
const
iforMOf
≡flip
.
imapMOf
iforMOf
::Monad
m =>IndexedLens
i s t a b -> s -> (i -> a -> m b) -> m tiforMOf
::Monad
m =>IndexedTraversal
i 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.
mapAccumROf
l ≡imapAccumROf
l.
const
imapAccumROf
::IndexedLens
i s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)imapAccumROf
::IndexedTraversal
i 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.
mapAccumLOf
l ≡imapAccumLOf
l.
const
imapAccumLOf
::IndexedLens
i s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)imapAccumLOf
::IndexedTraversal
i s t a b -> (i -> acc -> a -> (acc, b)) -> acc -> s -> (acc, t)
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
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 Bazaar
a b tN
a
s and a function from N
b
s 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
.
Corepresentable p => Sellable p (Bazaar p) | |
Profunctor p => Bizarre p (Bazaar p) | |
Conjoined p => IndexedComonad (Bazaar p) | |
IndexedFunctor (Bazaar p) | |
Functor (Bazaar p a b) | |
Applicative (Bazaar p a b) | |
(~ * a b, Conjoined p) => Comonad (Bazaar p a b) | |
(~ * a b, Conjoined p) => ComonadApply (Bazaar p a b) | |
Apply (Bazaar p a b) |
iloci :: IndexedTraversal i (Bazaar (Indexed i) a c s) (Bazaar (Indexed i) b c s) a bSource
This IndexedTraversal
allows you to traverse
the individual stores in
a Bazaar
with access to their indices.