monadology-0.3: The best ideas in monad-related classes and types.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Ology.General.Exception

Synopsis

Documentation

class Monad m => MonadException m where Source #

Pretty much every monad can be made an instance of this class.

Associated Types

type Exc m :: Type Source #

The type of all exceptions of this monad.

Methods

throwExc :: Exc m -> m a Source #

catchExc :: m a -> (Exc m -> m a) -> m a Source #

Instances

Instances details
MonadException Identity Source # 
Instance details

Defined in Control.Monad.Ology.General.Exception.Class

Associated Types

type Exc Identity Source #

MonadException IO Source # 
Instance details

Defined in Control.Monad.Ology.General.Exception.Class

Associated Types

type Exc IO Source #

Methods

throwExc :: Exc IO -> IO a Source #

catchExc :: IO a -> (Exc IO -> IO a) -> IO a Source #

MonadException Maybe Source # 
Instance details

Defined in Control.Monad.Ology.General.Exception.Class

Associated Types

type Exc Maybe Source #

Methods

throwExc :: Exc Maybe -> Maybe a Source #

catchExc :: Maybe a -> (Exc Maybe -> Maybe a) -> Maybe a Source #

MonadException [] Source # 
Instance details

Defined in Control.Monad.Ology.General.Exception.Class

Associated Types

type Exc [] Source #

Methods

throwExc :: Exc [] -> [a] Source #

catchExc :: [a] -> (Exc [] -> [a]) -> [a] Source #

(MonadInner inner, MonadException inner) => TransConstraint MonadException (ComposeInner inner) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ComposeInner

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadException m => Dict (MonadException (ComposeInner inner m)) Source #

TransConstraint MonadException (LifecycleT :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

TransConstraint MonadException (ExceptT e) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadException m => Dict (MonadException (ExceptT e m)) Source #

TransConstraint MonadException (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.IdentityT

TransConstraint MonadException (ReaderT r) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ReaderT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadException m => Dict (MonadException (ReaderT r m)) Source #

TransConstraint MonadException (StateT s) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.StateT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadException m => Dict (MonadException (StateT s m)) Source #

Monoid w => TransConstraint MonadException (WriterT w) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.WriterT

Methods

hasTransConstraint :: forall (m :: Type -> Type). MonadException m => Dict (MonadException (WriterT w m)) Source #

MonadException (Either e) Source # 
Instance details

Defined in Control.Monad.Ology.General.Exception.Class

Associated Types

type Exc (Either e) Source #

Methods

throwExc :: Exc (Either e) -> Either e a Source #

catchExc :: Either e a -> (Exc (Either e) -> Either e a) -> Either e a Source #

MonadException (Result e) Source # 
Instance details

Defined in Control.Monad.Ology.General.Exception.Class

Associated Types

type Exc (Result e) Source #

Methods

throwExc :: Exc (Result e) -> Result e a Source #

catchExc :: Result e a -> (Exc (Result e) -> Result e a) -> Result e a Source #

MonadException m => MonadException (MaybeT m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.MaybeT

Associated Types

type Exc (MaybeT m) Source #

Methods

throwExc :: Exc (MaybeT m) -> MaybeT m a Source #

catchExc :: MaybeT m a -> (Exc (MaybeT m) -> MaybeT m a) -> MaybeT m a Source #

Monoid p => MonadException ((,) p) Source # 
Instance details

Defined in Control.Monad.Ology.General.Exception.Class

Associated Types

type Exc ((,) p) Source #

Methods

throwExc :: Exc ((,) p) -> (p, a) Source #

catchExc :: (p, a) -> (Exc ((,) p) -> (p, a)) -> (p, a) Source #

(MonadInner inner, MonadException inner, MonadException m) => MonadException (ComposeInner inner m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ComposeInner

Associated Types

type Exc (ComposeInner inner m) Source #

Methods

throwExc :: Exc (ComposeInner inner m) -> ComposeInner inner m a Source #

catchExc :: ComposeInner inner m a -> (Exc (ComposeInner inner m) -> ComposeInner inner m a) -> ComposeInner inner m a Source #

(MonadOuter outer, MonadException m) => MonadException (ComposeOuter outer m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ComposeOuter

Associated Types

type Exc (ComposeOuter outer m) Source #

Methods

throwExc :: Exc (ComposeOuter outer m) -> ComposeOuter outer m a Source #

catchExc :: ComposeOuter outer m a -> (Exc (ComposeOuter outer m) -> ComposeOuter outer m a) -> ComposeOuter outer m a Source #

MonadException m => MonadException (LifecycleT m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.LifecycleT

Associated Types

type Exc (LifecycleT m) Source #

MonadException m => MonadException (WithT m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.WithT

Associated Types

type Exc (WithT m) Source #

Methods

throwExc :: Exc (WithT m) -> WithT m a Source #

catchExc :: WithT m a -> (Exc (WithT m) -> WithT m a) -> WithT m a Source #

MonadException m => MonadException (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ExceptT

Associated Types

type Exc (ExceptT e m) Source #

Methods

throwExc :: Exc (ExceptT e m) -> ExceptT e m a Source #

catchExc :: ExceptT e m a -> (Exc (ExceptT e m) -> ExceptT e m a) -> ExceptT e m a Source #

MonadException m => MonadException (IdentityT m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.IdentityT

Associated Types

type Exc (IdentityT m) Source #

Methods

throwExc :: Exc (IdentityT m) -> IdentityT m a Source #

catchExc :: IdentityT m a -> (Exc (IdentityT m) -> IdentityT m a) -> IdentityT m a Source #

MonadException m => MonadException (ReaderT r m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.ReaderT

Associated Types

type Exc (ReaderT r m) Source #

Methods

throwExc :: Exc (ReaderT r m) -> ReaderT r m a Source #

catchExc :: ReaderT r m a -> (Exc (ReaderT r m) -> ReaderT r m a) -> ReaderT r m a Source #

MonadException m => MonadException (StateT s m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.StateT

Associated Types

type Exc (StateT s m) Source #

Methods

throwExc :: Exc (StateT s m) -> StateT s m a Source #

catchExc :: StateT s m a -> (Exc (StateT s m) -> StateT s m a) -> StateT s m a Source #

(Monoid w, MonadException m) => MonadException (WriterT w m) Source # 
Instance details

Defined in Control.Monad.Ology.Specific.WriterT

Associated Types

type Exc (WriterT w m) Source #

Methods

throwExc :: Exc (WriterT w m) -> WriterT w m a Source #

catchExc :: WriterT w m a -> (Exc (WriterT w m) -> WriterT w m a) -> WriterT w m a Source #

MonadException ((->) r) Source # 
Instance details

Defined in Control.Monad.Ology.General.Exception.Class

Associated Types

type Exc ((->) r) Source #

Methods

throwExc :: Exc ((->) r) -> r -> a Source #

catchExc :: (r -> a) -> (Exc ((->) r) -> r -> a) -> r -> a Source #

catchSomeExc :: forall m a. MonadException m => m a -> (Exc m -> m (Maybe a)) -> m a Source #

Catch all exceptions, optionally returning or re-throwing.

fromResultExc :: forall m a. MonadException m => Result (Exc m) a -> m a Source #

tryExc :: forall m a. MonadException m => m a -> m (Result (Exc m) a) Source #

Catch all exceptions as a Result.

onException :: forall m a. MonadException m => m a -> m () -> m a Source #

Run the handler on exception. Does not mask asynchronous exceptions on the handler.

catchPureError :: a -> IO (Maybe SomeException) Source #

This catches certain "bottom values". Of course, since non-termination is bottom, this cannot catch all bottoms.

mask :: forall m b. MonadTunnelIO m => ((forall a. m a -> m a) -> m b) -> m b Source #

Run with asynchronous exceptions masked, passing an unmask function.

bracket :: forall m a b. (MonadException m, MonadTunnelIO m) => m a -> (a -> m ()) -> (a -> m b) -> m b Source #

Bracket an operation with before and after operations. The whole thing is masked, with the main operation unmasked.

finally :: forall m a. (MonadException m, MonadTunnelIO m) => m a -> m () -> m a Source #

Variant of bracket.

bracket_ :: forall m. (MonadException m, MonadTunnelIO m) => m () -> m () -> m --> m Source #

Variant of bracket.

bracketNoMask :: forall m a b. MonadException m => m a -> (a -> m ()) -> (a -> m b) -> m b Source #

Like bracket, but doesn't mask asynchronous exceptions.

bracketNoMask_ :: forall m. MonadException m => m () -> m () -> m --> m Source #

Variant of bracketNoMask.

bracketFake :: forall m a b. Monad m => m a -> (a -> m ()) -> (a -> m b) -> m b Source #

Like bracketNoMask, but doesn't catch any exceptions.

data SomeException #

The SomeException type is the root of the exception type hierarchy. When an exception of type e is thrown, behind the scenes it is encapsulated in a SomeException.

Instances

Instances details
Exception SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Show SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

evaluate :: a -> IO a #

Evaluate the argument to weak head normal form.

evaluate is typically used to uncover any exceptions that a lazy value may contain, and possibly handle them.

evaluate only evaluates to weak head normal form. If deeper evaluation is needed, the force function from Control.DeepSeq may be handy:

evaluate $ force x

There is a subtle difference between evaluate x and return $! x, analogous to the difference between throwIO and throw. If the lazy value x throws an exception, return $! x will fail to return an IO action and will throw an exception instead. evaluate x, on the other hand, always produces an IO action; that action will throw an exception upon execution iff x throws an exception upon evaluation.

The practical implication of this difference is that due to the imprecise exceptions semantics,

(return $! error "foo") >> error "bar"

may throw either "foo" or "bar", depending on the optimizations performed by the compiler. On the other hand,

evaluate (error "foo") >> error "bar"

is guaranteed to throw "foo".

The rule of thumb is to use evaluate to force or handle exceptions in lazy values. If, on the other hand, you are forcing a lazy value for efficiency reasons only and do not care about exceptions, you may use return $! x.