Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- data Fold a b = forall x. Fold x (x -> a -> x) (x -> b)
- data NonemptyFold a b = forall x. NonemptyFold (a -> x) (x -> a -> x) (x -> b)
- data EffectfulFold m a b = forall x. EffectfulFold (m x) (x -> a -> m x) (x -> m b)
- data ShortcutFold a b = forall x y. ShortcutFold (Vitality x y) (y -> a -> Vitality x y) (x -> b) (y -> b)
- data ShortcutNonemptyFold a b = forall x y. ShortcutNonemptyFold (a -> Vitality x y) (y -> a -> Vitality x y) (x -> b) (y -> b)
- data Vitality a b
- data Will
- runFold :: Foldable f => Fold a b -> f a -> b
- runNonemptyFold :: NonemptyFold a b -> NonEmpty a -> b
- runEffectfulFold :: Foldable f => Monad m => EffectfulFold m a b -> f a -> m b
- element :: Eq a => a -> ShortcutFold a Bool
- notElement :: Eq a => a -> ShortcutFold a Bool
- find :: (a -> Bool) -> ShortcutFold a (Maybe a)
- lookup :: Eq a => a -> ShortcutFold (a, b) (Maybe b)
- sum :: Num a => Fold a a
- product :: Num a => Fold a a
- mean :: Fractional a => Fold a a
- variance :: Fractional a => Fold a a
- standardDeviation :: Floating a => Fold a a
- index :: Natural -> ShortcutFold a (Maybe a)
- findIndex :: (a -> Bool) -> ShortcutFold a (Maybe Natural)
- elementIndex :: Eq a => a -> ShortcutFold a (Maybe Natural)
- null :: ShortcutFold a Bool
- length :: Fold a Natural
- and :: ShortcutFold Bool Bool
- or :: ShortcutFold Bool Bool
- all :: (a -> Bool) -> ShortcutFold a Bool
- any :: (a -> Bool) -> ShortcutFold a Bool
- maximum :: Ord a => NonemptyFold a a
- minimum :: Ord a => NonemptyFold a a
- maximumBy :: (a -> a -> Ordering) -> NonemptyFold a a
- minimumBy :: (a -> a -> Ordering) -> NonemptyFold a a
- first :: ShortcutNonemptyFold a a
- last :: NonemptyFold a a
- magma :: (a -> a -> a) -> NonemptyFold a a
- semigroup :: Semigroup a => NonemptyFold a a
- monoid :: Monoid a => Fold a a
- effect :: Monad m => (a -> m b) -> EffectfulFold m a ()
- effectMonoid :: (Monoid w, Monad m) => (a -> m w) -> EffectfulFold m a w
- list :: Fold a [a]
- reverseList :: Fold a [a]
- nonemptyList :: NonemptyFold a (NonEmpty a)
- reverseNonemptyList :: NonemptyFold a (NonEmpty a)
- emptyToNonempty :: Fold a b -> NonemptyFold a b
- nonemptyToEmpty :: NonemptyFold a b -> Fold a (Maybe b)
- pureToEffectful :: Monad m => Fold a b -> EffectfulFold m a b
- effectfulToPure :: EffectfulFold Identity a b -> Fold a b
- nonemptyToEffectful :: Monad m => NonemptyFold a b -> EffectfulFold m a (Maybe b)
- effectfulToNonempty :: EffectfulFold Identity a b -> NonemptyFold a b
- hoist :: (forall x. m x -> n x) -> EffectfulFold m a b -> EffectfulFold n a b
- duplicateFold :: Fold a b -> Fold a (Fold a b)
- duplicateNonemptyFold :: NonemptyFold a b -> NonemptyFold a (Fold a b)
- duplicateEffectfulFold :: Applicative m => EffectfulFold m a b -> EffectfulFold m a (EffectfulFold m a b)
Fold types
Processes inputs of type a
and results in a value of type b
forall x. Fold x (x -> a -> x) (x -> b) |
data NonemptyFold a b Source #
Processes at least one input of type a
and results in a value of type b
forall x. NonemptyFold (a -> x) (x -> a -> x) (x -> b) |
Instances
data EffectfulFold m a b Source #
Processes inputs of type a
and results in an effectful value of type m b
forall x. EffectfulFold (m x) (x -> a -> m x) (x -> m b) |
Instances
data ShortcutFold a b Source #
Processes inputs of type a
, has the ability to halt midway
through the stream, and results in a value of type b
forall x y. ShortcutFold (Vitality x y) (y -> a -> Vitality x y) (x -> b) (y -> b) |
Instances
data ShortcutNonemptyFold a b Source #
Processes at least one input of type a
, has the ability to halt
midway through the stream, and results in a value of type b
forall x y. ShortcutNonemptyFold (a -> Vitality x y) (y -> a -> Vitality x y) (x -> b) (y -> b) |
Instances
Running
runFold :: Foldable f => Fold a b -> f a -> b Source #
Fold a listlike container to a single summary result
runNonemptyFold :: NonemptyFold a b -> NonEmpty a -> b Source #
Fold a nonempty listlike container to a single summary result
runEffectfulFold :: Foldable f => Monad m => EffectfulFold m a b -> f a -> m b Source #
Fold an listlike container to an action that produces a single summary result
Search
element :: Eq a => a -> ShortcutFold a Bool Source #
True
if any input is equal to the given value (tenacious)
notElement :: Eq a => a -> ShortcutFold a Bool Source #
False
if any input is equal to the given value (tenacious)
find :: (a -> Bool) -> ShortcutFold a (Maybe a) Source #
The first input that satisfies the predicate, if any (tenacious)
lookup :: Eq a => a -> ShortcutFold (a, b) (Maybe b) Source #
The b
from the first tuple where a
equals the given value,
if any (tenacious)
Arithmetic folds
mean :: Fractional a => Fold a a Source #
Numerically stable arithmetic mean of the inputs
variance :: Fractional a => Fold a a Source #
Numerically stable (population) variance over the inputs
standardDeviation :: Floating a => Fold a a Source #
Numerically stable (population) standard deviation over the inputs
Working with indices
index :: Natural -> ShortcutFold a (Maybe a) Source #
The nth input, where n=0 is the first input, if the index is in bounds (tenacious)
findIndex :: (a -> Bool) -> ShortcutFold a (Maybe Natural) Source #
The index of the first input that satisfies the predicate, if any (tenacious)
elementIndex :: Eq a => a -> ShortcutFold a (Maybe Natural) Source #
The index of the first input that matches the given value, if any (tenacious)
Counting inputs
Boolean folds
all :: (a -> Bool) -> ShortcutFold a Bool Source #
True
if all inputs satisfy the predicate (tenacious)
any :: (a -> Bool) -> ShortcutFold a Bool Source #
True
if any input satisfies the predicate (tenacious)
Min/max
maximum :: Ord a => NonemptyFold a a Source #
The greatest input
minimum :: Ord a => NonemptyFold a a Source #
The least input
maximumBy :: (a -> a -> Ordering) -> NonemptyFold a a Source #
The greatest input with respect to the given comparison function
minimumBy :: (a -> a -> Ordering) -> NonemptyFold a a Source #
The least input with respect to the given comparison function
First/last
first :: ShortcutNonemptyFold a a Source #
The first input (tenacious)
last :: NonemptyFold a a Source #
The last input
General folds
magma :: (a -> a -> a) -> NonemptyFold a a Source #
Start with the first input, append each new input on the right with the given function
effect :: Monad m => (a -> m b) -> EffectfulFold m a () Source #
Performs an action for each input, discarding the result
effectMonoid :: (Monoid w, Monad m) => (a -> m w) -> EffectfulFold m a w Source #
Performs an action for each input, monoidally combining the results from all the actions.
List folds
reverseList :: Fold a [a] Source #
All the inputs in reverse order
nonemptyList :: NonemptyFold a (NonEmpty a) Source #
All the inputs from a nonempty fold
reverseNonemptyList :: NonemptyFold a (NonEmpty a) Source #
All the inputs from a nonempty fold, in reverse order
Fold conversions
emptyToNonempty :: Fold a b -> NonemptyFold a b Source #
Turn a regular fold that allows empty input into a fold that requires at least one input
nonemptyToEmpty :: NonemptyFold a b -> Fold a (Maybe b) Source #
Turn a fold that requires at least one input into a fold that returns
Nothing
when there are no inputs
pureToEffectful :: Monad m => Fold a b -> EffectfulFold m a b Source #
Generalize a pure fold to an effectful fold
effectfulToPure :: EffectfulFold Identity a b -> Fold a b Source #
Turn an effectful fold into a pure fold
nonemptyToEffectful :: Monad m => NonemptyFold a b -> EffectfulFold m a (Maybe b) Source #
Turn a nonempty fold that requires at least one input into a fold that
returns Nothing
when there are no inputs
effectfulToNonempty :: EffectfulFold Identity a b -> NonemptyFold a b Source #
Turn an effectful fold into a pure fold that requires at least one input
Hoist
hoist :: (forall x. m x -> n x) -> EffectfulFold m a b -> EffectfulFold n a b Source #
Shift an effectful fold from one monad to another with a morphism such as
lift
or liftIO
Duplicate
duplicateFold :: Fold a b -> Fold a (Fold a b) Source #
Allows to continue feeding a fold even after passing it to a function that closes it
duplicateNonemptyFold :: NonemptyFold a b -> NonemptyFold a (Fold a b) Source #
Allows to continue feeding a fold even after passing it to a function that closes it
duplicateEffectfulFold :: Applicative m => EffectfulFold m a b -> EffectfulFold m a (EffectfulFold m a b) Source #
Allows to continue feeding an effectful fold even after passing it to a function that closes it