gambler-0.4.1.0: Composable, streaming, and efficient left folds
Safe HaskellSafe-Inferred
LanguageGHC2021

Fold

Synopsis

Fold types

data Fold a b Source #

Processes inputs of type a and results in a value of type b

Constructors

forall x. Fold x (x -> a -> x) (x -> b) 

Instances

Instances details
Applicative (Fold a) Source # 
Instance details

Defined in Fold.Pure.Type

Methods

pure :: a0 -> Fold a a0 #

(<*>) :: Fold a (a0 -> b) -> Fold a a0 -> Fold a b #

liftA2 :: (a0 -> b -> c) -> Fold a a0 -> Fold a b -> Fold a c #

(*>) :: Fold a a0 -> Fold a b -> Fold a b #

(<*) :: Fold a a0 -> Fold a b -> Fold a a0 #

Functor (Fold a) Source # 
Instance details

Defined in Fold.Pure.Type

Methods

fmap :: (a0 -> b) -> Fold a a0 -> Fold a b #

(<$) :: a0 -> Fold a b -> Fold a a0 #

Monoid b => Monoid (Fold a b) Source # 
Instance details

Defined in Fold.Pure.Type

Methods

mempty :: Fold a b #

mappend :: Fold a b -> Fold a b -> Fold a b #

mconcat :: [Fold a b] -> Fold a b #

Semigroup b => Semigroup (Fold a b) Source # 
Instance details

Defined in Fold.Pure.Type

Methods

(<>) :: Fold a b -> Fold a b -> Fold a b #

sconcat :: NonEmpty (Fold a b) -> Fold a b #

stimes :: Integral b0 => b0 -> Fold a b -> Fold a b #

data NonemptyFold a b Source #

Processes at least one input of type a and results in a value of type b

Constructors

forall x. NonemptyFold (a -> x) (x -> a -> x) (x -> b) 

Instances

Instances details
Applicative (NonemptyFold a) Source # 
Instance details

Defined in Fold.Nonempty.Type

Methods

pure :: a0 -> NonemptyFold a a0 #

(<*>) :: NonemptyFold a (a0 -> b) -> NonemptyFold a a0 -> NonemptyFold a b #

liftA2 :: (a0 -> b -> c) -> NonemptyFold a a0 -> NonemptyFold a b -> NonemptyFold a c #

(*>) :: NonemptyFold a a0 -> NonemptyFold a b -> NonemptyFold a b #

(<*) :: NonemptyFold a a0 -> NonemptyFold a b -> NonemptyFold a a0 #

Functor (NonemptyFold a) Source # 
Instance details

Defined in Fold.Nonempty.Type

Methods

fmap :: (a0 -> b) -> NonemptyFold a a0 -> NonemptyFold a b #

(<$) :: a0 -> NonemptyFold a b -> NonemptyFold a a0 #

Monoid b => Monoid (NonemptyFold a b) Source # 
Instance details

Defined in Fold.Nonempty.Type

Semigroup b => Semigroup (NonemptyFold a b) Source # 
Instance details

Defined in Fold.Nonempty.Type

Methods

(<>) :: NonemptyFold a b -> NonemptyFold a b -> NonemptyFold a b #

sconcat :: NonEmpty (NonemptyFold a b) -> NonemptyFold a b #

stimes :: Integral b0 => b0 -> NonemptyFold a b -> NonemptyFold a b #

data EffectfulFold m a b Source #

Processes inputs of type a and results in an effectful value of type m b

Constructors

forall x. EffectfulFold (m x) (x -> a -> m x) (x -> m b) 

Instances

Instances details
Applicative m => Applicative (EffectfulFold m a) Source # 
Instance details

Defined in Fold.Effectful.Type

Methods

pure :: a0 -> EffectfulFold m a a0 #

(<*>) :: EffectfulFold m a (a0 -> b) -> EffectfulFold m a a0 -> EffectfulFold m a b #

liftA2 :: (a0 -> b -> c) -> EffectfulFold m a a0 -> EffectfulFold m a b -> EffectfulFold m a c #

(*>) :: EffectfulFold m a a0 -> EffectfulFold m a b -> EffectfulFold m a b #

(<*) :: EffectfulFold m a a0 -> EffectfulFold m a b -> EffectfulFold m a a0 #

Functor m => Functor (EffectfulFold m a) Source # 
Instance details

Defined in Fold.Effectful.Type

Methods

fmap :: (a0 -> b) -> EffectfulFold m a a0 -> EffectfulFold m a b #

(<$) :: a0 -> EffectfulFold m a b -> EffectfulFold m a a0 #

(Monoid b, Monad m) => Monoid (EffectfulFold m a b) Source # 
Instance details

Defined in Fold.Effectful.Type

Methods

mempty :: EffectfulFold m a b #

mappend :: EffectfulFold m a b -> EffectfulFold m a b -> EffectfulFold m a b #

mconcat :: [EffectfulFold m a b] -> EffectfulFold m a b #

(Semigroup b, Monad m) => Semigroup (EffectfulFold m a b) Source # 
Instance details

Defined in Fold.Effectful.Type

Methods

(<>) :: EffectfulFold m a b -> EffectfulFold m a b -> EffectfulFold m a b #

sconcat :: NonEmpty (EffectfulFold m a b) -> EffectfulFold m a b #

stimes :: Integral b0 => b0 -> EffectfulFold m a b -> EffectfulFold m a b #

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

Constructors

forall x y. ShortcutFold (Vitality x y) (y -> a -> Vitality x y) (Vitality x y -> b) 

Instances

Instances details
Applicative (ShortcutFold a) Source # 
Instance details

Defined in Fold.Shortcut.Type

Methods

pure :: a0 -> ShortcutFold a a0 #

(<*>) :: ShortcutFold a (a0 -> b) -> ShortcutFold a a0 -> ShortcutFold a b #

liftA2 :: (a0 -> b -> c) -> ShortcutFold a a0 -> ShortcutFold a b -> ShortcutFold a c #

(*>) :: ShortcutFold a a0 -> ShortcutFold a b -> ShortcutFold a b #

(<*) :: ShortcutFold a a0 -> ShortcutFold a b -> ShortcutFold a a0 #

Functor (ShortcutFold a) Source # 
Instance details

Defined in Fold.Shortcut.Type

Methods

fmap :: (a0 -> b) -> ShortcutFold a a0 -> ShortcutFold a b #

(<$) :: a0 -> ShortcutFold a b -> ShortcutFold a a0 #

Monoid b => Monoid (ShortcutFold a b) Source # 
Instance details

Defined in Fold.Shortcut.Type

Semigroup b => Semigroup (ShortcutFold a b) Source # 
Instance details

Defined in Fold.Shortcut.Type

Methods

(<>) :: ShortcutFold a b -> ShortcutFold a b -> ShortcutFold a b #

sconcat :: NonEmpty (ShortcutFold a b) -> ShortcutFold a b #

stimes :: Integral b0 => b0 -> ShortcutFold a b -> ShortcutFold a b #

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

Constructors

forall x y. ShortcutNonemptyFold (a -> Vitality x y) (y -> a -> Vitality x y) (Vitality x y -> b) 

Instances

Instances details
Applicative (ShortcutNonemptyFold a) Source # 
Instance details

Defined in Fold.ShortcutNonempty.Type

Functor (ShortcutNonemptyFold a) Source # 
Instance details

Defined in Fold.ShortcutNonempty.Type

Methods

fmap :: (a0 -> b) -> ShortcutNonemptyFold a a0 -> ShortcutNonemptyFold a b #

(<$) :: a0 -> ShortcutNonemptyFold a b -> ShortcutNonemptyFold a a0 #

Monoid b => Monoid (ShortcutNonemptyFold a b) Source # 
Instance details

Defined in Fold.ShortcutNonempty.Type

Semigroup b => Semigroup (ShortcutNonemptyFold a b) Source # 
Instance details

Defined in Fold.ShortcutNonempty.Type

data Vitality a b Source #

Constructors

Dead a 
Alive Will b 

Instances

Instances details
Functor (Vitality a) Source # 
Instance details

Defined in Strict

Methods

fmap :: (a0 -> b) -> Vitality a a0 -> Vitality a b #

(<$) :: a0 -> Vitality a b -> Vitality a a0 #

data Will Source #

Constructors

Ambivalent 
Tenacious 

Instances

Instances details
Monoid Will Source # 
Instance details

Defined in Strict

Methods

mempty :: Will #

mappend :: Will -> Will -> Will #

mconcat :: [Will] -> Will #

Semigroup Will Source # 
Instance details

Defined in Strict

Methods

(<>) :: Will -> Will -> Will #

sconcat :: NonEmpty Will -> Will #

stimes :: Integral b => b -> Will -> Will #

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

sum :: Num a => Fold a a Source #

Adds the inputs

product :: Num a => Fold a a Source #

Multiplies the inputs

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

null :: ShortcutFold a Bool Source #

True if the input contains no inputs (tenacious)

length :: Fold a Natural Source #

The number of inputs

Boolean folds

and :: ShortcutFold Bool Bool Source #

True if all inputs are True (tenacious)

or :: ShortcutFold Bool Bool Source #

True if any input is True (tenacious)

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

semigroup :: Semigroup a => NonemptyFold a a Source #

Append each new input on the right with (<>)

monoid :: Monoid a => Fold a a Source #

Start with mempty, append each input on the right with (<>)

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

list :: Fold a [a] Source #

All the inputs

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