| Copyright | (c) 2009 - 2014 Peter Trsko. |
|---|---|
| License | BSD3 |
| Stability | provisional |
| Portability | non-portable (NoImplicitPrelude, depends on non-portable modules) |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Control.Monad.TaggedException.Core
Description
Core functionality.
- throw :: (Exception e, MonadThrow m) => e -> Throws e m a
- catch :: (Exception e, MonadCatch m) => Throws e m a -> (e -> m a) -> m a
- catch' :: (Exception e, MonadCatch m) => m a -> (e -> m a) -> m a
- handle :: (Exception e, MonadCatch m) => (e -> m a) -> Throws e m a -> m a
- handle' :: (Exception e, MonadCatch m) => (e -> m a) -> m a -> m a
- try :: (Exception e, MonadCatch m) => Throws e m a -> m (Either e a)
- mapException :: (Exception e, Exception e', MonadCatch m) => (e -> e') -> Throws e m a -> Throws e' m a
- onException :: (Exception e, MonadCatch m) => Throws e m a -> m b -> Throws e m a
- onException' :: MonadCatch m => m a -> m b -> m a
- data Throws e m a
- liftT :: (Exception e, MonadThrow m) => m a -> Throws e m a
- lift2T :: (Exception e, Exception e', MonadThrow m) => m a -> Throws e' (Throws e m) a
- lift3T :: (Exception e, Exception e', Exception e'', MonadThrow m) => m a -> Throws e'' (Throws e' (Throws e m)) a
- liftT1 :: (Exception e, MonadThrow m) => (m a -> m b) -> Throws e m a -> Throws e m b
- liftT2 :: (Exception e, MonadThrow m) => (m a -> m b -> m c) -> Throws e m a -> Throws e m b -> Throws e m c
- liftT3 :: (Exception e, MonadThrow m) => (m a -> m b -> m c -> m d) -> Throws e m a -> Throws e m b -> Throws e m c -> Throws e m d
- joinT :: (Exception e, MonadThrow m) => Throws e (Throws e m) a -> Throws e m a
- joinT3 :: (Exception e, MonadThrow m) => Throws e (Throws e (Throws e m)) a -> Throws e m a
- flipT :: (Exception e, Exception e', MonadThrow m) => Throws e' (Throws e m) a -> Throws e (Throws e' m) a
- insideT :: (Exception e, MonadThrow m, MonadThrow m') => (m a -> m' b) -> Throws e m a -> Throws e m' b
- insideT2 :: (Exception e, MonadThrow m1, MonadThrow m2, MonadThrow m3) => (m1 a -> m2 b -> m3 c) -> Throws e m1 a -> Throws e m2 b -> Throws e m3 c
- insideT3 :: (Exception e, MonadThrow m1, MonadThrow m2, MonadThrow m3, MonadThrow m4) => (m1 a -> m2 b -> m3 c -> m4 d) -> Throws e m1 a -> Throws e m2 b -> Throws e m3 c -> Throws e m4 d
- insideTf :: (Exception e, Functor f, MonadThrow m, MonadThrow m') => (f (m a) -> m' b) -> f (Throws e m a) -> Throws e m' b
- insideTf2 :: (Exception e, Functor f, Functor f', MonadThrow m, MonadThrow m') => (f (f' (m a)) -> m' b) -> f (f' (Throws e m a)) -> Throws e m' b
- embedT :: (Exception e, MonadThrow m, MonadThrow m') => (m a -> Throws e m' b) -> Throws e m a -> Throws e m' b
MonadException
throw :: (Exception e, MonadThrow m) => e -> Throws e m a Source
catch :: (Exception e, MonadCatch m) => Throws e m a -> (e -> m a) -> m a Source
catch' :: (Exception e, MonadCatch m) => m a -> (e -> m a) -> m a Source
Catch any exception.
handle :: (Exception e, MonadCatch m) => (e -> m a) -> Throws e m a -> m a Source
handle' :: (Exception e, MonadCatch m) => (e -> m a) -> m a -> m a Source
Flipped version of catch'
mapException :: (Exception e, Exception e', MonadCatch m) => (e -> e') -> Throws e m a -> Throws e' m a Source
Map one exception to another.
Mapping "inner" exception has generally two forms:
1. Modifying raised exception, but not changing its type:
liftT1.mapException:: (Exceptione,Exceptione',MonadCatchm) => (e -> e) ->Throwse' (Throwse m) a ->Throwse' (Throwse m) a
2. Modifying raised exception, including its type:
insideT.mapException:: (Exceptione,Exceptione1,Exceptione2,MonadCatchm) => (e1 -> e2) ->Throwse (Throwse1 m) a ->Throwse (Throwse2 m) a
Unhiding exception by mapping it in to a different type of exception:
\f ->mapExceptionf .liftT:: (Exceptione,Exceptione',MonadCatchm) => (e -> e') -> m a ->Throwse' m a
Arguments
| :: (Exception e, MonadCatch m) | |
| => Throws e m a | Computation that may raise exception |
| -> m b | The computation to run if an exception |
| -> Throws e m a |
Arguments
| :: MonadCatch m | |
| => m a | Computation that may raise exception |
| -> m b | The computation to run if an exception is raised |
| -> m a |
Same as onException, but uses catch' and so second computation is
executed if any exception is raised.
Exception tag
Exception tag.
Instances
| Typeable (k -> (k -> *) -> k -> *) (Throws k k) | |
| MFunctor (Throws k * e) | Since |
| MMonad (Throws k * e) | Since |
| MonadTrans (Throws k * e) | |
| Alternative f => Alternative (Throws k * e f) | |
| Monad m => Monad (Throws k * e m) | |
| Functor f => Functor (Throws k * e f) | |
| MonadPlus m => MonadPlus (Throws k * e m) | |
| Applicative f => Applicative (Throws k * e f) | |
| MonadThrow m => MonadThrow (Throws k * e m) | Since |
| MonadCatch m => MonadCatch (Throws k * e m) | Since |
| MonadMask m => MonadMask (Throws k * e m) | Since |
| MonadIO m => MonadIO (Throws k * e m) | |
| Generic (Throws k k e m a) | |
| type Rep (Throws k k1 e m a) |
Cobinators
liftT :: (Exception e, MonadThrow m) => m a -> Throws e m a Source
Construct exception tag, with type restrictions.
Reflect raised exception in function's type:
import Control.Monad.TaggedException (Throws, liftT) import System.IO (Handle, IOMode) import qualified System.IO as IO (openFile) openFile :: FilePath -> IOMode -> Throws IOError IO Handle openFile = (liftT .) . IO.openFile
Lifting m to :Throws e m
import Control.Exception (Exception)
import Control.Monad.TaggedException (Throws, liftT, throw)
import Data.Typeable (Typeable)
data EmptyString = EmptyString
deriving (Show, Typeable)
instance Exception EmptyString
writeIfNotEmpty
:: FilePath
-> String
-> Throws EmptyString IO ()
writeIfNotEmpty filename str = do
when (null str) $ throw EmptyString
liftT $ writeFile filename strWe have a some commonly used patterns:
(liftT.) :: (Exceptione,MonadThrowm) => (a -> m b) -> a ->Throwse m b
Above is also usable for lifting throw-like functions:
import Control.Monad.Trans.Class (MonadTrans(lift)) ((liftT.lift) .) :: (Exceptione ,MonadThrowm ,MonadThrow(t m) ,MonadTranst) => (a -> m b) -> a ->Throwse (t m) b
lift3T :: (Exception e, Exception e', Exception e'', MonadThrow m) => m a -> Throws e'' (Throws e' (Throws e m)) a Source
liftT1 :: (Exception e, MonadThrow m) => (m a -> m b) -> Throws e m a -> Throws e m b Source
liftT for functions with arity one.
liftT2 :: (Exception e, MonadThrow m) => (m a -> m b -> m c) -> Throws e m a -> Throws e m b -> Throws e m c Source
liftT for functions with arity two.
liftT3 :: (Exception e, MonadThrow m) => (m a -> m b -> m c -> m d) -> Throws e m a -> Throws e m b -> Throws e m c -> Throws e m d Source
liftT for functions with arity three.
joinT :: (Exception e, MonadThrow m) => Throws e (Throws e m) a -> Throws e m a Source
Join two outermost exception tags.
joinT3 :: (Exception e, MonadThrow m) => Throws e (Throws e (Throws e m)) a -> Throws e m a Source
Join three outermost exception tags.
flipT :: (Exception e, Exception e', MonadThrow m) => Throws e' (Throws e m) a -> Throws e (Throws e' m) a Source
Flip two outermost exception tags.
insideT :: (Exception e, MonadThrow m, MonadThrow m') => (m a -> m' b) -> Throws e m a -> Throws e m' b Source
Generalized liftT. Usage examples:
insideTlift :: (MonadThrow(t m),MonadThrowm,Exceptione, MonadTrans t) =>Throwse m b ->Throwse (t m) b
This is variation on the first example that explicitly lifts monad:
insideT WriterT
:: (Exception e, MonadThrow m, Monoid w)
=> Throws e m (b, w)
-> Throws e (WriterT w m) b
Some useful compositions of exception tag combinators:
insideTflipT:: (Exceptione0,Exceptione1,Exceptione2,MonadThrowm) =>Throwse0 (Throwse1 (Throwse2 m)) a ->Throwse0 (Throwse2 (Throwse1 m)) a
flipT.insideTflipT:: (Exceptione0,Exceptione1,Exceptione2,MonadThrowm) =>Throwse0 (Throwse1 (Throwse2 m)) a ->Throwse2 (Throwse0 (Throwse1 m)) a
insideT2 :: (Exception e, MonadThrow m1, MonadThrow m2, MonadThrow m3) => (m1 a -> m2 b -> m3 c) -> Throws e m1 a -> Throws e m2 b -> Throws e m3 c Source
Generalized liftT2.
insideT3 :: (Exception e, MonadThrow m1, MonadThrow m2, MonadThrow m3, MonadThrow m4) => (m1 a -> m2 b -> m3 c -> m4 d) -> Throws e m1 a -> Throws e m2 b -> Throws e m3 c -> Throws e m4 d Source
Generalized liftT3.
insideTf :: (Exception e, Functor f, MonadThrow m, MonadThrow m') => (f (m a) -> m' b) -> f (Throws e m a) -> Throws e m' b Source
insideTf2 :: (Exception e, Functor f, Functor f', MonadThrow m, MonadThrow m') => (f (f' (m a)) -> m' b) -> f (f' (Throws e m a)) -> Throws e m' b Source
embedT :: (Exception e, MonadThrow m, MonadThrow m') => (m a -> Throws e m' b) -> Throws e m a -> Throws e m' b Source
Since 1.2.0.0