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

Fold.Effectful

Synopsis

Type

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 

Fields

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 #

Run

run :: 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

Examples

General

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

magma :: (a -> a -> a) -> Monad m => EffectfulFold m a (Maybe a) Source #

Start with the first input, append each new input on the right with the given function

semigroup :: Semigroup a => Monad m => EffectfulFold m a (Maybe a) Source #

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

monoid :: Monoid a => Monad m => EffectfulFold m a a Source #

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

Endpoints

first :: Monad m => EffectfulFold m a (Maybe a) Source #

The first input

last :: Monad m => EffectfulFold m a (Maybe a) Source #

The last input

Extrema

maximum :: Ord a => Monad m => EffectfulFold m a (Maybe a) Source #

The greatest input

minimum :: Ord a => Monad m => EffectfulFold m a (Maybe a) Source #

The least input

maximumBy :: (a -> a -> Ordering) -> Monad m => EffectfulFold m a (Maybe a) Source #

The greatest input with respect to the given comparison function

minimumBy :: (a -> a -> Ordering) -> Monad m => EffectfulFold m a (Maybe a) Source #

The least input with respect to the given comparison function

Length

null :: Monad m => EffectfulFold m a Bool Source #

True if the input contains no inputs

length :: Monad m => EffectfulFold m a Natural Source #

The number of inputs

Boolean

and :: Monad m => EffectfulFold m Bool Bool Source #

True if all inputs are True

or :: Monad m => EffectfulFold m Bool Bool Source #

True if any input is True

all :: Monad m => (a -> Bool) -> EffectfulFold m a Bool Source #

True if all inputs satisfy the predicate

any :: Monad m => (a -> Bool) -> EffectfulFold m a Bool Source #

True if any input satisfies the predicate

Numeric

sum :: Num a => Monad m => EffectfulFold m a a Source #

Adds the inputs

product :: Num a => Monad m => EffectfulFold m a a Source #

Multiplies the inputs

mean :: Fractional a => Monad m => EffectfulFold m a a Source #

Numerically stable arithmetic mean of the inputs

variance :: Fractional a => Monad m => EffectfulFold m a a Source #

Numerically stable (population) variance over the inputs

standardDeviation :: Floating a => Monad m => EffectfulFold m a a Source #

Numerically stable (population) standard deviation over the inputs

Search

element :: Eq a => Monad m => a -> EffectfulFold m a Bool Source #

True if any input is equal to the given value

notElement :: Eq a => Monad m => a -> EffectfulFold m a Bool Source #

False if any input is equal to the given value

find :: Monad m => (a -> Bool) -> EffectfulFold m a (Maybe a) Source #

The first input that satisfies the predicate, if any

lookup :: Eq a => Monad m => a -> EffectfulFold m (a, b) (Maybe b) Source #

The b from the first tuple where a equals the given value, if any

Index

index :: Monad m => Natural -> EffectfulFold m a (Maybe a) Source #

The nth input, where n=0 is the first input, if the index is in bounds

findIndex :: Monad m => (a -> Bool) -> EffectfulFold m a (Maybe Natural) Source #

The index of the first input that satisfies the predicate, if any

elementIndex :: Eq a => Monad m => a -> EffectfulFold m a (Maybe Natural) Source #

The index of the first input that matches the given value, if any

List

list :: Monad m => EffectfulFold m a [a] Source #

All the inputs

reverseList :: Monad m => EffectfulFold m a [a] Source #

All the inputs in reverse order

Conversion

fold :: Monad m => Fold a b -> EffectfulFold m a b Source #

Generalize a pure fold to an effectful fold

nonemptyFold :: 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

Utilities

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 :: 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

premap :: Monad m => (a -> m b) -> EffectfulFold m b r -> EffectfulFold m a r Source #

Apply a function to each input

prefilter :: Monad m => (a -> m Bool) -> EffectfulFold m a r -> EffectfulFold m a r Source #

Consider only inputs that match an effectful predicate

drop :: Monad m => Natural -> EffectfulFold m a b -> EffectfulFold m a b Source #

Ignore the first n inputs