| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Raise
Contents
Description
Monadic raise semantics & helpers
Synopsis
- ensure :: (MonadRaise m, Raises m inner) => Either inner a -> m a
- ensureM :: (MonadRaise m, Raises m inner) => m (Either inner a) -> m a
- module Control.Monad.Raise.Class
- module Control.Monad.Raise.Constraint
- module Data.WorldPeace.Subset.Class
Documentation
ensure :: (MonadRaise m, Raises m inner) => Either inner a -> m a Source #
Lift a pure error (Either) into a MonadRaise context
i.e. Turn Lefts into raises.
Examples
>>>:{mayFail :: Int -> Either FooErr Int mayFail n = if n > 50 then Left FooErr else Right n :}
>>>:{goesBoom :: (MonadRaise m, m `Raises` FooErr) => m Int goesBoom = do first <- ensure $ mayFail 100 second <- ensure $ mayFail 42 return $ second * 10 :}
>>>goesBoom :: Result '[FooErr, BarErr] IntLeft (Identity FooErr)
ensureM :: (MonadRaise m, Raises m inner) => m (Either inner a) -> m a Source #
A version of ensure that takes monadic actions
Examples
>>>:{mayFailM :: Monad m => Int -> m (Either (OpenUnion '[FooErr, BarErr]) Int) mayFailM n = return $ if n > 50 then Left (openUnionLift FooErr) else Right n :}
>>>:{foo :: (MonadRaise m, RaisesOnly m '[FooErr, BarErr]) => m Int foo = do first <- ensureM $ mayFailM 100 second <- ensureM $ mayFailM first return (second * 10) :}
>>>runRescue (foo :: Rescue '[FooErr, BarErr] Int)Left (Identity FooErr)
Class Reexports
module Control.Monad.Raise.Class
Data Reexports
module Data.WorldPeace.Subset.Class