break-1.0.0: Break from a loop

Safe HaskellNone
LanguageHaskell2010

Control.Break

Contents

Description

Example usage:

import Control.Break
import Control.Monad.State
import Prelude hiding (break)

example :: State Int ()
example = loop (do
    n <- lift get                -- Inside a `loop`, wrap commands in `lift`
    if n < 10
        then lift (put (n + 1))  -- You keep looping by default
        else break () )          -- Use `break` to exit from the `loop`

The loop command runs the given command repeatedly until the command breaks from the loop using break:

>>> execState example 0
10

For some effects (like State), you can omit lift:

example :: State Int ()
example = loop (do
    n <- get
    if n < 10
        then put (n + 1)
        else break () )

The loop will return whatever value you supply to break:

example :: State Int Bool
example = loop (do
    n <- get
    if n < 10
        then put (n + 1)
        else break True )
>>> runState example 0
(True,10)

Synopsis

Break

data Break r m a Source

For the most common use cases you will:

  • build Break commands using lift or break

    • combine Break commands using do notation
    • consume Break commands using loop

    The meaning of the type parameters:

    • r: the argument type of break and the return type of the loop
    • m: the base Monad that you are running in a loop
    • a: the return type of a Break command (not the same as the return value of the loop)

Instances

MonadState s m => MonadState s (Break r m) 
MonadWriter w m => MonadWriter w (Break r m) 
MonadTrans (Break r) 
Monad m => Monad (Break r m) 
Functor m => Functor (Break r m) 
(Monad m, Functor m) => Applicative (Break r m) 
MonadIO m => MonadIO (Break r m) 
MonadCont m => MonadCont (Break r m) 

loop :: Monad m => Break r m () -> m r Source

(loop m) runs the action 'm' repeatedly until you break from the loop

break :: Monad m => r -> Break r m a Source

break from a loop

The argument you supply to break is the return value of the loop

Re-exports

lift :: MonadTrans t => forall m a. Monad m => m a -> t m a

Lift a computation from the argument monad to the constructed monad.