monad-loops-0.3.3.0: Monadic loops

Safe HaskellSafe-Infered

Control.Monad.Loops

Description

A collection of loop operators for use in monads (mostly in stateful ones).

There is a general naming pattern for many of these: Functions with names ending in _ discard the results of the loop body as in the standard Prelude mapM functions.

Functions with names ending in ' collect their results into MonadPlus containers. Note that any short-circuit effect that those types' MonadPlus instances may provide in a lazy context (such as the instance for Maybe) will _not_ cause execution to short-circuit in these loops.

Functions with names ending in neither of those will generally return just plain old lists.

Synopsis

Documentation

forkMapM :: (a -> IO b) -> [a] -> IO [Either SomeException b]Source

Like mapM, but run all the actions in parallel threads, collecting up the results and returning them all. Does not return until all actions finish.

forkMapM_ :: (a -> IO b) -> [a] -> IO [Maybe SomeException]Source

like forkMapM but without bothering to keep the return values

forkMapM__ :: (a -> IO b) -> [a] -> IO ()Source

like forkMapM_ but not even bothering to track success or failure of the child threads. Still waits for them all though.

whileM :: Monad m => m Bool -> m a -> m [a]Source

Execute an action repeatedly as long as the given boolean expression returns True. The condition is evaluated before the loop body. Collects the results into a list.

whileM' :: (Monad m, MonadPlus f) => m Bool -> m a -> m (f a)Source

Execute an action repeatedly as long as the given boolean expression returns True. The condition is evaluated before the loop body. Collects the results into an arbitrary MonadPlus value.

whileM_ :: Monad m => m Bool -> m a -> m ()Source

Execute an action repeatedly as long as the given boolean expression returns True. The condition is evaluated before the loop body. Discards results.

iterateWhile :: Monad m => (a -> Bool) -> m a -> m aSource

Execute an action repeatedly until its result fails to satisfy a predicate, and return that result (discarding all others).

iterateM_ :: Monad m => (a -> m a) -> a -> m bSource

Execute an action forever, feeding the result of each execution as the input to the next.

untilM :: Monad m => m a -> m Bool -> m [a]Source

Execute an action repeatedly until the condition expression returns True. The condition is evaluated after the loop body. Collects results into a list. Parameters are arranged for infix usage. eg. do {...} untilM_ ...

untilM' :: (Monad m, MonadPlus f) => m a -> m Bool -> m (f a)Source

Execute an action repeatedly until the condition expression returns True. The condition is evaluated after the loop body. Collects results into a MonadPlus value. Parameters are arranged for infix usage. eg. do {...} untilM_ ...

untilM_ :: Monad m => m a -> m Bool -> m ()Source

Execute an action repeatedly until the condition expression returns True. The condition is evaluated after the loop body. Discards results. Parameters are arranged for infix usage. eg. do {...} untilM_ ...

iterateUntil :: Monad m => (a -> Bool) -> m a -> m aSource

Execute an action repeatedly until its result satisfies a predicate, and return that result (discarding all others).

whileJust :: Monad m => m (Maybe a) -> (a -> m b) -> m [b]Source

As long as the supplied Maybe expression returns Just _, the loop body will be called and passed the value contained in the Just. Results are collected into a list.

whileJust' :: (Monad m, MonadPlus f) => m (Maybe a) -> (a -> m b) -> m (f b)Source

As long as the supplied Maybe expression returns Just _, the loop body will be called and passed the value contained in the Just. Results are collected into an arbitrary MonadPlus container.

whileJust_ :: Monad m => m (Maybe a) -> (a -> m b) -> m ()Source

As long as the supplied Maybe expression returns Just _, the loop body will be called and passed the value contained in the Just. Results are discarded.

untilJust :: Monad m => m (Maybe a) -> m aSource

Run the supplied Maybe computation repeatedly until it returns a value. Returns that value.

unfoldM :: Monad m => m (Maybe a) -> m [a]Source

The supplied Maybe expression will be repeatedly called until it returns Nothing. All values returned are collected into a list.

unfoldM' :: (Monad m, MonadPlus f) => m (Maybe a) -> m (f a)Source

The supplied Maybe expression will be repeatedly called until it returns Nothing. All values returned are collected into an arbitrary MonadPlus thing.

unfoldM_ :: Monad m => m (Maybe a) -> m ()Source

The supplied Maybe expression will be repeatedly called until it returns Nothing. All values returned are discarded.

unfoldWhileM :: Monad m => (a -> Bool) -> m a -> m [a]Source

Repeatedly evaluates the second argument until the value satisfies the given predicate, and returns a list of all values that satisfied the predicate. Discards the final one (which failed the predicate).

unfoldWhileM' :: (Monad m, MonadPlus f) => (a -> Bool) -> m a -> m (f a)Source

Repeatedly evaluates the second argument until the value satisfies the given predicate, and returns a MonadPlus collection of all values that satisfied the predicate. Discards the final one (which failed the predicate).

unfoldrM :: Monad m => (a -> m (Maybe (b, a))) -> a -> m [b]Source

See unfoldr. This is a monad-friendly version of that.

unfoldrM' :: (Monad m, MonadPlus f) => (a -> m (Maybe (b, a))) -> a -> m (f b)Source

See unfoldr. This is a monad-friendly version of that, with a twist. Rather than returning a list, it returns any MonadPlus type of your choice.

concatM :: Monad m => [a -> m a] -> a -> m aSource

Compose a list of monadic actions into one action. Composes using (>=>) - that is, the output of each action is fed to the input of the one after it in the list.

andM :: Monad m => [m Bool] -> m BoolSource

short-circuit and for values of type Monad m => m Bool

orM :: Monad m => [m Bool] -> m BoolSource

short-circuit or for values of type Monad m => m Bool

anyPM :: Monad m => [a -> m Bool] -> a -> m BoolSource

short-circuit any with a list of "monadic predicates". Tests the value presented against each predicate in turn until one passes, then returns True without any further processing. If none passes, returns False.

allPM :: Monad m => [a -> m Bool] -> a -> m BoolSource

short-circuit all with a list of "monadic predicates". Tests the value presented against each predicate in turn until one fails, then returns False. if none fail, returns True.

anyM :: Monad m => (a -> m Bool) -> [a] -> m BoolSource

short-circuit any with a "monadic predicate".

allM :: Monad m => (a -> m Bool) -> [a] -> m BoolSource

short-circuit all with a "monadic predicate".

dropWhileM :: Monad m => (a -> m Bool) -> [a] -> m [a]Source

trimM :: Monad m => (a -> m Bool) -> [a] -> m [a]Source

like dropWhileM but trims both ends of the list.

firstM :: Monad m => (a -> m Bool) -> [a] -> m (Maybe a)Source

return the first value from a list, if any, satisfying the given predicate.

minimaOnByM :: Monad m => (a -> m b) -> (b -> b -> m Ordering) -> [a] -> m [a]Source

maximaOnByM :: Monad m => (a -> m b) -> (b -> b -> m Ordering) -> [a] -> m [a]Source

minimaByM :: Monad m => (a -> a -> m Ordering) -> [a] -> m [a]Source

maximaByM :: Monad m => (a -> a -> m Ordering) -> [a] -> m [a]Source

minimaOnM :: (Monad m, Ord b) => (a -> m b) -> [a] -> m [a]Source

maximaOnM :: (Monad m, Ord b) => (a -> m b) -> [a] -> m [a]Source

minimumOnByM :: Monad m => (a -> m b) -> (b -> b -> m Ordering) -> [a] -> m (Maybe a)Source

maximumOnByM :: Monad m => (a -> m b) -> (b -> b -> m Ordering) -> [a] -> m (Maybe a)Source

minimumByM :: Monad m => (a -> a -> m Ordering) -> [a] -> m (Maybe a)Source

maximumByM :: Monad m => (a -> a -> m Ordering) -> [a] -> m (Maybe a)Source

minimumOnM :: (Monad m, Ord b) => (a -> m b) -> [a] -> m (Maybe a)Source

maximumOnM :: (Monad m, Ord b) => (a -> m b) -> [a] -> m (Maybe a)Source

atomLoop :: STM a -> IO ()Source

forever and atomically rolled into one.

waitFor :: (a -> Bool) -> STM a -> STM aSource

retry until the given condition is true of the given value. Then return the value that satisfied the condition.

waitForTrue :: STM Bool -> STM ()Source

retry until the given value is True.

waitForJust :: STM (Maybe a) -> STM aSource

retry until the given value is Just _, returning the contained value.

waitForEvent :: (a -> Bool) -> TChan a -> STM aSource

waitFor a value satisfying a condition to come out of a TChan, reading and discarding everything else. Returns the winner.