backtracking-exceptions-0.1.0.0: A monad transformer for backtracking exceptions

Copyright(c) Jamaal Malek <mjm540@york.ac.uk> 2014
LicenseBSD3
Maintainermjm540@york.ac.uk
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Except.Backtracking

Contents

Description

 

Synopsis

The BExceptT monad transformer

data BExceptT e m a Source

BExceptT is a monad transformer that adds backtracking exception handling to its base monad.

Instances

(Functor m, MonadRWS r w s m) => MonadRWS r w s (BExceptT e m) 
MonadState s m => MonadState s (BExceptT e m) 
MonadReader r m => MonadReader r (BExceptT e m) 
(Functor f, MonadFree f m) => MonadFree f (BExceptT e m) 
Monad m => MonadError e (BExceptT e m) 
(Functor m, MonadWriter w m) => MonadWriter w (BExceptT e m) 
MonadTrans (BExceptT e) 
(Monad m, Semigroup e, Monoid e) => Alternative (BExceptT e m) 
Monad (BExceptT e m) 
Functor (BExceptT e m) 
(Monad m, Semigroup e, Monoid e) => MonadPlus (BExceptT e m) 
Applicative (BExceptT e m) 
MonadIO m => MonadIO (BExceptT e m) 
(Monad m, Semigroup e, Monoid e) => Plus (BExceptT e m) 
(Monad m, Semigroup e) => Alt (BExceptT e m) 
Apply (BExceptT e m) 

bExceptT :: Monad m => m (Either e a) -> BExceptT e m a Source

bExceptT constructs a BExceptT from the base monad.

runBExceptT :: Monad m => BExceptT e m a -> m (Either e a) Source

runBExceptT does the opposite of bExceptT

hoistEither :: Monad m => Either e a -> BExceptT e m a Source

hoistEither constructs a BExceptT from an Either value.

Usage example and explanation

The following example shows the basic operation of the BExceptT monad.

example1 :: StateT Int (BExceptT String IO) ()
example1 = do
    put 1
    catchError (put 2) $ \e -> do
        i <- get
        liftIO $ do
            putStrLn $ "caught an error: '" <|> e <|> "'"
            putStrLn $ "setting i to 4, current value is " <|> show i
        put 4
    i <- get
    when (i /= 4) $ put 3
    liftIO $ putStrLn "reading i"
    i <- get
    when (i /= 4) $ throwError "i isnt 4"

runexample1 :: IO (Either String ((), Int))
runexample1 = runBExceptT $ flip runStateT 0 example1

The output produced is:

reading i
caught an error: 'i isnt 4'
setting i to 4, current value is 1
reading i
Right ((),4)

At first, the execution proceeds normally, setting the state to 1, then 2, then 3. The final line throws an exception because the state is 3, not 4. The execution then backtracks to before put 2 was executed. The state has been restored to 1 at this stage. The exception handler applied to put 2 is executed, and execution continues from the line below.

Replacing when (i /= 4) $ put 3 with put 3 will not create an infinite loop, after the failure of each exception handler (in this case there is only one) execution will stop and return an error.

Using BExceptT String (StateT Int IO) () instead of StateT Int (BExceptT String IO) () means that the state will not be restored after an error.

The Alternative and MonadPlus instances of BExceptT can be used like the instances in a nondeterminism monad, such as the list monad, except only one successful result at most will be returned.