profunctor-optics-0.0.2: A compact optics library compatible with the typeclasses in profunctors.

Safe HaskellNone
LanguageHaskell2010

Data.Profunctor.Optic.Fold

Contents

Synopsis

Fold0

type Fold0 s a = forall p. (Affine p, CoerceR p) => Optic' p s a Source #

fold0 :: (s -> Maybe a) -> Fold0 s a Source #

Obtain a Fold0 directly.

fold0 . preview ≡ id
fold0 (view o) ≡ o . just
>>> preview (fold0 . preview $ selected even) (2, "yes")
Just "yes"
>>> preview (fold0 . preview $ selected even) (3, "no")
Nothing
>>> preview (fold0 listToMaybe) "foo"
Just 'f'

failing :: AFold0 a s a -> AFold0 a s a -> Fold0 s a infixl 3 Source #

If the first Fold0 has no focus then try the second one.

toFold0 :: View s (Maybe a) -> Fold0 s a Source #

Obtain a Fold0 from a View.

toFold0 o ≡ o . just
toFold0 o ≡ fold0 (view o)

fromFold0 :: AFold0 a s a -> View s (Maybe a) Source #

Obtain a View from a Fold0

Fold

type Fold s a = forall p. (Affine p, Traversing p, CoerceR p) => Optic' p s a Source #

fold_ :: Foldable f => (s -> f a) -> Fold s a Source #

Obtain a Fold directly.

fold_ (lists o) ≡ o
fold_ f ≡ to f . foldVl traverse_
fold_ f ≡ coercer . lmap f . lift traverse_

See Property.

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

>>> [1,2,3,4] ^.. fold_ tail
[2,3,4]

folding :: Traversable f => (s -> a) -> Fold (f s) a Source #

Obtain a Fold from a Traversable functor.

folding f ≡ traversed . to f
folding f ≡ foldVl traverse . to f

foldVl :: (forall f. Applicative f => (a -> f b) -> s -> f t) -> Fold s a Source #

Obtain a Fold from a Van Laarhoven Fold.

afold :: Monoid r => ((a -> r) -> s -> r) -> AFold r s a Source #

TODO: Document

Fold1

type Fold1 s a = forall p. (Strong p, Traversing1 p, CoerceR p) => Optic' p s a Source #

fold1_ :: Foldable1 f => (s -> f a) -> Fold1 s a Source #

Obtain a Fold1 directly.

fold1_ (nelists o) ≡ o
fold1_ f ≡ to f . fold1Vl traverse1_
fold1_ f ≡ coercer . lmap f . lift traverse1_

See Property.

This can be useful to repn operations from Data.List.NonEmpty and elsewhere into a Fold1.

folding1 :: Traversable1 f => (s -> a) -> Fold1 (f s) a Source #

Obtain a Fold1 from a Traversable1 functor.

folding1 f ≡ traversed1 . to f
folding1 f ≡ fold1Vl traverse1 . to f

fold1Vl :: (forall f. Apply f => (a -> f b) -> s -> f t) -> Fold1 s a Source #

Obtain a Fold1 from a Van Laarhoven Fold1.

See Property.

afold1 :: Semigroup r => ((a -> r) -> s -> r) -> AFold1 r s a Source #

TODO: Document

Optics

folded0 :: Fold0 (Maybe a) a Source #

The canonical Fold0.

>>> [Just 1, Nothing] ^.. folded . folded0
[1]

filtered :: (a -> Bool) -> Fold0 a a Source #

Filter another optic.

>>> [1..10] ^.. folded . filtered even
[2,4,6,8,10]

folded :: Traversable f => Fold (f a) a Source #

Obtain a Fold from a Traversable functor.

folded_ :: Foldable f => Fold (f a) a Source #

The canonical Fold.

foldMapwithFold folded_'

folded1 :: Traversable1 f => Fold1 (f a) a Source #

Obtain a Fold1 from a Traversable1 functor.

folded1_ :: Foldable1 f => Fold1 (f a) a Source #

The canonical Fold1.

foldMap1withFold1 folded1_'

Operators

(^?) :: s -> AFold0 a s a -> Maybe a infixl 8 Source #

An infix alias for preview'.

(^?) ≡ flip preview'

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

When using a Traversal as a partial Lens, or a Fold as a partial View this can be a convenient way to extract the optional value.

>>> Left 4 ^? left'
Just 4
>>> Right 4 ^? left'
Nothing

preview :: MonadReader s m => AFold0 a s a -> m (Maybe a) Source #

TODO: Document

preuse :: MonadState s m => AFold0 a s a -> m (Maybe a) Source #

TODO: Document

is :: AFold0 a s a -> s -> Bool Source #

Check whether the optic is matched.

>>> is just Nothing
False

isnt :: AFold0 a s a -> s -> Bool Source #

Check whether the optic isn't matched.

>>> isnt just Nothing
True

lists :: AFold (Endo [a]) s a -> s -> [a] Source #

Collect the foci of an optic into a list.

(^..) :: s -> AFold (Endo [a]) s a -> [a] infixl 8 Source #

Infix alias of lists.

toList xs ≡ xs ^.. folding
(^..) ≡ flip lists
>>> [[1,2], [3 :: Int64]] ^.. id
[[[1,2],[3]]]
>>> [[1,2], [3 :: Int64]] ^.. traversed
[[1,2],[3]]
>>> [[1,2], [3 :: Int64]] ^.. traversed . traversed
[1,2,3]
>>> (1,2) ^.. bitraversed
[1,2]
(^..) :: s -> View 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 -> Traversal0' s a    -> [a]

nelists :: AFold1 (Nedl a) s a -> s -> NonEmpty a Source #

Extract a NonEmpty of the foci of an optic.

>>> nelists bitraversed1 ('h' :| "ello", 'w' :| "orld")
('h' :| "ello") :| ['w' :| "orld"]

folds :: Monoid a => AFold a s a -> s -> a Source #

TODO: Document

folds1 :: Semigroup a => AFold1 a s a -> s -> a Source #

TODO: Document

foldsa :: Applicative f => Monoid (f a) => AFold (f a) s a -> s -> f a Source #

TODO: Document

foldsa :: Fold s a -> s -> [a]
foldsa :: Applicative f => Setter s t a b -> s -> f a

foldsr :: AFold (Endo r) s a -> (a -> r -> r) -> r -> s -> r Source #

Right fold over an optic.

>>> foldsr folded (+) 0 [1..5::Int64]
15

foldsl :: AFold ((Endo - Dual) r) s a -> (r -> a -> r) -> r -> s -> r Source #

Left fold over an optic.

foldsr' :: AFold ((Endo - Dual) (Endo r)) s a -> (a -> r -> r) -> r -> s -> r Source #

Strict right fold over an optic.

foldsl' :: AFold ((Endo - Endo) r) s a -> (r -> a -> r) -> r -> s -> r Source #

Strict left fold over an optic.

foldl'foldsl' folding
foldsl' :: Iso' s a        -> (c -> a -> c) -> c -> s -> c
foldsl' :: Lens' s a       -> (c -> a -> c) -> c -> s -> c
foldsl' :: View s a        -> (c -> a -> c) -> c -> s -> c
foldsl' :: Fold s a        -> (c -> a -> c) -> c -> s -> c
foldsl' :: Traversal' s a  -> (c -> a -> c) -> c -> s -> c
foldsl' :: Traversal0' s a -> (c -> a -> c) -> c -> s -> c

foldsrM :: Monad m => AFold ((Endo - Dual) (r -> m r)) s a -> (a -> r -> m r) -> r -> s -> m r Source #

Monadic right fold over an optic.

foldslM :: Monad m => AFold (Endo (r -> m r)) s a -> (r -> a -> m r) -> r -> s -> m r Source #

Monadic left fold over an optic.

traverses_ :: Applicative f => AFold (Endo (f ())) s a -> (a -> f r) -> s -> f () Source #

Applicative fold over an optic.

>>> traverses_ both putStrLn ("hello","world")
hello
world
traverse_traverses_ folded

concats :: AFold [r] s a -> (a -> [r]) -> s -> [r] Source #

Map a function over the foci of an optic and concatenate the resulting lists.

>>> concats both (\x -> [x, x + 1]) (1,3)
[1,2,3,4]
concatMapconcats folded

aconcats :: Alternative f => AFold ((Endo - Endo) (f a)) s (f a) -> s -> f a Source #

The sum of a collection of actions, generalizing concats.

>>> aconcats both ("hello","world")
"helloworld"
>>> aconcats both (Nothing, Just "hello")
Just "hello"
asumaconcats folded

mins :: Ord a => AFold ((Endo - Endo) a) s a -> a -> s -> a Source #

Compute the minimum of the targets of a totally ordered fold.

maxes :: Ord a => AFold ((Endo - Endo) a) s a -> a -> s -> a Source #

Compute the maximum of the targets of a totally ordered fold.

sums :: (Additive - Monoid) a => AFold ((Endo - Endo) a) s a -> s -> a Source #

The sum of a collection.

multiplies :: (Multiplicative - Monoid) a => AFold ((Endo - Endo) a) s a -> s -> a Source #

The product of a collection.

endo :: AFold (Endo (a -> a)) s (a -> a) -> s -> a -> a Source #

TODO: Document

endoM :: Monad m => AFold (Endo (a -> m a)) s (a -> m a) -> s -> a -> m a Source #

TODO: Document

finds :: AFold ((Maybe - Endo) a) s a -> (a -> Bool) -> s -> Maybe a Source #

Find the first focus of an optic that satisfies a predicate, if one exists.

>>> finds both even (1,4)
Just 4
>>> finds folded even [1,3,5,7]
Nothing
findfinds folded

has :: AFold (Additive Bool) s a -> s -> Bool Source #

Determine whether an optic has at least one focus.

hasnt :: AFold (Multiplicative Bool) s a -> s -> Bool Source #

Determine whether an optic does not have a focus.

contains :: Eq a => AFold (Additive Bool) s a -> a -> s -> Bool Source #

Determine whether the targets of a Fold contain a given element.

Auxilliary Types

newtype Nedl a Source #

Constructors

Nedl 

Fields

Instances
Semigroup (Nedl a) Source # 
Instance details

Defined in Data.Profunctor.Optic.Fold

Methods

(<>) :: Nedl a -> Nedl a -> Nedl a #

sconcat :: NonEmpty (Nedl a) -> Nedl a #

stimes :: Integral b => b -> Nedl a -> Nedl a #