| Portability | Rank2Types |
|---|---|
| Stability | provisional |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Safe Haskell | None |
Control.Lens.Fold
Contents
Description
A is a generalization of something Fold a cFoldable. It allows
you to extract multiple results from a container. A Foldable container
can be characterized by the behavior of
foldMap :: (.
Since we want to be able to work with monomorphic containers, we could
generalize this signature to Foldable t, Monoid m) => (c -> m) -> t c -> mforall m. ,
and then decorate it with Monoid m => (c -> m) -> a -> mAccessor to obtain
typeFolda c = forall m.Monoidm =>Gettingm a a c c
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.
- type Fold a c = forall f. (Gettable f, Applicative f) => (c -> f c) -> a -> f a
- (^?) :: a -> Getting (First c) a b c d -> Maybe c
- (^..) :: a -> Getting [c] a b c d -> [c]
- folding :: (Foldable f, Applicative g, Gettable g) => (a -> f c) -> LensLike g a b c d
- folded :: Foldable f => Fold (f c) c
- unfolded :: (b -> Maybe (a, b)) -> Fold b a
- iterated :: (a -> a) -> Fold a a
- filtered :: (Gettable f, Applicative f) => (c -> Bool) -> LensLike f a b c d -> LensLike f a b c d
- backwards :: LensLike (Backwards f) a b c d -> LensLike f a b c d
- repeated :: Fold a a
- replicated :: Int -> Fold a a
- cycled :: (Applicative f, Gettable f) => LensLike f a b c d -> LensLike f a b c d
- takingWhile :: (Gettable f, Applicative f) => (c -> Bool) -> Getting (Endo (f a)) a a c c -> LensLike f a a c c
- droppingWhile :: (Gettable f, Applicative f) => (c -> Bool) -> Getting (Endo (f a)) a a c c -> LensLike f a a c c
- foldMapOf :: Getting r a b c d -> (c -> r) -> a -> r
- foldOf :: Getting c a b c d -> a -> c
- foldrOf :: Getting (Endo e) a b c d -> (c -> e -> e) -> e -> a -> e
- foldlOf :: Getting (Dual (Endo e)) a b c d -> (e -> c -> e) -> e -> a -> e
- toListOf :: Getting [c] a b c d -> a -> [c]
- anyOf :: Getting Any a b c d -> (c -> Bool) -> a -> Bool
- allOf :: Getting All a b c d -> (c -> Bool) -> a -> Bool
- andOf :: Getting All a b Bool d -> a -> Bool
- orOf :: Getting Any a b Bool d -> a -> Bool
- productOf :: Getting (Product c) a b c d -> a -> c
- sumOf :: Getting (Sum c) a b c d -> a -> c
- traverseOf_ :: Functor f => Getting (Traversed f) a b c d -> (c -> f e) -> a -> f ()
- forOf_ :: Functor f => Getting (Traversed f) a b c d -> a -> (c -> f e) -> f ()
- sequenceAOf_ :: Functor f => Getting (Traversed f) a b (f ()) d -> a -> f ()
- mapMOf_ :: Monad m => Getting (Sequenced m) a b c d -> (c -> m e) -> a -> m ()
- forMOf_ :: Monad m => Getting (Sequenced m) a b c d -> a -> (c -> m e) -> m ()
- sequenceOf_ :: Monad m => Getting (Sequenced m) a b (m c) d -> a -> m ()
- asumOf :: Alternative f => Getting (Endo (f c)) a b (f c) d -> a -> f c
- msumOf :: MonadPlus m => Getting (Endo (m c)) a b (m c) d -> a -> m c
- concatMapOf :: Getting [e] a b c d -> (c -> [e]) -> a -> [e]
- concatOf :: Getting [e] a b [e] d -> a -> [e]
- elemOf :: Eq c => Getting Any a b c d -> c -> a -> Bool
- notElemOf :: Eq c => Getting All a b c d -> c -> a -> Bool
- lengthOf :: Getting (Sum Int) a b c d -> a -> Int
- nullOf :: Getting All a b c d -> a -> Bool
- headOf :: Getting (First c) a b c d -> a -> Maybe c
- lastOf :: Getting (Last c) a b c d -> a -> Maybe c
- maximumOf :: Getting (Max c) a b c d -> a -> Maybe c
- minimumOf :: Getting (Min c) a b c d -> a -> Maybe c
- maximumByOf :: Getting (Endo (Maybe c)) a b c d -> (c -> c -> Ordering) -> a -> Maybe c
- minimumByOf :: Getting (Endo (Maybe c)) a b c d -> (c -> c -> Ordering) -> a -> Maybe c
- findOf :: Getting (First c) a b c d -> (c -> Bool) -> a -> Maybe c
- foldrOf' :: Getting (Dual (Endo (e -> e))) a b c d -> (c -> e -> e) -> e -> a -> e
- foldlOf' :: Getting (Endo (e -> e)) a b c d -> (e -> c -> e) -> e -> a -> e
- foldr1Of :: Getting (Endo (Maybe c)) a b c d -> (c -> c -> c) -> a -> c
- foldl1Of :: Getting (Dual (Endo (Maybe c))) 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 e
- foldlMOf :: Monad m => Getting (Endo (e -> m e)) a b c d -> (e -> c -> m e) -> e -> a -> m e
- newtype ReifiedFold a c = ReifyFold {
- reflectFold :: Fold a c
Folds
type Fold a c = forall f. (Gettable f, Applicative f) => (c -> f c) -> a -> f aSource
A Fold describes how to retrieve multiple values in a way that can be composed
with other lens-like constructions.
A provides a structure with operations very similar to those of the Fold a cFoldable
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 c)fooOf method that takes a and a value of type Fold a ca.
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.
(^?) :: a -> Getting (First c) a b c d -> Maybe cSource
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.
(^?) ≡flipheadOf
(^?) :: a ->Gettera c ->Maybec (^?) :: a ->Folda c ->Maybec (^?) :: a ->SimpleLensa c ->Maybec (^?) :: a ->SimpleIsoa c ->Maybec (^?) :: a ->SimpleTraversala c ->Maybec
(^..) :: a -> Getting [c] a b c d -> [c]Source
A convenient infix (flipped) version of toListOf.
>>>import Control.Lens>>>[[1,2],[3]]^..traverse.traverse[1,2,3]
>>>(1,2)^..both[1,2]
toListxs ≡ xs^..folded(^..) ≡fliptoListOf
(^..) :: a ->Gettera c -> [c] (^..) :: a ->Folda c -> [c] (^..) :: a ->SimpleLensa c -> [c] (^..) :: a ->SimpleIsoa c -> [c] (^..) :: a ->SimpleTraversala c -> [c]
Building Folds
filtered :: (Gettable f, Applicative f) => (c -> Bool) -> LensLike f a b c d -> LensLike f a b c dSource
replicated :: Int -> Fold a aSource
A fold that replicates its input n times.
replicaten ≡toListOf(replicatedn)
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 a)) a a c c -> LensLike f a a c cSource
droppingWhile :: (Gettable f, Applicative f) => (c -> Bool) -> Getting (Endo (f a)) a a c c -> LensLike f a a c cSource
Folding
foldMapOf :: Getting r a b c d -> (c -> r) -> a -> rSource
foldMap=foldMapOffolded
foldMapOf≡views
foldMapOf::Gettera c -> (c -> r) -> a -> rfoldMapOf::Monoidr =>Folda c -> (c -> r) -> a -> rfoldMapOf::SimpleLensa c -> (c -> r) -> a -> rfoldMapOf::SimpleIsoa c -> (c -> r) -> a -> rfoldMapOf::Monoidr =>SimpleTraversala c -> (c -> r) -> a -> r
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≡foldrOffolded
foldrOf::Gettera c -> (c -> e -> e) -> e -> a -> efoldrOf::Folda c -> (c -> e -> e) -> e -> a -> efoldrOf::SimpleLensa c -> (c -> e -> e) -> e -> a -> efoldrOf::SimpleIsoa c -> (c -> e -> e) -> e -> a -> efoldrOf::SimpleTraversala c -> (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≡foldlOffolded
foldlOf::Gettera c -> (e -> c -> e) -> e -> a -> efoldlOf::Folda c -> (e -> c -> e) -> e -> a -> efoldlOf::SimpleLensa c -> (e -> c -> e) -> e -> a -> efoldlOf::SimpleIsoa c -> (e -> c -> e) -> e -> a -> efoldlOf::SimpleTraversala c -> (e -> c -> e) -> e -> a -> e
anyOf :: Getting Any a b c d -> (c -> Bool) -> a -> BoolSource
Returns True if any target of a Fold satisfies a predicate.
>>>import Control.Lens>>>anyOf both (=='x') ('x','y')True>>>import Data.Data.Lens>>>anyOf biplate (== "world") (((),2::Int),"hello",("world",11))True
any≡anyOffolded
anyOf::Gettera c -> (c ->Bool) -> a ->BoolanyOf::Folda c -> (c ->Bool) -> a ->BoolanyOf::SimpleLensa b c d -> (c ->Bool) -> a ->BoolanyOf::SimpleIsoa b c d -> (c ->Bool) -> a ->BoolanyOf::SimpleTraversala b c d -> (c ->Bool) -> a ->Bool
allOf :: Getting All a b c d -> (c -> Bool) -> a -> BoolSource
Returns True if every target of a Fold satisfies a predicate.
>>>import Control.Lens>>>allOf both (>=3) (4,5)True>>>allOf folded (>=2) [1..10]False
all≡allOffolded
allOf::Gettera c -> (c ->Bool) -> a ->BoolallOf::Folda c -> (c ->Bool) -> a ->BoolallOf::SimpleLensa c -> (c ->Bool) -> a ->BoolallOf::SimpleIsoa c -> (c ->Bool) -> a ->BoolallOf::SimpleTraversala c -> (c ->Bool) -> a ->Bool
andOf :: Getting All a b Bool d -> a -> BoolSource
Returns True if every target of a Fold is True.
>>>import Control.Lens>>>andOf both (True,False)False>>>andOf both (True,True)True
and≡andOffolded
andOf::GetteraBool-> a ->BoolandOf::FoldaBool-> a ->BoolandOf::SimpleLensaBool-> a ->BoolandOf::SimpleIsoaBool-> a ->BoolandOf::SimpleTraversalaBool-> a ->Bool
orOf :: Getting Any a b Bool d -> a -> BoolSource
Returns True if any target of a Fold is True.
>>>import Control.Lens>>>orOf both (True,False)True>>>orOf both (False,False)False
or≡orOffolded
orOf::GetteraBool-> a ->BoolorOf::FoldaBool-> a ->BoolorOf::SimpleLensaBool-> a ->BoolorOf::SimpleIsoaBool-> a ->BoolorOf::SimpleTraversalaBool-> a ->Bool
productOf :: Getting (Product c) a b c d -> a -> cSource
Calculate the product of every number targeted by a Fold
>>>import Control.Lens>>>productOf both (4,5)20>>>productOf folded [1,2,3,4,5]120
product≡productOffolded
productOf::Gettera c -> a -> cproductOf::Numc =>Folda c -> a -> cproductOf::SimpleLensa c -> a -> cproductOf::SimpleIsoa c -> a -> cproductOf::Numc =>SimpleTraversala c -> a -> c
sumOf :: Getting (Sum c) a b c d -> a -> cSource
Calculate the sum of every number targeted by a Fold.
>>>import Control.Lens>>>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)])] :: Int10
sum≡sumOffolded
sumOf_1:: (a, b) -> asumOf(folded._1) :: (Foldablef,Numa) => f (a, b) -> a
sumOf::Gettera c -> a -> csumOf::Numc =>Folda c -> a -> csumOf::SimpleLensa c -> a -> csumOf::SimpleIsoa c -> a -> csumOf::Numc =>SimpleTraversala c -> a -> c
traverseOf_ :: Functor f => Getting (Traversed f) a b c d -> (c -> f e) -> a -> 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.
>>>import Control.Lens>>>traverseOf_ both putStrLn ("hello","world")hello world
traverse_≡traverseOf_folded
traverseOf__2::Functorf => (c -> f e) -> (c1, c) -> f ()traverseOf_traverseLeft::Applicativef => (a -> f b) ->Eithera c -> f ()
The rather specific signature of traverseOf_ allows it to be used as if the signature was any of:
traverseOf_::Functorf =>Gettera c -> (c -> f e) -> a -> f ()traverseOf_::Applicativef =>Folda c -> (c -> f e) -> a -> f ()traverseOf_::Functorf =>SimpleLensa c -> (c -> f e) -> a -> f ()traverseOf_::Functorf =>SimpleIsoa c -> (c -> f e) -> a -> f ()traverseOf_::Applicativef =>SimpleTraversala c -> (c -> f e) -> a -> f ()
forOf_ :: Functor f => Getting (Traversed f) a b c d -> a -> (c -> f e) -> 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
The rather specific signature of forOf_ allows it to be used as if the signature was any of:
forOf_::Functorf =>Gettera c -> a -> (c -> f e) -> f ()forOf_::Applicativef =>Folda c -> a -> (c -> f e) -> f ()forOf_::Functorf =>SimpleLensa c -> a -> (c -> f e) -> f ()forOf_::Functorf =>SimpleIsoa c -> a -> (c -> f e) -> f ()forOf_::Applicativef =>SimpleTraversala c -> a -> (c -> f e) -> f ()
sequenceAOf_ :: Functor f => Getting (Traversed f) a b (f ()) d -> a -> f ()Source
Evaluate each action in observed by a Fold on a structure from left to right, ignoring the results.
sequenceA_≡sequenceAOf_folded
sequenceAOf_::Functorf =>Gettera (f ()) -> a -> f ()sequenceAOf_::Applicativef =>Folda (f ()) -> a -> f ()sequenceAOf_::Functorf =>SimpleLensa (f ()) -> a -> f ()sequenceAOf_::Functorf =>SimpleIsoa (f ()) -> a -> f ()sequenceAOf_::Applicativef =>SimpleTraversala (f ()) -> a -> f ()
mapMOf_ :: Monad m => Getting (Sequenced m) a b c d -> (c -> m e) -> a -> 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.
mapM_≡mapMOf_folded
mapMOf_::Monadm =>Gettera c -> (c -> m e) -> a -> m ()mapMOf_::Monadm =>Folda c -> (c -> m e) -> a -> m ()mapMOf_::Monadm =>SimpleLensa c -> (c -> m e) -> a -> m ()mapMOf_::Monadm =>SimpleIsoa c -> (c -> m e) -> a -> m ()mapMOf_::Monadm =>SimpleTraversala c -> (c -> m e) -> a -> m ()
forMOf_ :: Monad m => Getting (Sequenced m) a b c d -> a -> (c -> m e) -> m ()Source
forMOf_ is mapMOf_ with two of its arguments flipped.
forM_≡forMOf_folded
forMOf_::Monadm =>Gettera c -> a -> (c -> m e) -> m ()forMOf_::Monadm =>Folda c -> a -> (c -> m e) -> m ()forMOf_::Monadm =>SimpleLensa c -> a -> (c -> m e) -> m ()forMOf_::Monadm =>SimpleIsoa c -> a -> (c -> m e) -> m ()forMOf_::Monadm =>SimpleTraversala c -> a -> (c -> m e) -> m ()
sequenceOf_ :: Monad m => Getting (Sequenced m) a b (m c) d -> a -> m ()Source
Evaluate each monadic action referenced by a Fold on the structure from left to right, and ignore the results.
sequence_≡sequenceOf_folded
sequenceOf_::Monadm =>Gettera (m b) -> a -> m ()sequenceOf_::Monadm =>Folda (m b) -> a -> m ()sequenceOf_::Monadm =>SimpleLensa (m b) -> a -> m ()sequenceOf_::Monadm =>SimpleIsoa (m b) -> a -> m ()sequenceOf_::Monadm =>SimpleTraversala (m b) -> 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≡asumOffolded
asumOf::Alternativef =>Gettera c -> a -> f casumOf::Alternativef =>Folda c -> a -> f casumOf::Alternativef =>SimpleLensa c -> a -> f casumOf::Alternativef =>SimpleIsoa c -> a -> f casumOf::Alternativef =>SimpleTraversala c -> 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≡msumOffolded
msumOf::MonadPlusm =>Gettera c -> a -> m cmsumOf::MonadPlusm =>Folda c -> a -> m cmsumOf::MonadPlusm =>SimpleLensa c -> a -> m cmsumOf::MonadPlusm =>SimpleIsoa c -> a -> m cmsumOf::MonadPlusm =>SimpleTraversala c -> a -> m c
concatMapOf :: Getting [e] a b c d -> (c -> [e]) -> a -> [e]Source
Map a function over all the targets of a Fold of a container and concatenate the resulting lists.
concatMap≡concatMapOffolded
concatMapOf::Gettera c -> (c -> [e]) -> a -> [e]concatMapOf::Folda c -> (c -> [e]) -> a -> [e]concatMapOf::SimpleLensa c -> (c -> [e]) -> a -> [e]concatMapOf::SimpleIsoa c -> (c -> [e]) -> a -> [e]concatMapOf::SimpleTraversala c -> (c -> [e]) -> a -> [e]
concatOf :: Getting [e] a b [e] d -> a -> [e]Source
Concatenate all of the lists targeted by a Fold into a longer list.
>>>import Control.Lens>>>concatOf both ("pan","ama")"panama"
concat≡concatOffoldedconcatOf≡view
concatOf::Gettera [e] -> a -> [e]concatOf::Folda [e] -> a -> [e]concatOf::SimpleIsoa [e] -> a -> [e]concatOf::SimpleLensa [e] -> a -> [e]concatOf::SimpleTraversala [e] -> a -> [e]
elemOf :: Eq c => Getting Any a b c d -> c -> a -> BoolSource
Does the element occur anywhere within a given Fold of the structure?
>>>import Control.Lens>>>elemOf both "hello" ("hello","world")True
elem≡elemOffolded
elemOf::Eqc =>Gettera c -> c -> a ->BoolelemOf::Eqc =>Folda c -> c -> a ->BoolelemOf::Eqc =>SimpleLensa c -> c -> a ->BoolelemOf::Eqc =>SimpleIsoa c -> c -> a ->BoolelemOf::Eqc =>SimpleTraversala c -> c -> a ->Bool
notElemOf :: Eq c => Getting All a b c d -> c -> a -> BoolSource
Does the element not occur anywhere within a given Fold of the structure?
notElem≡notElemOffolded
notElemOf::Eqc =>Gettera c -> c -> a ->BoolnotElemOf::Eqc =>Folda c -> c -> a ->BoolnotElemOf::Eqc =>SimpleIsoa c -> c -> a ->BoolnotElemOf::Eqc =>SimpleLensa c -> c -> a ->BoolnotElemOf::Eqc =>SimpleTraversala c -> c -> a ->Bool
lengthOf :: Getting (Sum Int) a b c d -> a -> IntSource
Note: this can be rather inefficient for large containers.
length≡lengthOffolded
>>>import Control.Lens>>>lengthOf _1 ("hello",())1
lengthOf(folded.folded) ::Foldablef => f (g a) ->Int
lengthOf::Gettera c -> a ->IntlengthOf::Folda c -> a ->IntlengthOf::SimpleLensa c -> a ->IntlengthOf::SimpleIsoa c -> a ->IntlengthOf::SimpleTraversala c -> 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≡nullOffolded
This may be rather inefficient compared to the null check of many containers.
>>>import Control.Lens>>>nullOf _1 (1,2)False
nullOf(folded._1.folded) ::Foldablef => f (g a, b) ->Bool
nullOf::Gettera c -> a ->BoolnullOf::Folda c -> a ->BoolnullOf::SimpleIsoa c -> a ->BoolnullOf::SimpleLensa c -> a ->BoolnullOf::SimpleTraversala c -> 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. See also (^?).
listToMaybe.toList≡headOffolded
headOf::Gettera c -> a ->MaybecheadOf::Folda c -> a ->MaybecheadOf::SimpleLensa c -> a ->MaybecheadOf::SimpleIsoa c -> a ->MaybecheadOf::SimpleTraversala c -> a ->Maybec
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(errorempty).maximumOffolded
maximumOf::Gettera c -> a ->MaybecmaximumOf::Ordc =>Folda c -> a ->MaybecmaximumOf::SimpleIsoa c -> a ->MaybecmaximumOf::SimpleLensa c -> a ->MaybecmaximumOf::Ordc =>SimpleTraversala c -> a ->Maybec
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(errorempty).minimumOffolded
minimumOf::Gettera c -> a ->MaybecminimumOf::Ordc =>Folda c -> a ->MaybecminimumOf::SimpleIsoa c -> a ->MaybecminimumOf::SimpleLensa c -> a ->MaybecminimumOf::Ordc =>SimpleTraversala c -> a ->Maybec
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.
maximumBycmp ≡fromMaybe(errorempty).maximumByOffoldedcmp
maximumByOf::Gettera c -> (c -> c ->Ordering) -> a ->MaybecmaximumByOf::Folda c -> (c -> c ->Ordering) -> a ->MaybecmaximumByOf::SimpleIsoa c -> (c -> c ->Ordering) -> a ->MaybecmaximumByOf::SimpleLensa c -> (c -> c ->Ordering) -> a ->MaybecmaximumByOf::SimpleTraversala c -> (c -> c ->Ordering) -> a ->Maybec
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.
minimumBycmp ≡fromMaybe(errorempty).minimumByOffoldedcmp
minimumByOf::Gettera c -> (c -> c ->Ordering) -> a ->MaybecminimumByOf::Folda c -> (c -> c ->Ordering) -> a ->MaybecminimumByOf::SimpleIsoa c -> (c -> c ->Ordering) -> a ->MaybecminimumByOf::SimpleLensa c -> (c -> c ->Ordering) -> a ->MaybecminimumByOf::SimpleTraversala c -> (c -> c ->Ordering) -> a ->Maybec
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::Gettera c -> (c ->Bool) -> a ->MaybecfindOf::Folda c -> (c ->Bool) -> a ->MaybecfindOf::SimpleIsoa c -> (c ->Bool) -> a ->MaybecfindOf::SimpleLensa c -> (c ->Bool) -> a ->MaybecfindOf::SimpleTraversala c -> (c ->Bool) -> a ->Maybec
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'::Gettera c -> (c -> e -> e) -> e -> a -> efoldrOf'::Folda c -> (c -> e -> e) -> e -> a -> efoldrOf'::SimpleIsoa c -> (c -> e -> e) -> e -> a -> efoldrOf'::SimpleLensa c -> (c -> e -> e) -> e -> a -> efoldrOf'::SimpleTraversala c -> (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'::Gettera c -> (e -> c -> e) -> e -> a -> efoldlOf'::Folda c -> (e -> c -> e) -> e -> a -> efoldlOf'::SimpleIsoa c -> (e -> c -> e) -> e -> a -> efoldlOf'::SimpleLensa c -> (e -> c -> e) -> e -> a -> efoldlOf'::SimpleTraversala c -> (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.
foldr1Ofl f ≡foldr1f.toListOflfoldr1≡foldr1Offolded
foldr1Of::Gettera c -> (c -> c -> c) -> a -> cfoldr1Of::Folda c -> (c -> c -> c) -> a -> cfoldr1Of::SimpleIsoa c -> (c -> c -> c) -> a -> cfoldr1Of::SimpleLensa c -> (c -> c -> c) -> a -> cfoldr1Of::SimpleTraversala c -> (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.
foldl1Ofl f ≡foldl1Ofl f .toListfoldl1≡foldl1Offolded
foldl1Of::Gettera c -> (c -> c -> c) -> a -> cfoldl1Of::Folda c -> (c -> c -> c) -> a -> cfoldl1Of::SimpleIsoa c -> (c -> c -> c) -> a -> cfoldl1Of::SimpleLensa c -> (c -> c -> c) -> a -> cfoldl1Of::SimpleTraversala c -> (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≡foldrMOffolded
foldrMOf::Monadm =>Gettera c -> (c -> e -> m e) -> e -> a -> m efoldrMOf::Monadm =>Folda c -> (c -> e -> m e) -> e -> a -> m efoldrMOf::Monadm =>SimpleIsoa c -> (c -> e -> m e) -> e -> a -> m efoldrMOf::Monadm =>SimpleLensa c -> (c -> e -> m e) -> e -> a -> m efoldrMOf::Monadm =>SimpleTraversala c -> (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≡foldlMOffolded
foldlMOf::Monadm =>Gettera c -> (e -> c -> m e) -> e -> a -> m efoldlMOf::Monadm =>Folda c -> (e -> c -> m e) -> e -> a -> m efoldlMOf::Monadm =>SimpleIsoa c -> (e -> c -> m e) -> e -> a -> m efoldlMOf::Monadm =>SimpleLensa c -> (e -> c -> m e) -> e -> a -> m efoldlMOf::Monadm =>SimpleTraversala c -> (e -> c -> m e) -> e -> a -> m e
Storing Folds
newtype ReifiedFold a c Source
Useful for storing folds in containers.
Constructors
| ReifyFold | |
Fields
| |