control-monad-loop-0.1: Simple monad transformer for imperative-style loops

Maintainerjoeyadams3.14159@gmail.com
Safe HaskellSafe-Infered

Control.Monad.Trans.Loop

Contents

Description

 

Synopsis

The LoopT monad transformer

newtype LoopT c e m a Source

LoopT is a monad transformer for the loop body. It provides two capabilities:

Constructors

LoopT 

Fields

runLoopT :: forall r. (c -> m r) -> (e -> m r) -> (a -> m r) -> m r
 

Instances

MonadBase b m => MonadBase b (LoopT c e m) 
MonadTrans (LoopT c e) 
Monad (LoopT c e m) 
Functor (LoopT c e m) 
Applicative (LoopT c e m) 
MonadIO m => MonadIO (LoopT c e m) 

stepLoopT :: Monad m => LoopT c e m c -> (c -> m e) -> m eSource

Call a loop body, passing it a continuation for the next iteration. This can be used to construct custom looping constructs. For example, here is the definition of foreach:

foreach list body = loop list
  where loop []     = return ()
        loop (x:xs) = stepLoopT (body x) (\_ -> loop xs)

continue and exit

continue :: LoopT () e m aSource

Skip the rest of the loop body and go to the next iteration.

exit :: LoopT c () m aSource

Break out of the loop entirely.

continueWith :: c -> LoopT c e m aSource

Like continue, but return a value from the loop body.

exitWith :: e -> LoopT c e m aSource

Like exit, but return a value from the loop as a whole. See the documentation of iterateLoopT for an example.

Looping constructs

foreach :: Monad m => [a] -> (a -> LoopT c () m c) -> m ()Source

Call the loop body with each item in the list.

If you do not need to continue or exit the loop, consider using forM_ instead.

while :: Monad m => m Bool -> LoopT c () m c -> m ()Source

Repeat the loop body while the predicate holds. Like a while loop in C, the condition is tested first.

doWhile :: Monad m => LoopT a a m a -> m Bool -> m aSource

Like a do while loop in C, where the condition is tested after the loop body.

doWhile returns the result of the last iteration. This is possible because, unlike foreach and while, the loop body is guaranteed to be executed at least once.

once :: Monad m => LoopT a a m a -> m aSource

Execute the loop body once. This is a convenient way to introduce early exit support to a block of code.

continue and exit do the same thing inside of once.

repeatLoopT :: Monad m => LoopT c e m a -> m eSource

Execute the loop body again and again. The only way to exit repeatLoopT is to call exit or exitWith.

iterateLoopT :: Monad m => c -> (c -> LoopT c e m c) -> m eSource

Call the loop body again and again, passing it the result of the previous iteration each time around. The only way to exit iterateLoopT is to call exit or exitWith.

Example:

count :: Int -> IO Int
count n = iterateLoopT 0 $ \i ->
    if i < n
        then do
            lift $ print i
            return $ i+1
        else exitWith i

Lifting other operations

liftLocalLoopT :: Monad m => (forall a. m a -> m a) -> LoopT c e m b -> LoopT c e m bSource

Lift a function like local or mask_.