oops-0.1.0.0: Combinators for handling errors of many types in a composable way
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Oops.Classic

Synopsis

MTL/transformer utilities

catchFM :: forall x e e' f m a. Monad m => CatchF x e e' => ExceptT (VariantF f e) m a -> (f x -> ExceptT (VariantF f e') m a) -> ExceptT (VariantF f e') m a Source #

When working in some monadic context, using catch becomes trickier. The intuitive behaviour is that each catch shrinks the variant in the left side of my MonadError, but this is therefore type-changing: as we can only throwError and catchError with a MonadError type, this is impossible!

To get round this problem, we have to specialise to ExceptT, which allows us to map over the error type and change it as we go. If the error we catch is the one in the variant that we want to handle, we pluck it out and deal with it. Otherwise, we "re-throw" the variant minus the one we've handled.

catchM :: forall x e e' m a. Monad m => Catch x e e' => ExceptT (Variant e) m a -> (x -> ExceptT (Variant e') m a) -> ExceptT (Variant e') m a Source #

Just the same as catchFM, but specialised for our plain Variant and sounding much less like a radio station.

snatchFM :: forall x e f m a. Monad m => e `CouldBe` x => ExceptT (VariantF f e) m a -> (f x -> ExceptT (VariantF f e) m a) -> ExceptT (VariantF f e) m a Source #

Same as catchFM except the error is not removed from the type. This is useful for writing recursive computations or computations that rethrow the same error type.

snatchM :: forall x e m a. Monad m => e `CouldBe` x => ExceptT (Variant e) m a -> (x -> ExceptT (Variant e) m a) -> ExceptT (Variant e) m a Source #

Same as catchM except the error is not removed from the type. This is useful for writing recursive computations or computations that rethrow the same error type.

throwFM :: forall x e f m a. MonadError (VariantF f e) m => e `CouldBe` x => f x -> m a Source #

Throw an error into a variant MonadError context. Note that this isn't type-changing, so this can work for any MonadError, rather than just ExceptT.

throwM :: forall x e m a. MonadError (Variant e) m => e `CouldBe` x => x -> m a Source #

Same as throwFM, but without the f context. Given a value of some type within a Variant within a MonadError context, "throw" the error.

runOops :: Monad m => ExceptT (Variant '[]) m a -> m a Source #

Add 'ExceptT (Variant '[])' to the monad transformer stack.

suspendM :: forall x m a n b. (m (Either x a) -> n (Either x b)) -> ExceptT x m a -> ExceptT x n b Source #

Suspend the ExceptT monad transformer from the top of the stack so that the stack can be manipulated without the ExceptT layer.

catchAndExitFailureM :: forall x e m a. MonadIO m => ExceptT (Variant (x ': e)) m a -> ExceptT (Variant e) m a Source #

Catch the specified exception. If that exception is caught, exit the program.

throwLeftM :: forall x e m a. MonadError (Variant e) m => CouldBeF e x => Monad m => Either x a -> m a Source #

When the expression of type 'Either x a' evaluates to 'Left x', throw the x, otherwise return a.

throwNothingM :: MonadError (Variant e) m => CouldBeF e () => Monad m => Maybe a -> m a Source #

When the expression of type 'Maybe a' evaluates to Nothing, throw (), otherwise return a.

recoverM :: forall x e m a. Monad m => (x -> a) -> ExceptT (Variant (x ': e)) m a -> ExceptT (Variant e) m a Source #

Catch the specified exception and return it instead. The evaluated computation must return the same type that is being caught.

recoverOrVoidM :: forall x e m. Monad m => ExceptT (Variant (x ': e)) m Void -> ExceptT (Variant e) m x Source #

Catch the specified exception and return it instead. The evaluated computation must return Void (ie. it never returns)