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 | Haskell2010 |
A
is a generalization of something Fold
s aFoldable
. It allows
you to extract multiple results from a container. A Foldable
container
can be characterized by the behavior of
.
Since we want to be able to work with monomorphic containers, we could
generalize this signature to foldMap
:: (Foldable
t, Monoid
m) => (a -> m) -> t a -> mforall m.
,
and then decorate it with Monoid
m => (a -> m) -> s -> mConst
to obtain
typeFold
s a = forall m.Monoid
m =>Getting
m s a
Every Getter
is a valid Fold
that simply doesn't use the Monoid
it is passed.
In practice the type we use is slightly more complicated to allow for
better error messages and for it to be transformed by certain
Applicative
transformers.
Everything you can do with a Foldable
container, you can with with a Fold
and there are
combinators that generalize the usual Foldable
operations here.
Synopsis
- type Fold s a = forall (f :: Type -> Type). (Contravariant f, Applicative f) => (a -> f a) -> s -> f s
- type IndexedFold i s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Contravariant f, Applicative f) => p a (f a) -> s -> f s
- (^..) :: s -> Getting (Endo [a]) s a -> [a]
- (^?) :: s -> Getting (First a) s a -> Maybe a
- (^?!) :: HasCallStack => s -> Getting (Endo a) s a -> a
- pre :: Getting (First a) s a -> IndexPreservingGetter s (Maybe a)
- ipre :: IndexedGetting i (First (i, a)) s a -> IndexPreservingGetter s (Maybe (i, a))
- preview :: MonadReader s m => Getting (First a) s a -> m (Maybe a)
- previews :: MonadReader s m => Getting (First r) s a -> (a -> r) -> m (Maybe r)
- ipreview :: MonadReader s m => IndexedGetting i (First (i, a)) s a -> m (Maybe (i, a))
- ipreviews :: MonadReader s m => IndexedGetting i (First r) s a -> (i -> a -> r) -> m (Maybe r)
- preuse :: MonadState s m => Getting (First a) s a -> m (Maybe a)
- preuses :: MonadState s m => Getting (First r) s a -> (a -> r) -> m (Maybe r)
- ipreuse :: MonadState s m => IndexedGetting i (First (i, a)) s a -> m (Maybe (i, a))
- ipreuses :: MonadState s m => IndexedGetting i (First r) s a -> (i -> a -> r) -> m (Maybe r)
- has :: Getting Any s a -> s -> Bool
- hasn't :: Getting All s a -> s -> Bool
- folding :: Foldable f => (s -> f a) -> Fold s a
- ifolding :: (Foldable f, Indexable i p, Contravariant g, Applicative g) => (s -> f (i, a)) -> Over p g s t a b
- foldring :: (Contravariant f, Applicative f) => ((a -> f a -> f a) -> f a -> s -> f a) -> LensLike f s t a b
- ifoldring :: (Indexable i p, Contravariant f, Applicative f) => ((i -> a -> f a -> f a) -> f a -> s -> f a) -> Over p f s t a b
- folded :: forall (f :: Type -> Type) a. Foldable f => IndexedFold Int (f a) a
- folded64 :: forall (f :: Type -> Type) a. Foldable f => IndexedFold Int64 (f a) a
- unfolded :: (b -> Maybe (a, b)) -> Fold b a
- iterated :: Apply f => (a -> a) -> LensLike' f a a
- filtered :: (Choice p, Applicative f) => (a -> Bool) -> Optic' p f a a
- filteredBy :: (Indexable i p, Applicative f) => Getting (First i) a i -> p a (f a) -> a -> f a
- backwards :: (Profunctor p, Profunctor q) => Optical p q (Backwards f) s t a b -> Optical p q f s t a b
- repeated :: Apply f => LensLike' f a a
- replicated :: Int -> Fold a a
- cycled :: Apply f => LensLike f s t a b -> LensLike f s t a b
- takingWhile :: (Conjoined p, Applicative f) => (a -> Bool) -> Over p (TakingWhile p f a a) s t a a -> Over p f s t a a
- droppingWhile :: (Conjoined p, Profunctor q, Applicative f) => (a -> Bool) -> Optical p q (Compose (State Bool) f) s t a a -> Optical p q f s t a a
- worded :: forall (f :: Type -> Type). Applicative f => IndexedLensLike' Int f String String
- lined :: forall (f :: Type -> Type). Applicative f => IndexedLensLike' Int f String String
- foldMapOf :: Getting r s a -> (a -> r) -> s -> r
- foldOf :: Getting a s a -> s -> a
- foldrOf :: Getting (Endo r) s a -> (a -> r -> r) -> r -> s -> r
- foldlOf :: Getting (Dual (Endo r)) s a -> (r -> a -> r) -> r -> s -> r
- toListOf :: Getting (Endo [a]) s a -> s -> [a]
- toNonEmptyOf :: Getting (NonEmptyDList a) s a -> s -> NonEmpty a
- altOf :: Applicative f => Getting (Alt f a) s a -> s -> f a
- anyOf :: Getting Any s a -> (a -> Bool) -> s -> Bool
- allOf :: Getting All s a -> (a -> Bool) -> s -> Bool
- noneOf :: Getting Any s a -> (a -> Bool) -> s -> Bool
- andOf :: Getting All s Bool -> s -> Bool
- orOf :: Getting Any s Bool -> s -> Bool
- productOf :: Num a => Getting (Endo (Endo a)) s a -> s -> a
- sumOf :: Num a => Getting (Endo (Endo a)) s a -> s -> a
- traverseOf_ :: Functor f => Getting (Traversed r f) s a -> (a -> f r) -> s -> f ()
- forOf_ :: Functor f => Getting (Traversed r f) s a -> s -> (a -> f r) -> f ()
- sequenceAOf_ :: Functor f => Getting (Traversed a f) s (f a) -> s -> f ()
- traverse1Of_ :: Functor f => Getting (TraversedF r f) s a -> (a -> f r) -> s -> f ()
- for1Of_ :: Functor f => Getting (TraversedF r f) s a -> s -> (a -> f r) -> f ()
- sequence1Of_ :: Functor f => Getting (TraversedF a f) s (f a) -> s -> f ()
- mapMOf_ :: Monad m => Getting (Sequenced r m) s a -> (a -> m r) -> s -> m ()
- forMOf_ :: Monad m => Getting (Sequenced r m) s a -> s -> (a -> m r) -> m ()
- sequenceOf_ :: Monad m => Getting (Sequenced a m) s (m a) -> s -> m ()
- asumOf :: Alternative f => Getting (Endo (f a)) s (f a) -> s -> f a
- msumOf :: MonadPlus m => Getting (Endo (m a)) s (m a) -> s -> m a
- concatMapOf :: Getting [r] s a -> (a -> [r]) -> s -> [r]
- concatOf :: Getting [r] s [r] -> s -> [r]
- elemOf :: Eq a => Getting Any s a -> a -> s -> Bool
- notElemOf :: Eq a => Getting All s a -> a -> s -> Bool
- lengthOf :: Getting (Endo (Endo Int)) s a -> s -> Int
- nullOf :: Getting All s a -> s -> Bool
- notNullOf :: Getting Any s a -> s -> Bool
- firstOf :: Getting (Leftmost a) s a -> s -> Maybe a
- first1Of :: Getting (First a) s a -> s -> a
- lastOf :: Getting (Rightmost a) s a -> s -> Maybe a
- last1Of :: Getting (Last a) s a -> s -> a
- maximumOf :: Ord a => Getting (Endo (Endo (Maybe a))) s a -> s -> Maybe a
- maximum1Of :: Ord a => Getting (Max a) s a -> s -> a
- minimumOf :: Ord a => Getting (Endo (Endo (Maybe a))) s a -> s -> Maybe a
- minimum1Of :: Ord a => Getting (Min a) s a -> s -> a
- maximumByOf :: Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> Ordering) -> s -> Maybe a
- minimumByOf :: Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> Ordering) -> s -> Maybe a
- findOf :: Getting (Endo (Maybe a)) s a -> (a -> Bool) -> s -> Maybe a
- findMOf :: Monad m => Getting (Endo (m (Maybe a))) s a -> (a -> m Bool) -> s -> m (Maybe a)
- foldrOf' :: Getting (Dual (Endo (Endo r))) s a -> (a -> r -> r) -> r -> s -> r
- foldlOf' :: Getting (Endo (Endo r)) s a -> (r -> a -> r) -> r -> s -> r
- foldr1Of :: HasCallStack => Getting (Endo (Maybe a)) s a -> (a -> a -> a) -> s -> a
- foldl1Of :: HasCallStack => Getting (Dual (Endo (Maybe a))) s a -> (a -> a -> a) -> s -> a
- foldr1Of' :: HasCallStack => Getting (Dual (Endo (Endo (Maybe a)))) s a -> (a -> a -> a) -> s -> a
- foldl1Of' :: HasCallStack => Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> a) -> s -> a
- foldrMOf :: Monad m => Getting (Dual (Endo (r -> m r))) s a -> (a -> r -> m r) -> r -> s -> m r
- foldlMOf :: Monad m => Getting (Endo (r -> m r)) s a -> (r -> a -> m r) -> r -> s -> m r
- lookupOf :: Eq k => Getting (Endo (Maybe v)) s (k, v) -> k -> s -> Maybe v
- (^@..) :: s -> IndexedGetting i (Endo [(i, a)]) s a -> [(i, a)]
- (^@?) :: s -> IndexedGetting i (Endo (Maybe (i, a))) s a -> Maybe (i, a)
- (^@?!) :: HasCallStack => s -> IndexedGetting i (Endo (i, a)) s a -> (i, a)
- ifoldMapOf :: IndexedGetting i m s a -> (i -> a -> m) -> s -> m
- ifoldrOf :: IndexedGetting i (Endo r) s a -> (i -> a -> r -> r) -> r -> s -> r
- ifoldlOf :: IndexedGetting i (Dual (Endo r)) s a -> (i -> r -> a -> r) -> r -> s -> r
- ianyOf :: IndexedGetting i Any s a -> (i -> a -> Bool) -> s -> Bool
- iallOf :: IndexedGetting i All s a -> (i -> a -> Bool) -> s -> Bool
- inoneOf :: IndexedGetting i Any s a -> (i -> a -> Bool) -> s -> Bool
- itraverseOf_ :: Functor f => IndexedGetting i (Traversed r f) s a -> (i -> a -> f r) -> s -> f ()
- iforOf_ :: Functor f => IndexedGetting i (Traversed r f) s a -> s -> (i -> a -> f r) -> f ()
- imapMOf_ :: Monad m => IndexedGetting i (Sequenced r m) s a -> (i -> a -> m r) -> s -> m ()
- iforMOf_ :: Monad m => IndexedGetting i (Sequenced r m) s a -> s -> (i -> a -> m r) -> m ()
- iconcatMapOf :: IndexedGetting i [r] s a -> (i -> a -> [r]) -> s -> [r]
- ifindOf :: IndexedGetting i (Endo (Maybe a)) s a -> (i -> a -> Bool) -> s -> Maybe a
- ifindMOf :: Monad m => IndexedGetting i (Endo (m (Maybe a))) s a -> (i -> a -> m Bool) -> s -> m (Maybe a)
- ifoldrOf' :: IndexedGetting i (Dual (Endo (r -> r))) s a -> (i -> a -> r -> r) -> r -> s -> r
- ifoldlOf' :: IndexedGetting i (Endo (r -> r)) s a -> (i -> r -> a -> r) -> r -> s -> r
- ifoldrMOf :: Monad m => IndexedGetting i (Dual (Endo (r -> m r))) s a -> (i -> a -> r -> m r) -> r -> s -> m r
- ifoldlMOf :: Monad m => IndexedGetting i (Endo (r -> m r)) s a -> (i -> r -> a -> m r) -> r -> s -> m r
- itoListOf :: IndexedGetting i (Endo [(i, a)]) s a -> s -> [(i, a)]
- elemIndexOf :: Eq a => IndexedGetting i (First i) s a -> a -> s -> Maybe i
- elemIndicesOf :: Eq a => IndexedGetting i (Endo [i]) s a -> a -> s -> [i]
- findIndexOf :: IndexedGetting i (First i) s a -> (a -> Bool) -> s -> Maybe i
- findIndicesOf :: IndexedGetting i (Endo [i]) s a -> (a -> Bool) -> s -> [i]
- ifiltered :: (Indexable i p, Applicative f) => (i -> a -> Bool) -> Optical' p (Indexed i) f a a
- itakingWhile :: (Indexable i p, Profunctor q, Contravariant f, Applicative f) => (i -> a -> Bool) -> Optical' (Indexed i) q (Const (Endo (f s)) :: Type -> Type) s a -> Optical' p q f s a
- idroppingWhile :: (Indexable i p, Profunctor q, Applicative f) => (i -> a -> Bool) -> Optical (Indexed i) q (Compose (State Bool) f) s t a a -> Optical p q f s t a a
- data Leftmost a
- data Rightmost a
- data Traversed a (f :: Type -> Type)
- data Sequenced a (m :: Type -> Type)
- foldBy :: Foldable t => (a -> a -> a) -> a -> t a -> a
- foldByOf :: Fold s a -> (a -> a -> a) -> a -> s -> a
- foldMapBy :: Foldable t => (r -> r -> r) -> r -> (a -> r) -> t a -> r
- foldMapByOf :: Fold s a -> (r -> r -> r) -> r -> (a -> r) -> s -> r
Folds
type Fold s a = forall (f :: Type -> Type). (Contravariant f, Applicative f) => (a -> f a) -> s -> f s Source #
A Fold
describes how to retrieve multiple values in a way that can be composed
with other LensLike
constructions.
A
provides a structure with operations very similar to those of the Fold
s aFoldable
typeclass, see foldMapOf
and the other Fold
combinators.
By convention, if there exists a foo
method that expects a
, then there should be a
Foldable
(f a)fooOf
method that takes a
and a value of type Fold
s as
.
A Getter
is a legal Fold
that just ignores the supplied Monoid
.
Unlike a Traversal
a Fold
is read-only. Since a Fold
cannot be used to write back
there are no Lens
laws that apply.
type IndexedFold i s a = forall (p :: Type -> Type -> Type) (f :: Type -> Type). (Indexable i p, Contravariant f, Applicative f) => p a (f a) -> s -> f s Source #
Every IndexedFold
is a valid Fold
and can be used for Getting
.
Getting Started
(^..) :: s -> Getting (Endo [a]) s a -> [a] infixl 8 Source #
A convenient infix (flipped) version of toListOf
.
>>>
[[1,2],[3]]^..id
[[[1,2],[3]]]>>>
[[1,2],[3]]^..traverse
[[1,2],[3]]>>>
[[1,2],[3]]^..traverse.traverse
[1,2,3]
>>>
(1,2)^..both
[1,2]
toList
xs ≡ xs^..
folded
(^..
) ≡flip
toListOf
(^..
) :: s ->Getter
s a -> a :: s ->Fold
s a -> a :: s ->Lens'
s a -> a :: s ->Iso'
s a -> a :: s ->Traversal'
s a -> a :: s ->Prism'
s a -> [a]
(^?) :: s -> Getting (First a) s a -> Maybe a infixl 8 Source #
Perform a safe head
of a Fold
or Traversal
or retrieve Just
the result
from a Getter
or Lens
.
When using a Traversal
as a partial Lens
, or a Fold
as a partial Getter
this can be a convenient
way to extract the optional value.
Note: if you get stack overflows due to this, you may want to use firstOf
instead, which can deal
more gracefully with heavily left-biased trees. This is because ^?
works by using the
First
monoid, which can occasionally cause space leaks.
>>>
Left 4 ^?_Left
Just 4
>>>
Right 4 ^?_Left
Nothing
>>>
"world" ^? ix 3
Just 'l'
>>>
"world" ^? ix 20
Nothing
This operator works as an infix version of preview
.
(^?
) ≡flip
preview
It may be helpful to think of ^?
as having one of the following
more specialized types:
(^?
) :: s ->Getter
s a ->Maybe
a (^?
) :: s ->Fold
s a ->Maybe
a (^?
) :: s ->Lens'
s a ->Maybe
a (^?
) :: s ->Iso'
s a ->Maybe
a (^?
) :: s ->Traversal'
s a ->Maybe
a
pre :: Getting (First a) s a -> IndexPreservingGetter s (Maybe a) Source #
This converts a Fold
to a IndexPreservingGetter
that returns the first element, if it
exists, as a Maybe
.
pre
::Getter
s a ->IndexPreservingGetter
s (Maybe
a)pre
::Fold
s a ->IndexPreservingGetter
s (Maybe
a)pre
::Traversal'
s a ->IndexPreservingGetter
s (Maybe
a)pre
::Lens'
s a ->IndexPreservingGetter
s (Maybe
a)pre
::Iso'
s a ->IndexPreservingGetter
s (Maybe
a)pre
::Prism'
s a ->IndexPreservingGetter
s (Maybe
a)
ipre :: IndexedGetting i (First (i, a)) s a -> IndexPreservingGetter s (Maybe (i, a)) Source #
This converts an IndexedFold
to an IndexPreservingGetter
that returns the first index
and element, if they exist, as a Maybe
.
ipre
::IndexedGetter
i s a ->IndexPreservingGetter
s (Maybe
(i, a))ipre
::IndexedFold
i s a ->IndexPreservingGetter
s (Maybe
(i, a))ipre
::IndexedTraversal'
i s a ->IndexPreservingGetter
s (Maybe
(i, a))ipre
::IndexedLens'
i s a ->IndexPreservingGetter
s (Maybe
(i, a))
preview :: MonadReader s m => Getting (First a) s a -> m (Maybe a) Source #
Retrieve the first value targeted by a Fold
or Traversal
(or Just
the result
from a Getter
or Lens
). See also firstOf
and ^?
, which are similar with
some subtle differences (explained below).
listToMaybe
.
toList
≡preview
folded
preview
=view
.
pre
Unlike ^?
, this function uses a
MonadReader
to read the value to be focused in on.
This allows one to pass the value as the last argument by using the
MonadReader
instance for (->) s
However, it may also be used as part of some deeply nested transformer stack.
preview
uses a monoidal value to obtain the result.
This means that it generally has good performance, but can occasionally cause space leaks
or even stack overflows on some data types.
There is another function, firstOf
, which avoids these issues at the cost of
a slight constant performance cost and a little less flexibility.
It may be helpful to think of preview
as having one of the following
more specialized types:
preview
::Getter
s a -> s ->Maybe
apreview
::Fold
s a -> s ->Maybe
apreview
::Lens'
s a -> s ->Maybe
apreview
::Iso'
s a -> s ->Maybe
apreview
::Traversal'
s a -> s ->Maybe
a
preview
::MonadReader
s m =>Getter
s a -> m (Maybe
a)preview
::MonadReader
s m =>Fold
s a -> m (Maybe
a)preview
::MonadReader
s m =>Lens'
s a -> m (Maybe
a)preview
::MonadReader
s m =>Iso'
s a -> m (Maybe
a)preview
::MonadReader
s m =>Traversal'
s a -> m (Maybe
a)
ipreview :: MonadReader s m => IndexedGetting i (First (i, a)) s a -> m (Maybe (i, a)) Source #
Retrieve the first index and value targeted by a Fold
or Traversal
(or Just
the result
from a Getter
or Lens
). See also (^@?
).
ipreview
=view
.
ipre
This is usually applied in the Reader
Monad
(->) s
.
ipreview
::IndexedGetter
i s a -> s ->Maybe
(i, a)ipreview
::IndexedFold
i s a -> s ->Maybe
(i, a)ipreview
::IndexedLens'
i s a -> s ->Maybe
(i, a)ipreview
::IndexedTraversal'
i s a -> s ->Maybe
(i, a)
However, it may be useful to think of its full generality when working with
a Monad
transformer stack:
ipreview
::MonadReader
s m =>IndexedGetter
s a -> m (Maybe
(i, a))ipreview
::MonadReader
s m =>IndexedFold
s a -> m (Maybe
(i, a))ipreview
::MonadReader
s m =>IndexedLens'
s a -> m (Maybe
(i, a))ipreview
::MonadReader
s m =>IndexedTraversal'
s a -> m (Maybe
(i, a))
ipreviews :: MonadReader s m => IndexedGetting i (First r) s a -> (i -> a -> r) -> m (Maybe r) Source #
Retrieve a function of the first index and value targeted by an IndexedFold
or
IndexedTraversal
(or Just
the result from an IndexedGetter
or IndexedLens
).
See also (^@?
).
ipreviews
=views
.
ipre
This is usually applied in the Reader
Monad
(->) s
.
ipreviews
::IndexedGetter
i s a -> (i -> a -> r) -> s ->Maybe
ripreviews
::IndexedFold
i s a -> (i -> a -> r) -> s ->Maybe
ripreviews
::IndexedLens'
i s a -> (i -> a -> r) -> s ->Maybe
ripreviews
::IndexedTraversal'
i s a -> (i -> a -> r) -> s ->Maybe
r
However, it may be useful to think of its full generality when working with
a Monad
transformer stack:
ipreviews
::MonadReader
s m =>IndexedGetter
i s a -> (i -> a -> r) -> m (Maybe
r)ipreviews
::MonadReader
s m =>IndexedFold
i s a -> (i -> a -> r) -> m (Maybe
r)ipreviews
::MonadReader
s m =>IndexedLens'
i s a -> (i -> a -> r) -> m (Maybe
r)ipreviews
::MonadReader
s m =>IndexedTraversal'
i s a -> (i -> a -> r) -> m (Maybe
r)
preuse :: MonadState s m => Getting (First a) s a -> m (Maybe a) Source #
Retrieve the first value targeted by a Fold
or Traversal
(or Just
the result
from a Getter
or Lens
) into the current state.
preuse
=use
.
pre
preuse
::MonadState
s m =>Getter
s a -> m (Maybe
a)preuse
::MonadState
s m =>Fold
s a -> m (Maybe
a)preuse
::MonadState
s m =>Lens'
s a -> m (Maybe
a)preuse
::MonadState
s m =>Iso'
s a -> m (Maybe
a)preuse
::MonadState
s m =>Traversal'
s a -> m (Maybe
a)
preuses :: MonadState s m => Getting (First r) s a -> (a -> r) -> m (Maybe r) Source #
Retrieve a function of the first value targeted by a Fold
or
Traversal
(or Just
the result from a Getter
or Lens
) into the current state.
preuses
=uses
.
pre
preuses
::MonadState
s m =>Getter
s a -> (a -> r) -> m (Maybe
r)preuses
::MonadState
s m =>Fold
s a -> (a -> r) -> m (Maybe
r)preuses
::MonadState
s m =>Lens'
s a -> (a -> r) -> m (Maybe
r)preuses
::MonadState
s m =>Iso'
s a -> (a -> r) -> m (Maybe
r)preuses
::MonadState
s m =>Traversal'
s a -> (a -> r) -> m (Maybe
r)
ipreuse :: MonadState s m => IndexedGetting i (First (i, a)) s a -> m (Maybe (i, a)) Source #
Retrieve the first index and value targeted by an IndexedFold
or IndexedTraversal
(or Just
the index
and result from an IndexedGetter
or IndexedLens
) into the current state.
ipreuse
=use
.
ipre
ipreuse
::MonadState
s m =>IndexedGetter
i s a -> m (Maybe
(i, a))ipreuse
::MonadState
s m =>IndexedFold
i s a -> m (Maybe
(i, a))ipreuse
::MonadState
s m =>IndexedLens'
i s a -> m (Maybe
(i, a))ipreuse
::MonadState
s m =>IndexedTraversal'
i s a -> m (Maybe
(i, a))
ipreuses :: MonadState s m => IndexedGetting i (First r) s a -> (i -> a -> r) -> m (Maybe r) Source #
Retrieve a function of the first index and value targeted by an IndexedFold
or
IndexedTraversal
(or a function of Just
the index and result from an IndexedGetter
or IndexedLens
) into the current state.
ipreuses
=uses
.
ipre
ipreuses
::MonadState
s m =>IndexedGetter
i s a -> (i -> a -> r) -> m (Maybe
r)ipreuses
::MonadState
s m =>IndexedFold
i s a -> (i -> a -> r) -> m (Maybe
r)ipreuses
::MonadState
s m =>IndexedLens'
i s a -> (i -> a -> r) -> m (Maybe
r)ipreuses
::MonadState
s m =>IndexedTraversal'
i s a -> (i -> a -> r) -> m (Maybe
r)
has :: Getting Any s a -> s -> Bool Source #
Check to see if this Fold
or Traversal
matches 1 or more entries.
>>>
has (element 0) []
False
>>>
has _Left (Left 12)
True
>>>
has _Right (Left 12)
False
This will always return True
for a Lens
or Getter
.
>>>
has _1 ("hello","world")
True
has
::Getter
s a -> s ->Bool
has
::Fold
s a -> s ->Bool
has
::Iso'
s a -> s ->Bool
has
::Lens'
s a -> s ->Bool
has
::Traversal'
s a -> s ->Bool
Building Folds
ifolding :: (Foldable f, Indexable i p, Contravariant g, Applicative g) => (s -> f (i, a)) -> Over p g s t a b Source #
foldring :: (Contravariant f, Applicative f) => ((a -> f a -> f a) -> f a -> s -> f a) -> LensLike f s t a b Source #
ifoldring :: (Indexable i p, Contravariant f, Applicative f) => ((i -> a -> f a -> f a) -> f a -> s -> f a) -> Over p f s t a b Source #
Obtain FoldWithIndex
by lifting ifoldr
like function.
filtered :: (Choice p, Applicative f) => (a -> Bool) -> Optic' p f a a Source #
Obtain a Fold
that can be composed with to filter another Lens
, Iso
, Getter
, Fold
(or Traversal
).
Note: This is not a legal Traversal
, unless you are very careful not to invalidate the predicate on the target.
Note: This is also not a legal Prism
, unless you are very careful not to inject a value that fails the predicate.
As a counter example, consider that given evens =
the second filtered
even
Traversal
law is violated:
over
evenssucc
.
over
evenssucc
/=
over
evens (succ
.
succ
)
So, in order for this to qualify as a legal Traversal
you can only use it for actions that preserve the result of the predicate!
>>>
[1..10]^..folded.filtered even
[2,4,6,8,10]
This will preserve an index if it is present.
filteredBy :: (Indexable i p, Applicative f) => Getting (First i) a i -> p a (f a) -> a -> f a Source #
Obtain a potentially empty IndexedTraversal
by taking the first element from another,
potentially empty Fold
and using it as an index.
The resulting optic can be composed with to filter another Lens
, Iso
, Getter
, Fold
(or Traversal
).
>>>
[(Just 2, 3), (Nothing, 4)] & mapped . filteredBy (_1 . _Just) <. _2 %@~ (*) :: [(Maybe Int, Int)]
[(Just 2,6),(Nothing,4)]
filteredBy
::Fold
a i ->IndexedTraversal'
i a a
Note: As with filtered
, this is not a legal IndexedTraversal
, unless you are very careful not to invalidate the predicate on the target!
backwards :: (Profunctor p, Profunctor q) => Optical p q (Backwards f) s t a b -> Optical p q f s t a b Source #
This allows you to traverse
the elements of a pretty much any LensLike
construction in the opposite order.
This will preserve indexes on Indexed
types and will give you the elements of a (finite) Fold
or Traversal
in the opposite order.
This has no practical impact on a Getter
, Setter
, Lens
or Iso
.
NB: To write back through an Iso
, you want to use from
.
Similarly, to write back through an Prism
, you want to use re
.
replicated :: Int -> Fold a a Source #
A Fold
that replicates its input n
times.
replicate
n ≡toListOf
(replicated
n)
>>>
5^..replicated 20
[5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5,5]
takingWhile :: (Conjoined p, Applicative f) => (a -> Bool) -> Over p (TakingWhile p f a a) s t a a -> Over p f s t a a Source #
Obtain a Fold
by taking elements from another Fold
, Lens
, Iso
, Getter
or Traversal
while a predicate holds.
takeWhile
p ≡toListOf
(takingWhile
pfolded
)
>>>
timingOut $ toListOf (takingWhile (<=3) folded) [1..]
[1,2,3]
takingWhile
:: (a ->Bool
) ->Fold
s a ->Fold
s atakingWhile
:: (a ->Bool
) ->Getter
s a ->Fold
s atakingWhile
:: (a ->Bool
) ->Traversal'
s a ->Fold
s a -- * See note belowtakingWhile
:: (a ->Bool
) ->Lens'
s a ->Fold
s a -- * See note belowtakingWhile
:: (a ->Bool
) ->Prism'
s a ->Fold
s a -- * See note belowtakingWhile
:: (a ->Bool
) ->Iso'
s a ->Fold
s a -- * See note belowtakingWhile
:: (a ->Bool
) ->IndexedTraversal'
i s a ->IndexedFold
i s a -- * See note belowtakingWhile
:: (a ->Bool
) ->IndexedLens'
i s a ->IndexedFold
i s a -- * See note belowtakingWhile
:: (a ->Bool
) ->IndexedFold
i s a ->IndexedFold
i s atakingWhile
:: (a ->Bool
) ->IndexedGetter
i s a ->IndexedFold
i s a
Note: When applied to a Traversal
, takingWhile
yields something that can be used as if it were a Traversal
, but
which is not a Traversal
per the laws, unless you are careful to ensure that you do not invalidate the predicate when
writing back through it.
droppingWhile :: (Conjoined p, Profunctor q, Applicative f) => (a -> Bool) -> Optical p q (Compose (State Bool) f) s t a a -> Optical p q f s t a a Source #
Obtain a Fold
by dropping elements from another Fold
, Lens
, Iso
, Getter
or Traversal
while a predicate holds.
dropWhile
p ≡toListOf
(droppingWhile
pfolded
)
>>>
toListOf (droppingWhile (<=3) folded) [1..6]
[4,5,6]
>>>
toListOf (droppingWhile (<=3) folded) [1,6,1]
[6,1]
droppingWhile
:: (a ->Bool
) ->Fold
s a ->Fold
s adroppingWhile
:: (a ->Bool
) ->Getter
s a ->Fold
s adroppingWhile
:: (a ->Bool
) ->Traversal'
s a ->Fold
s a -- see notesdroppingWhile
:: (a ->Bool
) ->Lens'
s a ->Fold
s a -- see notesdroppingWhile
:: (a ->Bool
) ->Prism'
s a ->Fold
s a -- see notesdroppingWhile
:: (a ->Bool
) ->Iso'
s a ->Fold
s a -- see notes
droppingWhile
:: (a ->Bool
) ->IndexPreservingTraversal'
s a ->IndexPreservingFold
s a -- see notesdroppingWhile
:: (a ->Bool
) ->IndexPreservingLens'
s a ->IndexPreservingFold
s a -- see notesdroppingWhile
:: (a ->Bool
) ->IndexPreservingGetter
s a ->IndexPreservingFold
s adroppingWhile
:: (a ->Bool
) ->IndexPreservingFold
s a ->IndexPreservingFold
s a
droppingWhile
:: (a ->Bool
) ->IndexedTraversal'
i s a ->IndexedFold
i s a -- see notesdroppingWhile
:: (a ->Bool
) ->IndexedLens'
i s a ->IndexedFold
i s a -- see notesdroppingWhile
:: (a ->Bool
) ->IndexedGetter
i s a ->IndexedFold
i s adroppingWhile
:: (a ->Bool
) ->IndexedFold
i s a ->IndexedFold
i s a
Note: Many uses of this combinator will yield something that meets the types, but not the laws of a valid
Traversal
or IndexedTraversal
. The Traversal
and IndexedTraversal
laws are only satisfied if the
new values you assign to the first target also does not pass the predicate! Otherwise subsequent traversals
will visit fewer elements and Traversal
fusion is not sound.
So for any traversal t
and predicate p
,
may not be lawful, but
droppingWhile
p t(
is. For example:dropping
1 . droppingWhile
p) t
>>>
let l :: Traversal' [Int] Int; l = droppingWhile (<= 1) traverse
>>>
let l' :: Traversal' [Int] Int; l' = dropping 1 l
l
is not a lawful setter because
:over
l f .
over
l g ≢ over
l (f . g)
>>>
[1,2,3] & l .~ 0 & l .~ 4
[1,0,0]>>>
[1,2,3] & l .~ 4
[1,4,4]
l'
on the other hand behaves lawfully:
>>>
[1,2,3] & l' .~ 0 & l' .~ 4
[1,2,4]>>>
[1,2,3] & l' .~ 4
[1,2,4]
worded :: forall (f :: Type -> Type). Applicative f => IndexedLensLike' Int f String String Source #
A Fold
over the individual words
of a String
.
worded
::Fold
String
String
worded
::Traversal'
String
String
worded
::IndexedFold
Int
String
String
worded
::IndexedTraversal'
Int
String
String
Note: This function type-checks as a Traversal
but it doesn't satisfy the laws. It's only valid to use it
when you don't insert any whitespace characters while traversing, and if your original String
contains only
isolated space characters (and no other characters that count as space, such as non-breaking spaces).
lined :: forall (f :: Type -> Type). Applicative f => IndexedLensLike' Int f String String Source #
A Fold
over the individual lines
of a String
.
lined
::Fold
String
String
lined
::Traversal'
String
String
lined
::IndexedFold
Int
String
String
lined
::IndexedTraversal'
Int
String
String
Note: This function type-checks as a Traversal
but it doesn't satisfy the laws. It's only valid to use it
when you don't insert any newline characters while traversing, and if your original String
contains only
isolated newline characters.
Folding
foldMapOf :: Getting r s a -> (a -> r) -> s -> r Source #
Map each part of a structure viewed through a Lens
, Getter
,
Fold
or Traversal
to a monoid and combine the results.
>>>
foldMapOf (folded . both . _Just) Sum [(Just 21, Just 21)]
Sum {getSum = 42}
foldMap
=foldMapOf
folded
foldMapOf
≡views
ifoldMapOf
l =foldMapOf
l.
Indexed
foldMapOf
::Getter
s a -> (a -> r) -> s -> rfoldMapOf
::Monoid
r =>Fold
s a -> (a -> r) -> s -> rfoldMapOf
::Semigroup
r =>Fold1
s a -> (a -> r) -> s -> rfoldMapOf
::Lens'
s a -> (a -> r) -> s -> rfoldMapOf
::Iso'
s a -> (a -> r) -> s -> rfoldMapOf
::Monoid
r =>Traversal'
s a -> (a -> r) -> s -> rfoldMapOf
::Semigroup
r =>Traversal1'
s a -> (a -> r) -> s -> rfoldMapOf
::Monoid
r =>Prism'
s a -> (a -> r) -> s -> r
foldMapOf
::Getting
r s a -> (a -> r) -> s -> r
foldOf :: Getting a s a -> s -> a Source #
Combine the elements of a structure viewed through a Lens
, Getter
,
Fold
or Traversal
using a monoid.
>>>
foldOf (folded.folded) [[Sum 1,Sum 4],[Sum 8, Sum 8],[Sum 21]]
Sum {getSum = 42}
fold
=foldOf
folded
foldOf
≡view
foldOf
::Getter
s m -> s -> mfoldOf
::Monoid
m =>Fold
s m -> s -> mfoldOf
::Lens'
s m -> s -> mfoldOf
::Iso'
s m -> s -> mfoldOf
::Monoid
m =>Traversal'
s m -> s -> mfoldOf
::Monoid
m =>Prism'
s m -> s -> m
foldrOf :: Getting (Endo r) s a -> (a -> r -> r) -> r -> s -> r Source #
Right-associative fold of parts of a structure that are viewed through a Lens
, Getter
, Fold
or Traversal
.
foldr
≡foldrOf
folded
foldrOf
::Getter
s a -> (a -> r -> r) -> r -> s -> rfoldrOf
::Fold
s a -> (a -> r -> r) -> r -> s -> rfoldrOf
::Lens'
s a -> (a -> r -> r) -> r -> s -> rfoldrOf
::Iso'
s a -> (a -> r -> r) -> r -> s -> rfoldrOf
::Traversal'
s a -> (a -> r -> r) -> r -> s -> rfoldrOf
::Prism'
s a -> (a -> r -> r) -> r -> s -> r
ifoldrOf
l ≡foldrOf
l.
Indexed
foldrOf
::Getting
(Endo
r) s a -> (a -> r -> r) -> r -> s -> r
foldlOf :: Getting (Dual (Endo r)) s a -> (r -> a -> r) -> r -> s -> r Source #
Left-associative fold of the parts of a structure that are viewed through a Lens
, Getter
, Fold
or Traversal
.
foldl
≡foldlOf
folded
foldlOf
::Getter
s a -> (r -> a -> r) -> r -> s -> rfoldlOf
::Fold
s a -> (r -> a -> r) -> r -> s -> rfoldlOf
::Lens'
s a -> (r -> a -> r) -> r -> s -> rfoldlOf
::Iso'
s a -> (r -> a -> r) -> r -> s -> rfoldlOf
::Traversal'
s a -> (r -> a -> r) -> r -> s -> rfoldlOf
::Prism'
s a -> (r -> a -> r) -> r -> s -> r
toNonEmptyOf :: Getting (NonEmptyDList a) s a -> s -> NonEmpty a Source #
Extract a NonEmpty
of the targets of Fold1
.
>>>
toNonEmptyOf both1 ("hello", "world")
"hello" :| ["world"]
toNonEmptyOf
::Getter
s a -> s -> NonEmpty atoNonEmptyOf
::Fold1
s a -> s -> NonEmpty atoNonEmptyOf
::Lens'
s a -> s -> NonEmpty atoNonEmptyOf
::Iso'
s a -> s -> NonEmpty atoNonEmptyOf
::Traversal1'
s a -> s -> NonEmpty a
altOf :: Applicative f => Getting (Alt f a) s a -> s -> f a Source #
Calls pure
on the target of a Lens
, Getter
, or Iso
.
Calls pure
on the targets of a Traversal
, Fold
, or Prism
, and
combines them with <|>
(or empty
if none). Intuitively, it collects
targets into an Alternative
until the container fills up or it runs out of
targets, whichever comes first.
Generalizes toListOf
and (^?)
.
>>>
altOf both ("hello", "world") :: [String]
["hello","world"]>>>
altOf both ("hello", "world") :: Maybe String
Just "hello"
altOf
:: Applicative f =>Lens'
s a -> s -> f aaltOf
:: Applicative f =>Getter
s a -> s -> f aaltOf
:: Applicative f =>Iso'
s a -> s -> f aaltOf
:: Alternative f =>Traversal'
s a -> s -> f aaltOf
:: Alternative f =>Fold
s a -> s -> f aaltOf
:: Alternative f =>Prism'
s a -> s -> f a
anyOf :: Getting Any s a -> (a -> Bool) -> s -> Bool Source #
Returns True
if any target of a Fold
satisfies a predicate.
>>>
anyOf both (=='x') ('x','y')
True>>>
import Data.Data.Lens
>>>
anyOf biplate (== "world") (((),2::Int),"hello",("world",11::Int))
True
any
≡anyOf
folded
ianyOf
l ≡anyOf
l.
Indexed
anyOf
::Getter
s a -> (a ->Bool
) -> s ->Bool
anyOf
::Fold
s a -> (a ->Bool
) -> s ->Bool
anyOf
::Lens'
s a -> (a ->Bool
) -> s ->Bool
anyOf
::Iso'
s a -> (a ->Bool
) -> s ->Bool
anyOf
::Traversal'
s a -> (a ->Bool
) -> s ->Bool
anyOf
::Prism'
s a -> (a ->Bool
) -> s ->Bool
allOf :: Getting All s a -> (a -> Bool) -> s -> Bool Source #
Returns True
if every target of a Fold
satisfies a predicate.
>>>
allOf both (>=3) (4,5)
True>>>
allOf folded (>=2) [1..10]
False
all
≡allOf
folded
iallOf
l =allOf
l.
Indexed
allOf
::Getter
s a -> (a ->Bool
) -> s ->Bool
allOf
::Fold
s a -> (a ->Bool
) -> s ->Bool
allOf
::Lens'
s a -> (a ->Bool
) -> s ->Bool
allOf
::Iso'
s a -> (a ->Bool
) -> s ->Bool
allOf
::Traversal'
s a -> (a ->Bool
) -> s ->Bool
allOf
::Prism'
s a -> (a ->Bool
) -> s ->Bool
noneOf :: Getting Any s a -> (a -> Bool) -> s -> Bool Source #
Returns True
only if no targets of a Fold
satisfy a predicate.
>>>
noneOf each (is _Nothing) (Just 3, Just 4, Just 5)
True>>>
noneOf (folded.folded) (<10) [[13,99,20],[3,71,42]]
False
inoneOf
l =noneOf
l.
Indexed
noneOf
::Getter
s a -> (a ->Bool
) -> s ->Bool
noneOf
::Fold
s a -> (a ->Bool
) -> s ->Bool
noneOf
::Lens'
s a -> (a ->Bool
) -> s ->Bool
noneOf
::Iso'
s a -> (a ->Bool
) -> s ->Bool
noneOf
::Traversal'
s a -> (a ->Bool
) -> s ->Bool
noneOf
::Prism'
s a -> (a ->Bool
) -> s ->Bool
andOf :: Getting All s Bool -> s -> Bool Source #
Returns True
if every target of a Fold
is True
.
>>>
andOf both (True,False)
False>>>
andOf both (True,True)
True
and
≡andOf
folded
andOf
::Getter
sBool
-> s ->Bool
andOf
::Fold
sBool
-> s ->Bool
andOf
::Lens'
sBool
-> s ->Bool
andOf
::Iso'
sBool
-> s ->Bool
andOf
::Traversal'
sBool
-> s ->Bool
andOf
::Prism'
sBool
-> s ->Bool
orOf :: Getting Any s Bool -> s -> Bool Source #
Returns True
if any target of a Fold
is True
.
>>>
orOf both (True,False)
True>>>
orOf both (False,False)
False
or
≡orOf
folded
orOf
::Getter
sBool
-> s ->Bool
orOf
::Fold
sBool
-> s ->Bool
orOf
::Lens'
sBool
-> s ->Bool
orOf
::Iso'
sBool
-> s ->Bool
orOf
::Traversal'
sBool
-> s ->Bool
orOf
::Prism'
sBool
-> s ->Bool
productOf :: Num a => Getting (Endo (Endo a)) s a -> s -> a Source #
Calculate the Product
of every number targeted by a Fold
.
>>>
productOf both (4,5)
20>>>
productOf folded [1,2,3,4,5]
120
product
≡productOf
folded
This operation may be more strict than you would expect. If you
want a lazier version use ala
Product
.
foldMapOf
productOf
::Num
a =>Getter
s a -> s -> aproductOf
::Num
a =>Fold
s a -> s -> aproductOf
::Num
a =>Lens'
s a -> s -> aproductOf
::Num
a =>Iso'
s a -> s -> aproductOf
::Num
a =>Traversal'
s a -> s -> aproductOf
::Num
a =>Prism'
s a -> s -> a
sumOf :: Num a => Getting (Endo (Endo a)) s a -> s -> a Source #
Calculate the Sum
of every number targeted by a Fold
.
>>>
sumOf both (5,6)
11>>>
sumOf folded [1,2,3,4]
10>>>
sumOf (folded.both) [(1,2),(3,4)]
10>>>
import Data.Data.Lens
>>>
sumOf biplate [(1::Int,[]),(2,[(3::Int,4::Int)])] :: Int
10
sum
≡sumOf
folded
This operation may be more strict than you would expect. If you
want a lazier version use ala
Sum
.
foldMapOf
sumOf
_1
::Num
a => (a, b) -> asumOf
(folded
.
_1
) :: (Foldable
f,Num
a) => f (a, b) -> a
sumOf
::Num
a =>Getter
s a -> s -> asumOf
::Num
a =>Fold
s a -> s -> asumOf
::Num
a =>Lens'
s a -> s -> asumOf
::Num
a =>Iso'
s a -> s -> asumOf
::Num
a =>Traversal'
s a -> s -> asumOf
::Num
a =>Prism'
s a -> s -> a
traverseOf_ :: Functor f => Getting (Traversed r f) s a -> (a -> f r) -> s -> f () Source #
Traverse over all of the targets of a Fold
(or Getter
), computing an Applicative
(or Functor
)-based answer,
but unlike traverseOf
do not construct a new structure. traverseOf_
generalizes
traverse_
to work over any Fold
.
When passed a Getter
, traverseOf_
can work over any Functor
, but when passed a Fold
, traverseOf_
requires
an Applicative
.
>>>
traverseOf_ both putStrLn ("hello","world")
hello world
traverse_
≡traverseOf_
folded
traverseOf_
_2
::Functor
f => (c -> f r) -> (d, c) -> f ()traverseOf_
_Left
::Applicative
f => (a -> f b) ->Either
a c -> f ()
itraverseOf_
l ≡traverseOf_
l.
Indexed
The rather specific signature of traverseOf_
allows it to be used as if the signature was any of:
traverseOf_
::Functor
f =>Getter
s a -> (a -> f r) -> s -> f ()traverseOf_
::Applicative
f =>Fold
s a -> (a -> f r) -> s -> f ()traverseOf_
::Functor
f =>Lens'
s a -> (a -> f r) -> s -> f ()traverseOf_
::Functor
f =>Iso'
s a -> (a -> f r) -> s -> f ()traverseOf_
::Applicative
f =>Traversal'
s a -> (a -> f r) -> s -> f ()traverseOf_
::Applicative
f =>Prism'
s a -> (a -> f r) -> s -> f ()
forOf_ :: Functor f => Getting (Traversed r f) s a -> s -> (a -> f r) -> f () Source #
Traverse over all of the targets of a Fold
(or Getter
), computing an Applicative
(or Functor
)-based answer,
but unlike forOf
do not construct a new structure. forOf_
generalizes
for_
to work over any Fold
.
When passed a Getter
, forOf_
can work over any Functor
, but when passed a Fold
, forOf_
requires
an Applicative
.
for_
≡forOf_
folded
>>>
forOf_ both ("hello","world") putStrLn
hello world
The rather specific signature of forOf_
allows it to be used as if the signature was any of:
iforOf_
l s ≡forOf_
l s.
Indexed
forOf_
::Functor
f =>Getter
s a -> s -> (a -> f r) -> f ()forOf_
::Applicative
f =>Fold
s a -> s -> (a -> f r) -> f ()forOf_
::Functor
f =>Lens'
s a -> s -> (a -> f r) -> f ()forOf_
::Functor
f =>Iso'
s a -> s -> (a -> f r) -> f ()forOf_
::Applicative
f =>Traversal'
s a -> s -> (a -> f r) -> f ()forOf_
::Applicative
f =>Prism'
s a -> s -> (a -> f r) -> f ()
sequenceAOf_ :: Functor f => Getting (Traversed a f) s (f a) -> s -> f () Source #
Evaluate each action in observed by a Fold
on a structure from left to right, ignoring the results.
sequenceA_
≡sequenceAOf_
folded
>>>
sequenceAOf_ both (putStrLn "hello",putStrLn "world")
hello world
sequenceAOf_
::Functor
f =>Getter
s (f a) -> s -> f ()sequenceAOf_
::Applicative
f =>Fold
s (f a) -> s -> f ()sequenceAOf_
::Functor
f =>Lens'
s (f a) -> s -> f ()sequenceAOf_
::Functor
f =>Iso'
s (f a) -> s -> f ()sequenceAOf_
::Applicative
f =>Traversal'
s (f a) -> s -> f ()sequenceAOf_
::Applicative
f =>Prism'
s (f a) -> s -> f ()
traverse1Of_ :: Functor f => Getting (TraversedF r f) s a -> (a -> f r) -> s -> f () Source #
Traverse over all of the targets of a Fold1
, computing an Apply
based answer.
As long as you have Applicative
or Functor
effect you are better using traverseOf_
.
The traverse1Of_
is useful only when you have genuine Apply
effect.
>>>
traverse1Of_ both1 (\ks -> Map.fromList [ (k, ()) | k <- ks ]) ("abc", "bcd")
fromList [('b',()),('c',())]
traverse1Of_
::Apply
f =>Fold1
s a -> (a -> f r) -> s -> f ()
Since: 4.16
for1Of_ :: Functor f => Getting (TraversedF r f) s a -> s -> (a -> f r) -> f () Source #
See forOf_
and traverse1Of_
.
>>>
for1Of_ both1 ("abc", "bcd") (\ks -> Map.fromList [ (k, ()) | k <- ks ])
fromList [('b',()),('c',())]
for1Of_
::Apply
f =>Fold1
s a -> s -> (a -> f r) -> f ()
Since: 4.16
sequence1Of_ :: Functor f => Getting (TraversedF a f) s (f a) -> s -> f () Source #
mapMOf_ :: Monad m => Getting (Sequenced r m) s a -> (a -> m r) -> s -> m () Source #
Map each target of a Fold
on a structure to a monadic action, evaluate these actions from left to right, and ignore the results.
>>>
mapMOf_ both putStrLn ("hello","world")
hello world
mapM_
≡mapMOf_
folded
mapMOf_
::Monad
m =>Getter
s a -> (a -> m r) -> s -> m ()mapMOf_
::Monad
m =>Fold
s a -> (a -> m r) -> s -> m ()mapMOf_
::Monad
m =>Lens'
s a -> (a -> m r) -> s -> m ()mapMOf_
::Monad
m =>Iso'
s a -> (a -> m r) -> s -> m ()mapMOf_
::Monad
m =>Traversal'
s a -> (a -> m r) -> s -> m ()mapMOf_
::Monad
m =>Prism'
s a -> (a -> m r) -> s -> m ()
forMOf_ :: Monad m => Getting (Sequenced r m) s a -> s -> (a -> m r) -> m () Source #
forMOf_
is mapMOf_
with two of its arguments flipped.
>>>
forMOf_ both ("hello","world") putStrLn
hello world
forM_
≡forMOf_
folded
forMOf_
::Monad
m =>Getter
s a -> s -> (a -> m r) -> m ()forMOf_
::Monad
m =>Fold
s a -> s -> (a -> m r) -> m ()forMOf_
::Monad
m =>Lens'
s a -> s -> (a -> m r) -> m ()forMOf_
::Monad
m =>Iso'
s a -> s -> (a -> m r) -> m ()forMOf_
::Monad
m =>Traversal'
s a -> s -> (a -> m r) -> m ()forMOf_
::Monad
m =>Prism'
s a -> s -> (a -> m r) -> m ()
sequenceOf_ :: Monad m => Getting (Sequenced a m) s (m a) -> s -> m () Source #
Evaluate each monadic action referenced by a Fold
on the structure from left to right, and ignore the results.
>>>
sequenceOf_ both (putStrLn "hello",putStrLn "world")
hello world
sequence_
≡sequenceOf_
folded
sequenceOf_
::Monad
m =>Getter
s (m a) -> s -> m ()sequenceOf_
::Monad
m =>Fold
s (m a) -> s -> m ()sequenceOf_
::Monad
m =>Lens'
s (m a) -> s -> m ()sequenceOf_
::Monad
m =>Iso'
s (m a) -> s -> m ()sequenceOf_
::Monad
m =>Traversal'
s (m a) -> s -> m ()sequenceOf_
::Monad
m =>Prism'
s (m a) -> s -> m ()
asumOf :: Alternative f => Getting (Endo (f a)) s (f a) -> s -> f a Source #
The sum of a collection of actions, generalizing concatOf
.
>>>
asumOf both ("hello","world")
"helloworld"
>>>
asumOf each (Nothing, Just "hello", Nothing)
Just "hello"
asum
≡asumOf
folded
asumOf
::Alternative
f =>Getter
s (f a) -> s -> f aasumOf
::Alternative
f =>Fold
s (f a) -> s -> f aasumOf
::Alternative
f =>Lens'
s (f a) -> s -> f aasumOf
::Alternative
f =>Iso'
s (f a) -> s -> f aasumOf
::Alternative
f =>Traversal'
s (f a) -> s -> f aasumOf
::Alternative
f =>Prism'
s (f a) -> s -> f a
msumOf :: MonadPlus m => Getting (Endo (m a)) s (m a) -> s -> m a Source #
The sum of a collection of actions, generalizing concatOf
.
>>>
msumOf both ("hello","world")
"helloworld"
>>>
msumOf each (Nothing, Just "hello", Nothing)
Just "hello"
msum
≡msumOf
folded
msumOf
::MonadPlus
m =>Getter
s (m a) -> s -> m amsumOf
::MonadPlus
m =>Fold
s (m a) -> s -> m amsumOf
::MonadPlus
m =>Lens'
s (m a) -> s -> m amsumOf
::MonadPlus
m =>Iso'
s (m a) -> s -> m amsumOf
::MonadPlus
m =>Traversal'
s (m a) -> s -> m amsumOf
::MonadPlus
m =>Prism'
s (m a) -> s -> m a
concatMapOf :: Getting [r] s a -> (a -> [r]) -> s -> [r] Source #
Map a function over all the targets of a Fold
of a container and concatenate the resulting lists.
>>>
concatMapOf both (\x -> [x, x + 1]) (1,3)
[1,2,3,4]
concatMap
≡concatMapOf
folded
concatMapOf
::Getter
s a -> (a -> [r]) -> s -> [r]concatMapOf
::Fold
s a -> (a -> [r]) -> s -> [r]concatMapOf
::Lens'
s a -> (a -> [r]) -> s -> [r]concatMapOf
::Iso'
s a -> (a -> [r]) -> s -> [r]concatMapOf
::Traversal'
s a -> (a -> [r]) -> s -> [r]
concatOf :: Getting [r] s [r] -> s -> [r] Source #
Concatenate all of the lists targeted by a Fold
into a longer list.
>>>
concatOf both ("pan","ama")
"panama"
concat
≡concatOf
folded
concatOf
≡view
concatOf
::Getter
s [r] -> s -> [r]concatOf
::Fold
s [r] -> s -> [r]concatOf
::Iso'
s [r] -> s -> [r]concatOf
::Lens'
s [r] -> s -> [r]concatOf
::Traversal'
s [r] -> s -> [r]
elemOf :: Eq a => Getting Any s a -> a -> s -> Bool Source #
Does the element occur anywhere within a given Fold
of the structure?
>>>
elemOf both "hello" ("hello","world")
True
elem
≡elemOf
folded
elemOf
::Eq
a =>Getter
s a -> a -> s ->Bool
elemOf
::Eq
a =>Fold
s a -> a -> s ->Bool
elemOf
::Eq
a =>Lens'
s a -> a -> s ->Bool
elemOf
::Eq
a =>Iso'
s a -> a -> s ->Bool
elemOf
::Eq
a =>Traversal'
s a -> a -> s ->Bool
elemOf
::Eq
a =>Prism'
s a -> a -> s ->Bool
notElemOf :: Eq a => Getting All s a -> a -> s -> Bool Source #
Does the element not occur anywhere within a given Fold
of the structure?
>>>
notElemOf each 'd' ('a','b','c')
True
>>>
notElemOf each 'a' ('a','b','c')
False
notElem
≡notElemOf
folded
notElemOf
::Eq
a =>Getter
s a -> a -> s ->Bool
notElemOf
::Eq
a =>Fold
s a -> a -> s ->Bool
notElemOf
::Eq
a =>Iso'
s a -> a -> s ->Bool
notElemOf
::Eq
a =>Lens'
s a -> a -> s ->Bool
notElemOf
::Eq
a =>Traversal'
s a -> a -> s ->Bool
notElemOf
::Eq
a =>Prism'
s a -> a -> s ->Bool
lengthOf :: Getting (Endo (Endo Int)) s a -> s -> Int Source #
Calculate the number of targets there are for a Fold
in a given container.
Note: This can be rather inefficient for large containers and just like length
,
this will not terminate for infinite folds.
length
≡lengthOf
folded
>>>
lengthOf _1 ("hello",())
1
>>>
lengthOf traverse [1..10]
10
>>>
lengthOf (traverse.traverse) [[1,2],[3,4],[5,6]]
6
lengthOf
(folded
.
folded
) :: (Foldable
f,Foldable
g) => f (g a) ->Int
lengthOf
::Getter
s a -> s ->Int
lengthOf
::Fold
s a -> s ->Int
lengthOf
::Lens'
s a -> s ->Int
lengthOf
::Iso'
s a -> s ->Int
lengthOf
::Traversal'
s a -> s ->Int
nullOf :: Getting All s a -> s -> Bool Source #
Returns True
if this Fold
or Traversal
has no targets in the given container.
Note: nullOf
on a valid Iso
, Lens
or Getter
should always return False
.
null
≡nullOf
folded
This may be rather inefficient compared to the null
check of many containers.
>>>
nullOf _1 (1,2)
False
>>>
nullOf ignored ()
True
>>>
nullOf traverse []
True
>>>
nullOf (element 20) [1..10]
True
nullOf
(folded
.
_1
.
folded
) :: (Foldable
f,Foldable
g) => f (g a, b) ->Bool
nullOf
::Getter
s a -> s ->Bool
nullOf
::Fold
s a -> s ->Bool
nullOf
::Iso'
s a -> s ->Bool
nullOf
::Lens'
s a -> s ->Bool
nullOf
::Traversal'
s a -> s ->Bool
notNullOf :: Getting Any s a -> s -> Bool Source #
Returns True
if this Fold
or Traversal
has any targets in the given container.
A more "conversational" alias for this combinator is has
.
Note: notNullOf
on a valid Iso
, Lens
or Getter
should always return True
.
not
.
null
≡notNullOf
folded
This may be rather inefficient compared to the
check of many containers.not
.
null
>>>
notNullOf _1 (1,2)
True
>>>
notNullOf traverse [1..10]
True
>>>
notNullOf folded []
False
>>>
notNullOf (element 20) [1..10]
False
notNullOf
(folded
.
_1
.
folded
) :: (Foldable
f,Foldable
g) => f (g a, b) ->Bool
notNullOf
::Getter
s a -> s ->Bool
notNullOf
::Fold
s a -> s ->Bool
notNullOf
::Iso'
s a -> s ->Bool
notNullOf
::Lens'
s a -> s ->Bool
notNullOf
::Traversal'
s a -> s ->Bool
firstOf :: Getting (Leftmost a) s a -> s -> Maybe a Source #
Retrieve the First
entry of a Fold
or Traversal
or retrieve Just
the result
from a Getter
or Lens
.
The answer is computed in a manner that leaks space less than
or preview
^?'
and gives you back access to the outermost Just
constructor more quickly, but does so
in a way that builds an intermediate structure, and thus may have worse
constant factors. This also means that it can not be used in any MonadReader
,
but must instead have s
passed as its last argument, unlike preview
.
Note: this could been named headOf
.
>>>
firstOf traverse [1..10]
Just 1
>>>
firstOf both (1,2)
Just 1
>>>
firstOf ignored ()
Nothing
firstOf
::Getter
s a -> s ->Maybe
afirstOf
::Fold
s a -> s ->Maybe
afirstOf
::Lens'
s a -> s ->Maybe
afirstOf
::Iso'
s a -> s ->Maybe
afirstOf
::Traversal'
s a -> s ->Maybe
a
first1Of :: Getting (First a) s a -> s -> a Source #
Retrieve the First
entry of a Fold1
or Traversal1
or the result from a Getter
or Lens
.
>>>
first1Of traverse1 (1 :| [2..10])
1
>>>
first1Of both1 (1,2)
1
Note: this is different from ^.
.
>>>
first1Of traverse1 ([1,2] :| [[3,4],[5,6]])
[1,2]
>>>
([1,2] :| [[3,4],[5,6]]) ^. traverse1
[1,2,3,4,5,6]
first1Of
::Getter
s a -> s -> afirst1Of
::Fold1
s a -> s -> afirst1Of
::Lens'
s a -> s -> afirst1Of
::Iso'
s a -> s -> afirst1Of
::Traversal1'
s a -> s -> a
lastOf :: Getting (Rightmost a) s a -> s -> Maybe a Source #
Retrieve the Last
entry of a Fold
or Traversal
or retrieve Just
the result
from a Getter
or Lens
.
The answer is computed in a manner that leaks space less than
and gives you back access to the outermost ala
Last
.
foldMapOf
Just
constructor more quickly, but may have worse
constant factors.
>>>
lastOf traverse [1..10]
Just 10
>>>
lastOf both (1,2)
Just 2
>>>
lastOf ignored ()
Nothing
lastOf
::Getter
s a -> s ->Maybe
alastOf
::Fold
s a -> s ->Maybe
alastOf
::Lens'
s a -> s ->Maybe
alastOf
::Iso'
s a -> s ->Maybe
alastOf
::Traversal'
s a -> s ->Maybe
a
last1Of :: Getting (Last a) s a -> s -> a Source #
Retrieve the Last
entry of a Fold1
or Traversal1
or retrieve the result
from a Getter
or Lens
.o
>>>
last1Of traverse1 (1 :| [2..10])
10
>>>
last1Of both1 (1,2)
2
last1Of
::Getter
s a -> s ->Maybe
alast1Of
::Fold1
s a -> s ->Maybe
alast1Of
::Lens'
s a -> s ->Maybe
alast1Of
::Iso'
s a -> s ->Maybe
alast1Of
::Traversal1'
s a -> s ->Maybe
a
maximumOf :: Ord a => Getting (Endo (Endo (Maybe a))) s a -> s -> Maybe a Source #
Obtain the maximum element (if any) targeted by a Fold
or Traversal
safely.
Note: maximumOf
on a valid Iso
, Lens
or Getter
will always return Just
a value.
>>>
maximumOf traverse [1..10]
Just 10
>>>
maximumOf traverse []
Nothing
>>>
maximumOf (folded.filtered even) [1,4,3,6,7,9,2]
Just 6
maximum
≡fromMaybe
(error
"empty").
maximumOf
folded
In the interest of efficiency, This operation has semantics more strict than strictly necessary.
has lazier semantics but could leak memory.rmap
getMax
(foldMapOf
l Max
)
maximumOf
::Ord
a =>Getter
s a -> s ->Maybe
amaximumOf
::Ord
a =>Fold
s a -> s ->Maybe
amaximumOf
::Ord
a =>Iso'
s a -> s ->Maybe
amaximumOf
::Ord
a =>Lens'
s a -> s ->Maybe
amaximumOf
::Ord
a =>Traversal'
s a -> s ->Maybe
a
maximum1Of :: Ord a => Getting (Max a) s a -> s -> a Source #
Obtain the maximum element targeted by a Fold1
or Traversal1
.
>>>
maximum1Of traverse1 (1 :| [2..10])
10
maximum1Of
::Ord
a =>Getter
s a -> s -> amaximum1Of
::Ord
a =>Fold1
s a -> s -> amaximum1Of
::Ord
a =>Iso'
s a -> s -> amaximum1Of
::Ord
a =>Lens'
s a -> s -> amaximum1Of
::Ord
a =>Traversal1'
s a -> s -> a
minimumOf :: Ord a => Getting (Endo (Endo (Maybe a))) s a -> s -> Maybe a Source #
Obtain the minimum element (if any) targeted by a Fold
or Traversal
safely.
Note: minimumOf
on a valid Iso
, Lens
or Getter
will always return Just
a value.
>>>
minimumOf traverse [1..10]
Just 1
>>>
minimumOf traverse []
Nothing
>>>
minimumOf (folded.filtered even) [1,4,3,6,7,9,2]
Just 2
minimum
≡fromMaybe
(error
"empty").
minimumOf
folded
In the interest of efficiency, This operation has semantics more strict than strictly necessary.
has lazier semantics but could leak memory.rmap
getMin
(foldMapOf
l Min
)
minimumOf
::Ord
a =>Getter
s a -> s ->Maybe
aminimumOf
::Ord
a =>Fold
s a -> s ->Maybe
aminimumOf
::Ord
a =>Iso'
s a -> s ->Maybe
aminimumOf
::Ord
a =>Lens'
s a -> s ->Maybe
aminimumOf
::Ord
a =>Traversal'
s a -> s ->Maybe
a
minimum1Of :: Ord a => Getting (Min a) s a -> s -> a Source #
Obtain the minimum element targeted by a Fold1
or Traversal1
.
>>>
minimum1Of traverse1 (1 :| [2..10])
1
minimum1Of
::Ord
a =>Getter
s a -> s -> aminimum1Of
::Ord
a =>Fold1
s a -> s -> aminimum1Of
::Ord
a =>Iso'
s a -> s -> aminimum1Of
::Ord
a =>Lens'
s a -> s -> aminimum1Of
::Ord
a =>Traversal1'
s a -> s -> a
maximumByOf :: Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> Ordering) -> s -> Maybe a Source #
Obtain the maximum element (if any) targeted by a Fold
, Traversal
, Lens
, Iso
,
or Getter
according to a user supplied Ordering
.
>>>
maximumByOf traverse (compare `on` length) ["mustard","relish","ham"]
Just "mustard"
In the interest of efficiency, This operation has semantics more strict than strictly necessary.
maximumBy
cmp ≡fromMaybe
(error
"empty").
maximumByOf
folded
cmp
maximumByOf
::Getter
s a -> (a -> a ->Ordering
) -> s ->Maybe
amaximumByOf
::Fold
s a -> (a -> a ->Ordering
) -> s ->Maybe
amaximumByOf
::Iso'
s a -> (a -> a ->Ordering
) -> s ->Maybe
amaximumByOf
::Lens'
s a -> (a -> a ->Ordering
) -> s ->Maybe
amaximumByOf
::Traversal'
s a -> (a -> a ->Ordering
) -> s ->Maybe
a
minimumByOf :: Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> Ordering) -> s -> Maybe a Source #
Obtain the minimum element (if any) targeted by a Fold
, Traversal
, Lens
, Iso
or Getter
according to a user supplied Ordering
.
In the interest of efficiency, This operation has semantics more strict than strictly necessary.
>>>
minimumByOf traverse (compare `on` length) ["mustard","relish","ham"]
Just "ham"
minimumBy
cmp ≡fromMaybe
(error
"empty").
minimumByOf
folded
cmp
minimumByOf
::Getter
s a -> (a -> a ->Ordering
) -> s ->Maybe
aminimumByOf
::Fold
s a -> (a -> a ->Ordering
) -> s ->Maybe
aminimumByOf
::Iso'
s a -> (a -> a ->Ordering
) -> s ->Maybe
aminimumByOf
::Lens'
s a -> (a -> a ->Ordering
) -> s ->Maybe
aminimumByOf
::Traversal'
s a -> (a -> a ->Ordering
) -> s ->Maybe
a
findOf :: Getting (Endo (Maybe a)) s a -> (a -> Bool) -> s -> Maybe a Source #
The findOf
function takes a Lens
(or Getter
, Iso
, Fold
, or Traversal
),
a predicate and a structure and returns the leftmost element of the structure
matching the predicate, or Nothing
if there is no such element.
>>>
findOf each even (1,3,4,6)
Just 4
>>>
findOf folded even [1,3,5,7]
Nothing
findOf
::Getter
s a -> (a ->Bool
) -> s ->Maybe
afindOf
::Fold
s a -> (a ->Bool
) -> s ->Maybe
afindOf
::Iso'
s a -> (a ->Bool
) -> s ->Maybe
afindOf
::Lens'
s a -> (a ->Bool
) -> s ->Maybe
afindOf
::Traversal'
s a -> (a ->Bool
) -> s ->Maybe
a
find
≡findOf
folded
ifindOf
l ≡findOf
l.
Indexed
A simpler version that didn't permit indexing, would be:
findOf
::Getting
(Endo
(Maybe
a)) s a -> (a ->Bool
) -> s ->Maybe
afindOf
l p =foldrOf
l (a y -> if p a thenJust
a else y)Nothing
findMOf :: Monad m => Getting (Endo (m (Maybe a))) s a -> (a -> m Bool) -> s -> m (Maybe a) Source #
The findMOf
function takes a Lens
(or Getter
, Iso
, Fold
, or Traversal
),
a monadic predicate and a structure and returns in the monad the leftmost element of the structure
matching the predicate, or Nothing
if there is no such element.
>>>
findMOf each ( \x -> print ("Checking " ++ show x) >> return (even x)) (1,3,4,6)
"Checking 1" "Checking 3" "Checking 4" Just 4
>>>
findMOf each ( \x -> print ("Checking " ++ show x) >> return (even x)) (1,3,5,7)
"Checking 1" "Checking 3" "Checking 5" "Checking 7" Nothing
findMOf
:: (Monad
m,Getter
s a) -> (a -> mBool
) -> s -> m (Maybe
a)findMOf
:: (Monad
m,Fold
s a) -> (a -> mBool
) -> s -> m (Maybe
a)findMOf
:: (Monad
m,Iso'
s a) -> (a -> mBool
) -> s -> m (Maybe
a)findMOf
:: (Monad
m,Lens'
s a) -> (a -> mBool
) -> s -> m (Maybe
a)findMOf
:: (Monad
m,Traversal'
s a) -> (a -> mBool
) -> s -> m (Maybe
a)
findMOf
folded
:: (Monad m, Foldable f) => (a -> m Bool) -> f a -> m (Maybe a)ifindMOf
l ≡findMOf
l.
Indexed
A simpler version that didn't permit indexing, would be:
findMOf
:: Monad m =>Getting
(Endo
(m (Maybe
a))) s a -> (a -> mBool
) -> s -> m (Maybe
a)findMOf
l p =foldrOf
l (a y -> p a >>= x -> if x then return (Just
a) else y) $ returnNothing
foldrOf' :: Getting (Dual (Endo (Endo r))) s a -> (a -> r -> r) -> r -> s -> r Source #
Strictly fold right over the elements of a structure.
foldr'
≡foldrOf'
folded
foldrOf'
::Getter
s a -> (a -> r -> r) -> r -> s -> rfoldrOf'
::Fold
s a -> (a -> r -> r) -> r -> s -> rfoldrOf'
::Iso'
s a -> (a -> r -> r) -> r -> s -> rfoldrOf'
::Lens'
s a -> (a -> r -> r) -> r -> s -> rfoldrOf'
::Traversal'
s a -> (a -> r -> r) -> r -> s -> r
foldlOf' :: Getting (Endo (Endo r)) s a -> (r -> a -> r) -> r -> s -> r Source #
Fold over the elements of a structure, associating to the left, but strictly.
foldl'
≡foldlOf'
folded
foldlOf'
::Getter
s a -> (r -> a -> r) -> r -> s -> rfoldlOf'
::Fold
s a -> (r -> a -> r) -> r -> s -> rfoldlOf'
::Iso'
s a -> (r -> a -> r) -> r -> s -> rfoldlOf'
::Lens'
s a -> (r -> a -> r) -> r -> s -> rfoldlOf'
::Traversal'
s a -> (r -> a -> r) -> r -> s -> r
foldr1Of :: HasCallStack => Getting (Endo (Maybe a)) s a -> (a -> a -> a) -> s -> a Source #
A variant of foldrOf
that has no base case and thus may only be applied
to lenses and structures such that the Lens
views at least one element of
the structure.
>>>
foldr1Of each (+) (1,2,3,4)
10
foldr1Of
l f ≡foldr1
f.
toListOf
lfoldr1
≡foldr1Of
folded
foldr1Of
::Getter
s a -> (a -> a -> a) -> s -> afoldr1Of
::Fold
s a -> (a -> a -> a) -> s -> afoldr1Of
::Iso'
s a -> (a -> a -> a) -> s -> afoldr1Of
::Lens'
s a -> (a -> a -> a) -> s -> afoldr1Of
::Traversal'
s a -> (a -> a -> a) -> s -> a
foldl1Of :: HasCallStack => Getting (Dual (Endo (Maybe a))) s a -> (a -> a -> a) -> s -> a Source #
A variant of foldlOf
that has no base case and thus may only be applied to lenses and structures such
that the Lens
views at least one element of the structure.
>>>
foldl1Of each (+) (1,2,3,4)
10
foldl1Of
l f ≡foldl1
f.
toListOf
lfoldl1
≡foldl1Of
folded
foldl1Of
::Getter
s a -> (a -> a -> a) -> s -> afoldl1Of
::Fold
s a -> (a -> a -> a) -> s -> afoldl1Of
::Iso'
s a -> (a -> a -> a) -> s -> afoldl1Of
::Lens'
s a -> (a -> a -> a) -> s -> afoldl1Of
::Traversal'
s a -> (a -> a -> a) -> s -> a
foldr1Of' :: HasCallStack => Getting (Dual (Endo (Endo (Maybe a)))) s a -> (a -> a -> a) -> s -> a Source #
A variant of foldrOf'
that has no base case and thus may only be applied
to folds and structures such that the fold views at least one element of the
structure.
foldr1Of
l f ≡foldr1
f.
toListOf
l
foldr1Of'
::Getter
s a -> (a -> a -> a) -> s -> afoldr1Of'
::Fold
s a -> (a -> a -> a) -> s -> afoldr1Of'
::Iso'
s a -> (a -> a -> a) -> s -> afoldr1Of'
::Lens'
s a -> (a -> a -> a) -> s -> afoldr1Of'
::Traversal'
s a -> (a -> a -> a) -> s -> a
foldl1Of' :: HasCallStack => Getting (Endo (Endo (Maybe a))) s a -> (a -> a -> a) -> s -> a Source #
A variant of foldlOf'
that has no base case and thus may only be applied
to folds and structures such that the fold views at least one element of
the structure.
foldl1Of'
l f ≡foldl1'
f.
toListOf
l
foldl1Of'
::Getter
s a -> (a -> a -> a) -> s -> afoldl1Of'
::Fold
s a -> (a -> a -> a) -> s -> afoldl1Of'
::Iso'
s a -> (a -> a -> a) -> s -> afoldl1Of'
::Lens'
s a -> (a -> a -> a) -> s -> afoldl1Of'
::Traversal'
s a -> (a -> a -> a) -> s -> a
foldrMOf :: Monad m => Getting (Dual (Endo (r -> m r))) s a -> (a -> r -> m r) -> r -> s -> m r Source #
Monadic fold over the elements of a structure, associating to the right, i.e. from right to left.
foldrM
≡foldrMOf
folded
foldrMOf
::Monad
m =>Getter
s a -> (a -> r -> m r) -> r -> s -> m rfoldrMOf
::Monad
m =>Fold
s a -> (a -> r -> m r) -> r -> s -> m rfoldrMOf
::Monad
m =>Iso'
s a -> (a -> r -> m r) -> r -> s -> m rfoldrMOf
::Monad
m =>Lens'
s a -> (a -> r -> m r) -> r -> s -> m rfoldrMOf
::Monad
m =>Traversal'
s a -> (a -> r -> m r) -> r -> s -> m r
foldlMOf :: Monad m => Getting (Endo (r -> m r)) s a -> (r -> a -> m r) -> r -> s -> m r Source #
Monadic fold over the elements of a structure, associating to the left, i.e. from left to right.
foldlM
≡foldlMOf
folded
foldlMOf
::Monad
m =>Getter
s a -> (r -> a -> m r) -> r -> s -> m rfoldlMOf
::Monad
m =>Fold
s a -> (r -> a -> m r) -> r -> s -> m rfoldlMOf
::Monad
m =>Iso'
s a -> (r -> a -> m r) -> r -> s -> m rfoldlMOf
::Monad
m =>Lens'
s a -> (r -> a -> m r) -> r -> s -> m rfoldlMOf
::Monad
m =>Traversal'
s a -> (r -> a -> m r) -> r -> s -> m r
lookupOf :: Eq k => Getting (Endo (Maybe v)) s (k, v) -> k -> s -> Maybe v Source #
The lookupOf
function takes a Fold
(or Getter
, Traversal
,
Lens
, Iso
, etc.), a key, and a structure containing key/value pairs.
It returns the first value corresponding to the given key. This function
generalizes lookup
to work on an arbitrary Fold
instead of lists.
>>>
lookupOf folded 4 [(2, 'a'), (4, 'b'), (4, 'c')]
Just 'b'
>>>
lookupOf each 2 [(2, 'a'), (4, 'b'), (4, 'c')]
Just 'a'
lookupOf
::Eq
k =>Fold
s (k,v) -> k -> s ->Maybe
v
Indexed Folds
(^@..) :: s -> IndexedGetting i (Endo [(i, a)]) s a -> [(i, a)] infixl 8 Source #
An infix version of itoListOf
.
(^@?) :: s -> IndexedGetting i (Endo (Maybe (i, a))) s a -> Maybe (i, a) infixl 8 Source #
Perform a safe head
(with index) of an IndexedFold
or IndexedTraversal
or retrieve Just
the index and result
from an IndexedGetter
or IndexedLens
.
When using a IndexedTraversal
as a partial IndexedLens
, or an IndexedFold
as a partial IndexedGetter
this can be a convenient
way to extract the optional value.
(^@?
) :: s ->IndexedGetter
i s a ->Maybe
(i, a) (^@?
) :: s ->IndexedFold
i s a ->Maybe
(i, a) (^@?
) :: s ->IndexedLens'
i s a ->Maybe
(i, a) (^@?
) :: s ->IndexedTraversal'
i s a ->Maybe
(i, a)
(^@?!) :: HasCallStack => s -> IndexedGetting i (Endo (i, a)) s a -> (i, a) infixl 8 Source #
Perform an *UNSAFE* head
(with index) of an IndexedFold
or IndexedTraversal
assuming that it is there.
(^@?!
) :: s ->IndexedGetter
i s a -> (i, a) (^@?!
) :: s ->IndexedFold
i s a -> (i, a) (^@?!
) :: s ->IndexedLens'
i s a -> (i, a) (^@?!
) :: s ->IndexedTraversal'
i s a -> (i, a)
Indexed Folding
ifoldMapOf :: IndexedGetting i m s a -> (i -> a -> m) -> s -> m Source #
Fold an IndexedFold
or IndexedTraversal
by mapping indices and values to an arbitrary Monoid
with access
to the i
.
When you don't need access to the index then foldMapOf
is more flexible in what it accepts.
foldMapOf
l ≡ifoldMapOf
l.
const
ifoldMapOf
::IndexedGetter
i s a -> (i -> a -> m) -> s -> mifoldMapOf
::Monoid
m =>IndexedFold
i s a -> (i -> a -> m) -> s -> mifoldMapOf
::IndexedLens'
i s a -> (i -> a -> m) -> s -> mifoldMapOf
::Monoid
m =>IndexedTraversal'
i s a -> (i -> a -> m) -> s -> m
ifoldrOf :: IndexedGetting i (Endo r) s a -> (i -> a -> r -> r) -> r -> s -> r Source #
Right-associative fold of parts of a structure that are viewed through an IndexedFold
or IndexedTraversal
with
access to the i
.
When you don't need access to the index then foldrOf
is more flexible in what it accepts.
foldrOf
l ≡ifoldrOf
l.
const
ifoldrOf
::IndexedGetter
i s a -> (i -> a -> r -> r) -> r -> s -> rifoldrOf
::IndexedFold
i s a -> (i -> a -> r -> r) -> r -> s -> rifoldrOf
::IndexedLens'
i s a -> (i -> a -> r -> r) -> r -> s -> rifoldrOf
::IndexedTraversal'
i s a -> (i -> a -> r -> r) -> r -> s -> r
ifoldlOf :: IndexedGetting i (Dual (Endo r)) s a -> (i -> r -> a -> r) -> r -> s -> r Source #
Left-associative fold of the parts of a structure that are viewed through an IndexedFold
or IndexedTraversal
with
access to the i
.
When you don't need access to the index then foldlOf
is more flexible in what it accepts.
foldlOf
l ≡ifoldlOf
l.
const
ifoldlOf
::IndexedGetter
i s a -> (i -> r -> a -> r) -> r -> s -> rifoldlOf
::IndexedFold
i s a -> (i -> r -> a -> r) -> r -> s -> rifoldlOf
::IndexedLens'
i s a -> (i -> r -> a -> r) -> r -> s -> rifoldlOf
::IndexedTraversal'
i s a -> (i -> r -> a -> r) -> r -> s -> r
ianyOf :: IndexedGetting i Any s a -> (i -> a -> Bool) -> s -> Bool Source #
Return whether or not any element viewed through an IndexedFold
or IndexedTraversal
satisfy a predicate, with access to the i
.
When you don't need access to the index then anyOf
is more flexible in what it accepts.
anyOf
l ≡ianyOf
l.
const
ianyOf
::IndexedGetter
i s a -> (i -> a ->Bool
) -> s ->Bool
ianyOf
::IndexedFold
i s a -> (i -> a ->Bool
) -> s ->Bool
ianyOf
::IndexedLens'
i s a -> (i -> a ->Bool
) -> s ->Bool
ianyOf
::IndexedTraversal'
i s a -> (i -> a ->Bool
) -> s ->Bool
iallOf :: IndexedGetting i All s a -> (i -> a -> Bool) -> s -> Bool Source #
Return whether or not all elements viewed through an IndexedFold
or IndexedTraversal
satisfy a predicate, with access to the i
.
When you don't need access to the index then allOf
is more flexible in what it accepts.
allOf
l ≡iallOf
l.
const
iallOf
::IndexedGetter
i s a -> (i -> a ->Bool
) -> s ->Bool
iallOf
::IndexedFold
i s a -> (i -> a ->Bool
) -> s ->Bool
iallOf
::IndexedLens'
i s a -> (i -> a ->Bool
) -> s ->Bool
iallOf
::IndexedTraversal'
i s a -> (i -> a ->Bool
) -> s ->Bool
inoneOf :: IndexedGetting i Any s a -> (i -> a -> Bool) -> s -> Bool Source #
Return whether or not none of the elements viewed through an IndexedFold
or IndexedTraversal
satisfy a predicate, with access to the i
.
When you don't need access to the index then noneOf
is more flexible in what it accepts.
noneOf
l ≡inoneOf
l.
const
inoneOf
::IndexedGetter
i s a -> (i -> a ->Bool
) -> s ->Bool
inoneOf
::IndexedFold
i s a -> (i -> a ->Bool
) -> s ->Bool
inoneOf
::IndexedLens'
i s a -> (i -> a ->Bool
) -> s ->Bool
inoneOf
::IndexedTraversal'
i s a -> (i -> a ->Bool
) -> s ->Bool
itraverseOf_ :: Functor f => IndexedGetting i (Traversed r f) s a -> (i -> a -> f r) -> s -> f () Source #
Traverse the targets of an IndexedFold
or IndexedTraversal
with access to the i
, discarding the results.
When you don't need access to the index then traverseOf_
is more flexible in what it accepts.
traverseOf_
l ≡itraverseOf
l.
const
itraverseOf_
::Functor
f =>IndexedGetter
i s a -> (i -> a -> f r) -> s -> f ()itraverseOf_
::Applicative
f =>IndexedFold
i s a -> (i -> a -> f r) -> s -> f ()itraverseOf_
::Functor
f =>IndexedLens'
i s a -> (i -> a -> f r) -> s -> f ()itraverseOf_
::Applicative
f =>IndexedTraversal'
i s a -> (i -> a -> f r) -> s -> f ()
iforOf_ :: Functor f => IndexedGetting i (Traversed r f) s a -> s -> (i -> a -> f r) -> f () Source #
Traverse the targets of an IndexedFold
or IndexedTraversal
with access to the index, discarding the results
(with the arguments flipped).
iforOf_
≡flip
.
itraverseOf_
When you don't need access to the index then forOf_
is more flexible in what it accepts.
forOf_
l a ≡iforOf_
l a.
const
iforOf_
::Functor
f =>IndexedGetter
i s a -> s -> (i -> a -> f r) -> f ()iforOf_
::Applicative
f =>IndexedFold
i s a -> s -> (i -> a -> f r) -> f ()iforOf_
::Functor
f =>IndexedLens'
i s a -> s -> (i -> a -> f r) -> f ()iforOf_
::Applicative
f =>IndexedTraversal'
i s a -> s -> (i -> a -> f r) -> f ()
imapMOf_ :: Monad m => IndexedGetting i (Sequenced r m) s a -> (i -> a -> m r) -> s -> m () Source #
Run monadic actions for each target of an IndexedFold
or IndexedTraversal
with access to the index,
discarding the results.
When you don't need access to the index then mapMOf_
is more flexible in what it accepts.
mapMOf_
l ≡imapMOf
l.
const
imapMOf_
::Monad
m =>IndexedGetter
i s a -> (i -> a -> m r) -> s -> m ()imapMOf_
::Monad
m =>IndexedFold
i s a -> (i -> a -> m r) -> s -> m ()imapMOf_
::Monad
m =>IndexedLens'
i s a -> (i -> a -> m r) -> s -> m ()imapMOf_
::Monad
m =>IndexedTraversal'
i s a -> (i -> a -> m r) -> s -> m ()
iforMOf_ :: Monad m => IndexedGetting i (Sequenced r m) s a -> s -> (i -> a -> m r) -> m () Source #
Run monadic actions for each target of an IndexedFold
or IndexedTraversal
with access to the index,
discarding the results (with the arguments flipped).
iforMOf_
≡flip
.
imapMOf_
When you don't need access to the index then forMOf_
is more flexible in what it accepts.
forMOf_
l a ≡iforMOf
l a.
const
iforMOf_
::Monad
m =>IndexedGetter
i s a -> s -> (i -> a -> m r) -> m ()iforMOf_
::Monad
m =>IndexedFold
i s a -> s -> (i -> a -> m r) -> m ()iforMOf_
::Monad
m =>IndexedLens'
i s a -> s -> (i -> a -> m r) -> m ()iforMOf_
::Monad
m =>IndexedTraversal'
i s a -> s -> (i -> a -> m r) -> m ()
iconcatMapOf :: IndexedGetting i [r] s a -> (i -> a -> [r]) -> s -> [r] Source #
Concatenate the results of a function of the elements of an IndexedFold
or IndexedTraversal
with access to the index.
When you don't need access to the index then concatMapOf
is more flexible in what it accepts.
concatMapOf
l ≡iconcatMapOf
l.
const
iconcatMapOf
≡ifoldMapOf
iconcatMapOf
::IndexedGetter
i s a -> (i -> a -> [r]) -> s -> [r]iconcatMapOf
::IndexedFold
i s a -> (i -> a -> [r]) -> s -> [r]iconcatMapOf
::IndexedLens'
i s a -> (i -> a -> [r]) -> s -> [r]iconcatMapOf
::IndexedTraversal'
i s a -> (i -> a -> [r]) -> s -> [r]
ifindOf :: IndexedGetting i (Endo (Maybe a)) s a -> (i -> a -> Bool) -> s -> Maybe a Source #
The ifindOf
function takes an IndexedFold
or IndexedTraversal
, a predicate that is also
supplied the index, a structure and returns the left-most element of the structure
matching the predicate, or Nothing
if there is no such element.
When you don't need access to the index then findOf
is more flexible in what it accepts.
findOf
l ≡ifindOf
l.
const
ifindOf
::IndexedGetter
i s a -> (i -> a ->Bool
) -> s ->Maybe
aifindOf
::IndexedFold
i s a -> (i -> a ->Bool
) -> s ->Maybe
aifindOf
::IndexedLens'
i s a -> (i -> a ->Bool
) -> s ->Maybe
aifindOf
::IndexedTraversal'
i s a -> (i -> a ->Bool
) -> s ->Maybe
a
ifindMOf :: Monad m => IndexedGetting i (Endo (m (Maybe a))) s a -> (i -> a -> m Bool) -> s -> m (Maybe a) Source #
The ifindMOf
function takes an IndexedFold
or IndexedTraversal
, a monadic predicate that is also
supplied the index, a structure and returns in the monad the left-most element of the structure
matching the predicate, or Nothing
if there is no such element.
When you don't need access to the index then findMOf
is more flexible in what it accepts.
findMOf
l ≡ifindMOf
l.
const
ifindMOf
::Monad
m =>IndexedGetter
i s a -> (i -> a -> mBool
) -> s -> m (Maybe
a)ifindMOf
::Monad
m =>IndexedFold
i s a -> (i -> a -> mBool
) -> s -> m (Maybe
a)ifindMOf
::Monad
m =>IndexedLens'
i s a -> (i -> a -> mBool
) -> s -> m (Maybe
a)ifindMOf
::Monad
m =>IndexedTraversal'
i s a -> (i -> a -> mBool
) -> s -> m (Maybe
a)
ifoldrOf' :: IndexedGetting i (Dual (Endo (r -> r))) s a -> (i -> a -> r -> r) -> r -> s -> r Source #
Strictly fold right over the elements of a structure with an index.
When you don't need access to the index then foldrOf'
is more flexible in what it accepts.
foldrOf'
l ≡ifoldrOf'
l.
const
ifoldrOf'
::IndexedGetter
i s a -> (i -> a -> r -> r) -> r -> s -> rifoldrOf'
::IndexedFold
i s a -> (i -> a -> r -> r) -> r -> s -> rifoldrOf'
::IndexedLens'
i s a -> (i -> a -> r -> r) -> r -> s -> rifoldrOf'
::IndexedTraversal'
i s a -> (i -> a -> r -> r) -> r -> s -> r
ifoldlOf' :: IndexedGetting i (Endo (r -> r)) s a -> (i -> r -> a -> r) -> r -> s -> r Source #
Fold over the elements of a structure with an index, associating to the left, but strictly.
When you don't need access to the index then foldlOf'
is more flexible in what it accepts.
foldlOf'
l ≡ifoldlOf'
l.
const
ifoldlOf'
::IndexedGetter
i s a -> (i -> r -> a -> r) -> r -> s -> rifoldlOf'
::IndexedFold
i s a -> (i -> r -> a -> r) -> r -> s -> rifoldlOf'
::IndexedLens'
i s a -> (i -> r -> a -> r) -> r -> s -> rifoldlOf'
::IndexedTraversal'
i s a -> (i -> r -> a -> r) -> r -> s -> r
ifoldrMOf :: Monad m => IndexedGetting i (Dual (Endo (r -> m r))) s a -> (i -> a -> r -> m r) -> r -> s -> m r Source #
Monadic fold right over the elements of a structure with an index.
When you don't need access to the index then foldrMOf
is more flexible in what it accepts.
foldrMOf
l ≡ifoldrMOf
l.
const
ifoldrMOf
::Monad
m =>IndexedGetter
i s a -> (i -> a -> r -> m r) -> r -> s -> m rifoldrMOf
::Monad
m =>IndexedFold
i s a -> (i -> a -> r -> m r) -> r -> s -> m rifoldrMOf
::Monad
m =>IndexedLens'
i s a -> (i -> a -> r -> m r) -> r -> s -> m rifoldrMOf
::Monad
m =>IndexedTraversal'
i s a -> (i -> a -> r -> m r) -> r -> s -> m r
ifoldlMOf :: Monad m => IndexedGetting i (Endo (r -> m r)) s a -> (i -> r -> a -> m r) -> r -> s -> m r Source #
Monadic fold over the elements of a structure with an index, associating to the left.
When you don't need access to the index then foldlMOf
is more flexible in what it accepts.
foldlMOf
l ≡ifoldlMOf
l.
const
ifoldlMOf
::Monad
m =>IndexedGetter
i s a -> (i -> r -> a -> m r) -> r -> s -> m rifoldlMOf
::Monad
m =>IndexedFold
i s a -> (i -> r -> a -> m r) -> r -> s -> m rifoldlMOf
::Monad
m =>IndexedLens'
i s a -> (i -> r -> a -> m r) -> r -> s -> m rifoldlMOf
::Monad
m =>IndexedTraversal'
i s a -> (i -> r -> a -> m r) -> r -> s -> m r
itoListOf :: IndexedGetting i (Endo [(i, a)]) s a -> s -> [(i, a)] Source #
Extract the key-value pairs from a structure.
When you don't need access to the indices in the result, then toListOf
is more flexible in what it accepts.
toListOf
l ≡map
snd
.
itoListOf
l
itoListOf
::IndexedGetter
i s a -> s -> [(i,a)]itoListOf
::IndexedFold
i s a -> s -> [(i,a)]itoListOf
::IndexedLens'
i s a -> s -> [(i,a)]itoListOf
::IndexedTraversal'
i s a -> s -> [(i,a)]
elemIndexOf :: Eq a => IndexedGetting i (First i) s a -> a -> s -> Maybe i Source #
Retrieve the index of the first value targeted by a IndexedFold
or IndexedTraversal
which is equal to a given value.
elemIndex
≡elemIndexOf
folded
elemIndexOf
::Eq
a =>IndexedFold
i s a -> a -> s ->Maybe
ielemIndexOf
::Eq
a =>IndexedTraversal'
i s a -> a -> s ->Maybe
i
elemIndicesOf :: Eq a => IndexedGetting i (Endo [i]) s a -> a -> s -> [i] Source #
Retrieve the indices of the values targeted by a IndexedFold
or IndexedTraversal
which are equal to a given value.
elemIndices
≡elemIndicesOf
folded
elemIndicesOf
::Eq
a =>IndexedFold
i s a -> a -> s -> [i]elemIndicesOf
::Eq
a =>IndexedTraversal'
i s a -> a -> s -> [i]
findIndexOf :: IndexedGetting i (First i) s a -> (a -> Bool) -> s -> Maybe i Source #
Retrieve the index of the first value targeted by a IndexedFold
or IndexedTraversal
which satisfies a predicate.
findIndex
≡findIndexOf
folded
findIndexOf
::IndexedFold
i s a -> (a ->Bool
) -> s ->Maybe
ifindIndexOf
::IndexedTraversal'
i s a -> (a ->Bool
) -> s ->Maybe
i
findIndicesOf :: IndexedGetting i (Endo [i]) s a -> (a -> Bool) -> s -> [i] Source #
Retrieve the indices of the values targeted by a IndexedFold
or IndexedTraversal
which satisfy a predicate.
findIndices
≡findIndicesOf
folded
findIndicesOf
::IndexedFold
i s a -> (a ->Bool
) -> s -> [i]findIndicesOf
::IndexedTraversal'
i s a -> (a ->Bool
) -> s -> [i]
Building Indexed Folds
ifiltered :: (Indexable i p, Applicative f) => (i -> a -> Bool) -> Optical' p (Indexed i) f a a Source #
Filter an IndexedFold
or IndexedGetter
, obtaining an IndexedFold
.
>>>
[0,0,0,5,5,5]^..traversed.ifiltered (\i a -> i <= a)
[0,5,5,5]
Compose with ifiltered
to filter another IndexedLens
, IndexedIso
, IndexedGetter
, IndexedFold
(or IndexedTraversal
) with
access to both the value and the index.
Note: As with filtered
, this is not a legal IndexedTraversal
, unless you are very careful not to invalidate the predicate on the target!
itakingWhile :: (Indexable i p, Profunctor q, Contravariant f, Applicative f) => (i -> a -> Bool) -> Optical' (Indexed i) q (Const (Endo (f s)) :: Type -> Type) s a -> Optical' p q f s a Source #
Obtain an IndexedFold
by taking elements from another
IndexedFold
, IndexedLens
, IndexedGetter
or IndexedTraversal
while a predicate holds.
itakingWhile
:: (i -> a ->Bool
) ->IndexedFold
i s a ->IndexedFold
i s aitakingWhile
:: (i -> a ->Bool
) ->IndexedTraversal'
i s a ->IndexedFold
i s aitakingWhile
:: (i -> a ->Bool
) ->IndexedLens'
i s a ->IndexedFold
i s aitakingWhile
:: (i -> a ->Bool
) ->IndexedGetter
i s a ->IndexedFold
i s a
Note: Applying itakingWhile
to an IndexedLens
or IndexedTraversal
will still allow you to use it as a
pseudo-IndexedTraversal
, but if you change the value of any target to one where the predicate returns
False
, then you will break the Traversal
laws and Traversal
fusion will no longer be sound.
idroppingWhile :: (Indexable i p, Profunctor q, Applicative f) => (i -> a -> Bool) -> Optical (Indexed i) q (Compose (State Bool) f) s t a a -> Optical p q f s t a a Source #
Obtain an IndexedFold
by dropping elements from another IndexedFold
, IndexedLens
, IndexedGetter
or IndexedTraversal
while a predicate holds.
idroppingWhile
:: (i -> a ->Bool
) ->IndexedFold
i s a ->IndexedFold
i s aidroppingWhile
:: (i -> a ->Bool
) ->IndexedTraversal'
i s a ->IndexedFold
i s a -- see notesidroppingWhile
:: (i -> a ->Bool
) ->IndexedLens'
i s a ->IndexedFold
i s a -- see notesidroppingWhile
:: (i -> a ->Bool
) ->IndexedGetter
i s a ->IndexedFold
i s a
Note: As with droppingWhile
applying idroppingWhile
to an IndexedLens
or IndexedTraversal
will still
allow you to use it as a pseudo-IndexedTraversal
, but if you change the value of the first target to one
where the predicate returns True
, then you will break the Traversal
laws and Traversal
fusion will
no longer be sound.
Internal types
data Traversed a (f :: Type -> Type) Source #
Used internally by traverseOf_
and the like.
The argument a
of the result should not be used!
Instances
Applicative f => Monoid (Traversed a f) Source # | |
Applicative f => Semigroup (Traversed a f) Source # | |
data Sequenced a (m :: Type -> Type) Source #
Used internally by mapM_
and the like.
The argument a
of the result should not be used!
See 4.16 Changelog entry for the explanation of "why not Apply f =>"?
Fold with Reified Monoid
foldByOf :: Fold s a -> (a -> a -> a) -> a -> s -> a Source #
Fold a value using a specified Fold
and Monoid
operations.
This is like foldBy
where the Foldable
instance can be
manually specified.
foldByOf
folded
≡foldBy
foldByOf
::Getter
s a -> (a -> a -> a) -> a -> s -> afoldByOf
::Fold
s a -> (a -> a -> a) -> a -> s -> afoldByOf
::Lens'
s a -> (a -> a -> a) -> a -> s -> afoldByOf
::Traversal'
s a -> (a -> a -> a) -> a -> s -> afoldByOf
::Iso'
s a -> (a -> a -> a) -> a -> s -> a
>>>
foldByOf both (++) [] ("hello","world")
"helloworld"
foldMapByOf :: Fold s a -> (r -> r -> r) -> r -> (a -> r) -> s -> r Source #
Fold a value using a specified Fold
and Monoid
operations.
This is like foldMapBy
where the Foldable
instance can be
manually specified.
foldMapByOf
folded
≡foldMapBy
foldMapByOf
::Getter
s a -> (r -> r -> r) -> r -> (a -> r) -> s -> rfoldMapByOf
::Fold
s a -> (r -> r -> r) -> r -> (a -> r) -> s -> rfoldMapByOf
::Traversal'
s a -> (r -> r -> r) -> r -> (a -> r) -> s -> rfoldMapByOf
::Lens'
s a -> (r -> r -> r) -> r -> (a -> r) -> s -> rfoldMapByOf
::Iso'
s a -> (r -> r -> r) -> r -> (a -> r) -> s -> r
>>>
foldMapByOf both (+) 0 length ("hello","world")
10