lens-1.7.1: Lenses, Folds and Traversals

PortabilityRank2Types
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe-Infered

Control.Lens.Fold

Contents

Description

A Fold a c is a generalization of something Foldable. It allows you to extract multiple results from a container. A Foldable container can be characterized by the behavior of foldMap :: (Foldable t, Monoid m) => (c -> m) -> t c -> m. Since we want to be able to work with monomorphic containers, we could generalize this signature to forall m. Monoid m => (c -> m) -> a -> m, and then decorate it with Accessor to obtain

type Fold a c = forall m b d. Monoid m => Getting m a b c d

Every Getter is a valid Fold that simply doesn't use the Monoid it is passed.

But 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

Folds

type Fold a c = forall f b d. (Gettable f, Applicative f) => (c -> f d) -> a -> f bSource

A Fold describes how to retrieve multiple values in a way that can be composed with other lens-like constructions.

A Fold a c provides a structure with operations very similar to those of the Foldable typeclass, see foldMapOf and the other Fold combinators.

By convention, if there exists a foo method that expects a Foldable (f c), then there should be a fooOf method that takes a Fold a c and a value of type a.

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.

Building Folds

folding :: (Foldable f, Applicative g, Gettable g) => (a -> f c) -> LensLike g a b c dSource

Obtain a Fold by lifting an operation that returns a foldable result.

This can be useful to lift operations from Data.List and elsewhere into a Fold.

folded :: Foldable f => Fold (f c) cSource

Obtain a Fold from any Foldable.

unfolded :: (b -> Maybe (a, b)) -> Fold b aSource

Build a fold that unfolds its values from a seed.

unfoldr = toListOf . unfolded

iterated :: (a -> a) -> Fold a aSource

x ^. iterated f Return an infinite fold of repeated applications of f to x.

 toListOf (iterated f) a = iterate f a

filtered :: (Gettable f, Applicative f) => (c -> Bool) -> LensLike f a b c d -> LensLike f a b c dSource

Obtain a Fold by filtering a Lens, Iso, Getter, Fold or Traversal.

backwards :: LensLike (Backwards f) a b c d -> LensLike f a b c dSource

This allows you to traverse the elements of a Traversal or Fold in the opposite order.

Note: backwards should have no impact on a Getter Setter, Lens or Iso.

To change the direction of an Iso, use from.

repeated :: Fold a aSource

Fold by repeating the input forever.

repeat = toListOf repeated

replicated :: Int -> Fold a aSource

A fold that replicates its input n times.

replicate n = toListOf (replicated n)

cycled :: (Applicative f, Gettable f) => LensLike f a b c d -> LensLike f a b c dSource

Transform a fold into a fold that loops over its elements over and over.

>>> import Control.Lens
>>> take 6 $ toListOf (cycled traverse) [1,2,3]
[1,2,3,1,2,3]

takingWhile :: (Gettable f, Applicative f) => (c -> Bool) -> Getting (Endo (f b)) a b c d -> LensLike f a b c dSource

Obtain a Fold by taking elements from another Fold, Lens, Iso, Getter or Traversal while a predicate holds.

takeWhile p = toListOf (takingWhile p folded)
>>> toListOf (takingWhile (<=3) folded) [1..]
[1,2,3]

droppingWhile :: (Gettable f, Applicative f) => (c -> Bool) -> Getting (Endo (f b)) a b c d -> LensLike f a b c dSource

Obtain a Fold by dropping elements from another Fold, Lens, Iso, Getter or Traversal while a predicate holds.

dropWhile p = toListOf (droppingWhile p folded)
>>> toListOf (droppingWhile (<=3) folded) [1..6]
[4,5,6]

Folding

foldMapOf :: Getting r a b c d -> (c -> r) -> a -> rSource

foldMap = foldMapOf folded
foldMapOf = views
 foldMapOf ::             Getter a c        -> (c -> r) -> a -> r
 foldMapOf :: Monoid r => Fold a c          -> (c -> r) -> a -> r
 foldMapOf ::             Lens a b c d      -> (c -> r) -> a -> r
 foldMapOf ::             Iso a b c d       -> (c -> r) -> a -> r
 foldMapOf :: Monoid r => Traversal a b c d -> (c -> r) -> a -> r

foldOf :: Getting c a b c d -> a -> cSource

fold = foldOf folded
foldOf = view
 foldOf ::             Getter a m        -> a -> m
 foldOf :: Monoid m => Fold a m          -> a -> m
 foldOf ::             Lens a b m d      -> a -> m
 foldOf ::             Iso a b m d       -> a -> m
 foldOf :: Monoid m => Traversal a b m d -> a -> m

foldrOf :: Getting (Endo e) a b c d -> (c -> e -> e) -> e -> a -> eSource

Right-associative fold of parts of a structure that are viewed through a Lens, Getter, Fold or Traversal.

foldr = foldrOf folded
 foldrOf :: Getter a c        -> (c -> e -> e) -> e -> a -> e
 foldrOf :: Fold a c          -> (c -> e -> e) -> e -> a -> e
 foldrOf :: Lens a b c d      -> (c -> e -> e) -> e -> a -> e
 foldrOf :: Iso a b c d       -> (c -> e -> e) -> e -> a -> e
 foldrOf :: Traversal a b c d -> (c -> e -> e) -> e -> a -> e

foldlOf :: Getting (Dual (Endo e)) a b c d -> (e -> c -> e) -> e -> a -> eSource

Left-associative fold of the parts of a structure that are viewed through a Lens, Getter, Fold or Traversal.

foldl = foldlOf folded
 foldlOf :: Getter a c        -> (e -> c -> e) -> e -> a -> e
 foldlOf :: Fold a c          -> (e -> c -> e) -> e -> a -> e
 foldlOf :: Lens a b c d      -> (e -> c -> e) -> e -> a -> e
 foldlOf :: Iso a b c d       -> (e -> c -> e) -> e -> a -> e
 foldlOf :: Traversal a b c d -> (e -> c -> e) -> e -> a -> e

toListOf :: Getting [c] a b c d -> a -> [c]Source

toList = toListOf folded
 toListOf :: Getter a c        -> a -> [c]
 toListOf :: Fold a c          -> a -> [c]
 toListOf :: Lens a b c d      -> a -> [c]
 toListOf :: Iso a b c d       -> a -> [c]
 toListOf :: Traversal a b c d -> a -> [c]

anyOf :: Getting Any a b c d -> (c -> Bool) -> a -> BoolSource

any = anyOf folded
 anyOf :: Getter a c        -> (c -> Bool) -> a -> Bool
 anyOf :: Fold a c          -> (c -> Bool) -> a -> Bool
 anyOf :: Lens a b c d      -> (c -> Bool) -> a -> Bool
 anyOf :: Iso a b c d       -> (c -> Bool) -> a -> Bool
 anyOf :: Traversal a b c d -> (c -> Bool) -> a -> Bool

allOf :: Getting All a b c d -> (c -> Bool) -> a -> BoolSource

all = allOf folded
 allOf :: Getter a c        -> (c -> Bool) -> a -> Bool
 allOf :: Fold a c          -> (c -> Bool) -> a -> Bool
 allOf :: Lens a b c d      -> (c -> Bool) -> a -> Bool
 allOf :: Iso a b c d       -> (c -> Bool) -> a -> Bool
 allOf :: Traversal a b c d -> (c -> Bool) -> a -> Bool

andOf :: Getting All a b Bool d -> a -> BoolSource

and = andOf folded
 andOf :: Getter a Bool       -> a -> Bool
 andOf :: Fold a Bool         -> a -> Bool
 andOf :: Lens a b Bool d     -> a -> Bool
 andOf :: Iso a b Bool d      -> a -> Bool
 andOf :: Traversl a b Bool d -> a -> Bool

orOf :: Getting Any a b Bool d -> a -> BoolSource

or = orOf folded
 orOf :: Getter a Bool        -> a -> Bool
 orOf :: Fold a Bool          -> a -> Bool
 orOf :: Lens a b Bool d      -> a -> Bool
 orOf :: Iso a b Bool d       -> a -> Bool
 orOf :: Traversal a b Bool d -> a -> Bool

productOf :: Getting (Product c) a b c d -> a -> cSource

product = productOf folded
 productOf ::          Getter a c        -> a -> c
 productOf :: Num c => Fold a c          -> a -> c
 productOf ::          Lens a b c d      -> a -> c
 productOf ::          Iso a b c d       -> a -> c
 productOf :: Num c => Traversal a b c d -> a -> c

sumOf :: Getting (Sum c) a b c d -> a -> cSource

sum = sumOf folded
sumOf _1 :: (a, b) -> a
sumOf (folded . _1) :: (Foldable f, Num a) => f (a, b) -> a
 sumOf ::          Getter a c        -> a -> c
 sumOf :: Num c => Fold a c          -> a -> c
 sumOf ::          Lens a b c d      -> a -> c
 sumOf ::          Iso a b c d       -> a -> c
 sumOf :: Num c => Traversal a b c d -> a -> c

traverseOf_ :: Functor f => Getting (Traversed f) a b c d -> (c -> f e) -> a -> f ()Source

When passed a Getter, traverseOf_ can work over a Functor.

When passed a Fold, traverseOf_ requires an Applicative.

traverse_ = traverseOf_ folded
traverseOf_ _2 :: Functor f => (c -> f e) -> (c1, c) -> f ()
traverseOf_ traverseLeft :: Applicative f => (a -> f b) -> Either a c -> f ()

The rather specific signature of traverseOf_ allows it to be used as if the signature was either:

 traverseOf_ :: Functor f     => Getter a c        -> (c -> f e) -> a -> f ()
 traverseOf_ :: Applicative f => Fold a c          -> (c -> f e) -> a -> f ()
 traverseOf_ :: Functor f     => Lens a b c d      -> (c -> f e) -> a -> f ()
 traverseOf_ :: Functor f     => Iso a b c d       -> (c -> f e) -> a -> f ()
 traverseOf_ :: Applicative f => Traversal a b c d -> (c -> f e) -> a -> f ()

forOf_ :: Functor f => Getting (Traversed f) a b c d -> a -> (c -> f e) -> f ()Source

for_ = forOf_ folded
 forOf_ :: Functor f     => Getter a c        -> a -> (c -> f e) -> f ()
 forOf_ :: Applicative f => Fold a c          -> a -> (c -> f e) -> f ()
 forOf_ :: Functor f     => Lens a b c d      -> a -> (c -> f e) -> f ()
 forOf_ :: Functor f     => Iso a b c d       -> a -> (c -> f e) -> f ()
 forOf_ :: Applicative f => Traversal a b c d -> a -> (c -> f e) -> f ()

sequenceAOf_ :: Functor f => Getting (Traversed f) a b (f ()) d -> a -> f ()Source

sequenceA_ = sequenceAOf_ folded
 sequenceAOf_ :: Functor f     => Getter a (f ())        -> a -> f ()
 sequenceAOf_ :: Applicative f => Fold a (f ())          -> a -> f ()
 sequenceAOf_ :: Functor f     => Lens a b (f ()) d      -> a -> f ()
 sequenceAOf_ :: Functor f     => Iso a b (f ()) d       -> a -> f ()
 sequenceAOf_ :: Applicative f => Traversal a b (f ()) d -> a -> f ()

mapMOf_ :: Monad m => Getting (Sequenced m) a b c d -> (c -> m e) -> a -> m ()Source

mapM_ = mapMOf_ folded
 mapMOf_ :: Monad m => Getter a c        -> (c -> m e) -> a -> m ()
 mapMOf_ :: Monad m => Fold a c          -> (c -> m e) -> a -> m ()
 mapMOf_ :: Monad m => Lens a b c d      -> (c -> m e) -> a -> m ()
 mapMOf_ :: Monad m => Iso a b c d       -> (c -> m e) -> a -> m ()
 mapMOf_ :: Monad m => Traversal a b c d -> (c -> m e) -> a -> m ()

forMOf_ :: Monad m => Getting (Sequenced m) a b c d -> a -> (c -> m e) -> m ()Source

forM_ = forMOf_ folded
 forMOf_ :: Monad m => Getter a c        -> a -> (c -> m e) -> m ()
 forMOf_ :: Monad m => Fold a c          -> a -> (c -> m e) -> m ()
 forMOf_ :: Monad m => Lens a b c d      -> a -> (c -> m e) -> m ()
 forMOf_ :: Monad m => Iso a b c d       -> a -> (c -> m e) -> m ()
 forMOf_ :: Monad m => Traversal a b c d -> a -> (c -> m e) -> m ()

sequenceOf_ :: Monad m => Getting (Sequenced m) a b (m c) d -> a -> m ()Source

sequence_ = sequenceOf_ folded
 sequenceOf_ :: Monad m => Getter a (m b)        -> a -> m ()
 sequenceOf_ :: Monad m => Fold a (m b)          -> a -> m ()
 sequenceOf_ :: Monad m => Lens a b (m b) d      -> a -> m ()
 sequenceOf_ :: Monad m => Iso a b (m b) d       -> a -> m ()
 sequenceOf_ :: Monad m => Traversal a b (m b) d -> a -> m ()

asumOf :: Alternative f => Getting (Endo (f c)) a b (f c) d -> a -> f cSource

The sum of a collection of actions, generalizing concatOf.

asum = asumOf folded
 asumOf :: Alternative f => Getter a c        -> a -> f c
 asumOf :: Alternative f => Fold a c          -> a -> f c
 asumOf :: Alternative f => Lens a b c d      -> a -> f c
 asumOf :: Alternative f => Iso a b c d       -> a -> f c
 asumOf :: Alternative f => Traversal a b c d -> a -> f c

msumOf :: MonadPlus m => Getting (Endo (m c)) a b (m c) d -> a -> m cSource

The sum of a collection of actions, generalizing concatOf.

msum = msumOf folded
 msumOf :: MonadPlus m => Getter a c        -> a -> m c
 msumOf :: MonadPlus m => Fold a c          -> a -> m c
 msumOf :: MonadPlus m => Lens a b c d      -> a -> m c
 msumOf :: MonadPlus m => Iso a b c d       -> a -> m c
 msumOf :: MonadPlus m => Traversal a b c d -> a -> m c

concatMapOf :: Getting [e] a b c d -> (c -> [e]) -> a -> [e]Source

concatMap = concatMapOf folded
 concatMapOf :: Getter a c        -> (c -> [e]) -> a -> [e]
 concatMapOf :: Fold a c          -> (c -> [e]) -> a -> [e]
 concatMapOf :: Lens a b c d      -> (c -> [e]) -> a -> [e]
 concatMapOf :: Iso a b c d       -> (c -> [e]) -> a -> [e]
 concatMapOf :: Traversal a b c d -> (c -> [e]) -> a -> [e]

concatOf :: Getting [e] a b [e] d -> a -> [e]Source

concat = concatOf folded
 concatOf :: Getter a [e]        -> a -> [e]
 concatOf :: Fold a [e]          -> a -> [e]
 concatOf :: Iso a b [e] d       -> a -> [e]
 concatOf :: Lens a b [e] d      -> a -> [e]
 concatOf :: Traversal a b [e] d -> a -> [e]

elemOf :: Eq c => Getting Any a b c d -> c -> a -> BoolSource

elem = elemOf folded
 elemOf :: Eq c => Getter a c        -> c -> a -> Bool
 elemOf :: Eq c => Fold a c          -> c -> a -> Bool
 elemOf :: Eq c => Lens a b c d      -> c -> a -> Bool
 elemOf :: Eq c => Iso a b c d       -> c -> a -> Bool
 elemOf :: Eq c => Traversal a b c d -> c -> a -> Bool

notElemOf :: Eq c => Getting All a b c d -> c -> a -> BoolSource

notElem = notElemOf folded
 notElemOf :: Eq c => Getter a c        -> c -> a -> Bool
 notElemOf :: Eq c => Fold a c          -> c -> a -> Bool
 notElemOf :: Eq c => Iso a b c d       -> c -> a -> Bool
 notElemOf :: Eq c => Lens a b c d      -> c -> a -> Bool
 notElemOf :: Eq c => Traversal a b c d -> c -> a -> Bool

lengthOf :: Getting (Sum Int) a b c d -> a -> IntSource

Note: this can be rather inefficient for large containers.

length = lengthOf folded
>>> lengthOf _1 ("hello",())
1
lengthOf (folded . folded) :: Foldable f => f (g a) -> Int
 lengthOf :: Getter a c        -> a -> Int
 lengthOf :: Fold a c          -> a -> Int
 lengthOf :: Lens a b c d      -> a -> Int
 lengthOf :: Iso a b c d       -> a -> Int
 lengthOf :: Traversal a b c d -> a -> Int

nullOf :: Getting All a b c d -> a -> BoolSource

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 (folded . _1 . folded) :: Foldable f => f (g a, b) -> Bool
 nullOf :: Getter a c        -> a -> Bool
 nullOf :: Fold a c          -> a -> Bool
 nullOf :: Iso a b c d       -> a -> Bool
 nullOf :: Lens a b c d      -> a -> Bool
 nullOf :: Traversal a b c d -> a -> Bool

headOf :: Getting (First c) a b c d -> a -> Maybe cSource

Perform a safe head of a Fold or Traversal or retrieve Just the result from a Getter or Lens.

listToMaybe . toList = headOf folded
 headOf :: Getter a c        -> a -> Maybe c
 headOf :: Fold a c          -> a -> Maybe c
 headOf :: Lens a b c d      -> a -> Maybe c
 headOf :: Iso a b c d       -> a -> Maybe c
 headOf :: Traversal a b c d -> a -> Maybe c

lastOf :: Getting (Last c) a b c d -> a -> Maybe cSource

Perform a safe last of a Fold or Traversal or retrieve Just the result from a Getter or Lens.

 lastOf :: Getter a c        -> a -> Maybe c
 lastOf :: Fold a c          -> a -> Maybe c
 lastOf :: Lens a b c d      -> a -> Maybe c
 lastOf :: Iso a b c d       -> a -> Maybe c
 lastOf :: Traversal a b c d -> a -> Maybe c

maximumOf :: Getting (Max c) a b c d -> a -> Maybe cSource

Obtain the maximum element (if any) targeted by a Fold or Traversal

Note: maximumOf on a valid Iso, Lens or Getter will always return Just a value.

maximum = fromMaybe (error empty) . maximumOf folded
 maximumOf ::          Getter a c        -> a -> Maybe c
 maximumOf :: Ord c => Fold a c          -> a -> Maybe c
 maximumOf ::          Iso a b c d       -> a -> Maybe c
 maximumOf ::          Lens a b c d      -> a -> Maybe c
 maximumOf :: Ord c => Traversal a b c d -> a -> Maybe c

minimumOf :: Getting (Min c) a b c d -> a -> Maybe cSource

Obtain the minimum element (if any) targeted by a Fold or Traversal

Note: minimumOf on a valid Iso, Lens or Getter will always return Just a value.

minimum = fromMaybe (error empty) . minimumOf folded
 minimumOf ::          Getter a c        -> a -> Maybe c
 minimumOf :: Ord c => Fold a c          -> a -> Maybe c
 minimumOf ::          Iso a b c d       -> a -> Maybe c
 minimumOf ::          Lens a b c d      -> a -> Maybe c
 minimumOf :: Ord c => Traversal a b c d -> a -> Maybe c

maximumByOf :: Getting (Endo (Maybe c)) a b c d -> (c -> c -> Ordering) -> a -> Maybe cSource

Obtain the maximum element (if any) targeted by a Fold, Traversal, Lens, Iso, or Getter according to a user supplied ordering.

maximumBy cmp = fromMaybe (error empty) . maximumByOf folded cmp
 maximumByOf :: Getter a c        -> (c -> c -> Ordering) -> a -> Maybe c
 maximumByOf :: Fold a c          -> (c -> c -> Ordering) -> a -> Maybe c
 maximumByOf :: Iso a b c d       -> (c -> c -> Ordering) -> a -> Maybe c
 maximumByOf :: Lens a b c d      -> (c -> c -> Ordering) -> a -> Maybe c
 maximumByOf :: Traversal a b c d -> (c -> c -> Ordering) -> a -> Maybe c

minimumByOf :: Getting (Endo (Maybe c)) a b c d -> (c -> c -> Ordering) -> a -> Maybe cSource

Obtain the minimum element (if any) targeted by a Fold, Traversal, Lens, Iso or Getter according to a user supplied ordering.

 minimumBy cmp = fromMaybe (error "empty") . minimumByOf folded cmp
 minimumByOf :: Getter a c        -> (c -> c -> Ordering) -> a -> Maybe c
 minimumByOf :: Fold a c          -> (c -> c -> Ordering) -> a -> Maybe c
 minimumByOf :: Iso a b c d       -> (c -> c -> Ordering) -> a -> Maybe c
 minimumByOf :: Lens a b c d      -> (c -> c -> Ordering) -> a -> Maybe c
 minimumByOf :: Traversal a b c d -> (c -> c -> Ordering) -> a -> Maybe c

findOf :: Getting (First c) a b c d -> (c -> Bool) -> a -> Maybe cSource

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 :: Getter a c        -> (c -> Bool) -> a -> Maybe c
 findOf :: Fold a c          -> (c -> Bool) -> a -> Maybe c
 findOf :: Iso a b c d       -> (c -> Bool) -> a -> Maybe c
 findOf :: Lens a b c d      -> (c -> Bool) -> a -> Maybe c
 findOf :: Traversal a b c d -> (c -> Bool) -> a -> Maybe c

foldrOf' :: Getting (Dual (Endo (e -> e))) a b c d -> (c -> e -> e) -> e -> a -> eSource

Strictly fold right over the elements of a structure.

foldr' = foldrOf' folded
 foldrOf' :: Getter a c        -> (c -> e -> e) -> e -> a -> e
 foldrOf' :: Fold a c          -> (c -> e -> e) -> e -> a -> e
 foldrOf' :: Iso a b c d       -> (c -> e -> e) -> e -> a -> e
 foldrOf' :: Lens a b c d      -> (c -> e -> e) -> e -> a -> e
 foldrOf' :: Traversal a b c d -> (c -> e -> e) -> e -> a -> e

foldlOf' :: Getting (Endo (e -> e)) a b c d -> (e -> c -> e) -> e -> a -> eSource

Fold over the elements of a structure, associating to the left, but strictly.

foldl' = foldlOf' folded
 foldlOf' :: Getter a c          -> (e -> c -> e) -> e -> a -> e
 foldlOf' :: Fold a c            -> (e -> c -> e) -> e -> a -> e
 foldlOf' :: Iso a b c d         -> (e -> c -> e) -> e -> a -> e
 foldlOf' :: Lens a b c d        -> (e -> c -> e) -> e -> a -> e
 foldlOf' :: Traversal a b c d   -> (e -> c -> e) -> e -> a -> e

foldr1Of :: Getting (Endo (Maybe c)) a b c d -> (c -> c -> c) -> a -> cSource

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 l f = foldr1 f . toListOf l
foldr1 = foldr1Of folded
 foldr1Of :: Getter a c        -> (c -> c -> c) -> a -> c
 foldr1Of :: Fold a c          -> (c -> c -> c) -> a -> c
 foldr1Of :: Iso a b c d       -> (c -> c -> c) -> a -> c
 foldr1Of :: Lens a b c d      -> (c -> c -> c) -> a -> c
 foldr1Of :: Traversal a b c d -> (c -> c -> c) -> a -> c

foldl1Of :: Getting (Dual (Endo (Maybe c))) a b c d -> (c -> c -> c) -> a -> cSource

A variant of foldlOf that has no base case and thus may only be applied to lenses and strutures such that the lens views at least one element of the structure.

foldl1Of l f = foldl1Of l f . toList
foldl1 = foldl1Of folded
 foldl1Of :: Getter a c        -> (c -> c -> c) -> a -> c
 foldl1Of :: Fold a c          -> (c -> c -> c) -> a -> c
 foldl1Of :: Iso a b c d       -> (c -> c -> c) -> a -> c
 foldl1Of :: Lens a b c d      -> (c -> c -> c) -> a -> c
 foldl1Of :: Traversal a b c d -> (c -> c -> c) -> a -> c

foldrMOf :: Monad m => Getting (Dual (Endo (e -> m e))) a b c d -> (c -> e -> m e) -> e -> a -> m eSource

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 a c        -> (c -> e -> m e) -> e -> a -> m e
 foldrMOf :: Monad m => Fold a c          -> (c -> e -> m e) -> e -> a -> m e
 foldrMOf :: Monad m => Iso a b c d       -> (c -> e -> m e) -> e -> a -> m e
 foldrMOf :: Monad m => Lens a b c d      -> (c -> e -> m e) -> e -> a -> m e
 foldrMOf :: Monad m => Traversal a b c d -> (c -> e -> m e) -> e -> a -> m e

foldlMOf :: Monad m => Getting (Endo (e -> m e)) a b c d -> (e -> c -> m e) -> e -> a -> m eSource

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 a c        -> (e -> c -> m e) -> e -> a -> m e
 foldlMOf :: Monad m => Fold a c          -> (e -> c -> m e) -> e -> a -> m e
 foldlMOf :: Monad m => Iso a b c d       -> (e -> c -> m e) -> e -> a -> m e
 foldlMOf :: Monad m => Lens a b c d      -> (e -> c -> m e) -> e -> a -> m e
 foldlMOf :: Monad m => Traversal a b c d -> (e -> c -> m e) -> e -> a -> m e