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

Control.Monad.Oops

Synopsis

Catching and throwing exceptions

catchF :: forall x e e' f m a. Monad m => CatchF x e e' => (f x -> ExceptT (VariantF f e') m a) -> 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.

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

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

throwF :: 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.

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

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

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

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

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

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

Typeclasses to describe oops-style errors

class CouldBeF (xs :: [k]) (x :: k) Source #

When dealing with larger (or polymorphic) variants, it becomes difficult (or impossible) to construct VariantF values explicitly. In that case, the throwF function gives us a polymorphic way to lift values into variants.

>>> throwF (pure "Hello") :: VariantF Maybe '[Bool, Int, Double, String]
There (There (There (Here (Just "Hello"))))
>>> throwF (pure True) :: VariantF Maybe '[Bool, Int, Double, String]
Here (Just True)
>>> throwF (pure True) :: VariantF IO '[Int, Double, String]
...
... • Uh oh! I couldn't find Bool inside the variant!
...   If you're pretty sure I'm wrong, perhaps the variant type is ambiguous;
...   could you add some annotations?
...

Minimal complete definition

throwF, snatchF

Instances

Instances details
(TypeNotFound x :: Constraint) => CouldBeF ('[] :: [k]) (x :: k) Source # 
Instance details

Defined in Data.Variant

Methods

throwF :: f x -> VariantF f '[] Source #

snatchF :: VariantF f '[] -> Either (VariantF f '[]) (f x) Source #

CouldBeF (x ': xs :: [k]) (x :: k) Source # 
Instance details

Defined in Data.Variant

Methods

throwF :: f x -> VariantF f (x ': xs) Source #

snatchF :: VariantF f (x ': xs) -> Either (VariantF f (x ': xs)) (f x) Source #

CouldBeF xs x => CouldBeF (y ': xs :: [k]) (x :: k) Source # 
Instance details

Defined in Data.Variant

Methods

throwF :: f x -> VariantF f (y ': xs) Source #

snatchF :: VariantF f (y ': xs) -> Either (VariantF f (y ': xs)) (f x) Source #

class CouldBeF xs x => CouldBe (xs :: [Type]) (x :: Type) Source #

Just as with CouldBeF, we can "throw" values not in a functor context into a regular Variant.

>>> throw (3 :: Int) :: Variant '[Bool, Int, Double, String]
There (Here (Identity 3))
>>> throw "Woo!" :: Variant '[Bool, Int, Double, String]
There (There (There (Here (Identity "Woo!"))))

Minimal complete definition

throw, snatch

Instances

Instances details
CouldBeF xs x => CouldBe xs x Source # 
Instance details

Defined in Data.Variant

Methods

throw :: x -> Variant xs Source #

snatch :: Variant xs -> Either (Variant xs) x Source #

type CouldBeAnyOfF e xs = All (Map (CouldBeF e) xs) Source #

As with CouldBeAnyOf, we can also constrain a variant to represent several possible types, as we might with several CouldBeF constraints, using one type-level list.

type CouldBeAnyOf e xs = All (Map (CouldBe e) xs) Source #

Listing larger variants' constraints might amplify the noise of functions' signatures. The CouldBeAnyOfF constraint lets us specify several types a variant may contain in a single type-level list, as opposed to several independent constraints. So, we could replace,

f :: (e CouldBe Int, e CouldBe Bool, e CouldBe Char) => VariantF IO e

with the equivalent constraint,

f :: e CouldBeAnyOf '[Int, Bool, Char] => VariantF IO e

As CouldBeAnyOf is just short-hand, we can use throw just like when we have CouldBe constraints:

>>> :set -XTypeOperators
>>> :{
f :: e `CouldBeAnyOf` '[Int, Bool, Char] => Variant e
f = throw 'c'
:}

... and eliminate constraints in just the same way:

>>> :{
g :: e `CouldBeAnyOf` '[Int, Bool] => Either (Variant e) Char
g = catch @Char f
:}

Variant type to carry oops-style errors

type Variant (xs :: [Type]) = VariantF Identity xs Source #

Often, you'll want to have a choice of types that aren't all wrapped in a functor. For this, we provide the Variant type synonym, as well as equivalents of all the functions below. These functions take care of wrapping and unwrapping the Identity wrapper, too, so it should be invisible to users.

data VariantF (f :: k -> Type) (xs :: [k]) Source #

The type VariantF f '[x, y, z] is either f x, f y, or f z. The We construct these with Here, There . Here, and There . There . Here respectively, and we can think o fthe number of There-nestings as being the index of our chosen type in the type-level list of options.

Often, however, we'll want to avoid being too explicit about our list of types, preferring instead to describe it with constraints. See the methods below for more information!

> > :t [ Here (pure "Hello"), There (Here (pure True)) ]
Here (pure Hello), There (Here (pure True))
:: Applicative f => [VariantF f ([Char] : Bool : xs)]

Instances

Instances details
(EithersF f xs nested, Arbitrary nested) => Arbitrary (VariantF f xs) Source # 
Instance details

Defined in Data.Variant

Methods

arbitrary :: Gen (VariantF f xs) #

shrink :: VariantF f xs -> [VariantF f xs] #

(Monoid (f x), Semigroup (VariantF f (x ': xs))) => Monoid (VariantF f (x ': xs)) Source # 
Instance details

Defined in Data.Variant

Methods

mempty :: VariantF f (x ': xs) #

mappend :: VariantF f (x ': xs) -> VariantF f (x ': xs) -> VariantF f (x ': xs) #

mconcat :: [VariantF f (x ': xs)] -> VariantF f (x ': xs) #

AllF Semigroup f xs => Semigroup (VariantF f xs) Source # 
Instance details

Defined in Data.Variant

Methods

(<>) :: VariantF f xs -> VariantF f xs -> VariantF f xs #

sconcat :: NonEmpty (VariantF f xs) -> VariantF f xs #

stimes :: Integral b => b -> VariantF f xs -> VariantF f xs #

AllF Show f xs => Show (VariantF f xs) Source # 
Instance details

Defined in Data.Variant

Methods

showsPrec :: Int -> VariantF f xs -> ShowS #

show :: VariantF f xs -> String #

showList :: [VariantF f xs] -> ShowS #

AllF Eq f xs => Eq (VariantF f xs) Source # 
Instance details

Defined in Data.Variant

Methods

(==) :: VariantF f xs -> VariantF f xs -> Bool #

(/=) :: VariantF f xs -> VariantF f xs -> Bool #

(AllF Eq f xs, AllF Ord f xs) => Ord (VariantF f xs) Source # 
Instance details

Defined in Data.Variant

Methods

compare :: VariantF f xs -> VariantF f xs -> Ordering #

(<) :: VariantF f xs -> VariantF f xs -> Bool #

(<=) :: VariantF f xs -> VariantF f xs -> Bool #

(>) :: VariantF f xs -> VariantF f xs -> Bool #

(>=) :: VariantF f xs -> VariantF f xs -> Bool #

max :: VariantF f xs -> VariantF f xs -> VariantF f xs #

min :: VariantF f xs -> VariantF f xs -> VariantF f xs #

Embedding code with oops-style error handling into other code

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

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

runOopsInExceptT :: forall x m a. Monad m => ExceptT (Variant '[x]) m a -> ExceptT x m a Source #

Run an oops expression that throws one error in an ExceptT.

runOopsInEither :: forall x m a. Monad m => ExceptT (Variant '[x]) m a -> m (Either x a) Source #

Run an oops expression that throws one error in an Either.

This function can also be implemented this way (which could be instructive for implementing your own combinators)

suspend :: 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.

Error handling

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

Catch the specified exception and return the caught value as Left. If no value was caught, then return the returned value in Right.

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

Catch the specified exception and return the caught value as Left. If no value was caught, then return the returned value in Right.

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

Catch the specified exception and return Nothing. If no value was caught, then return the returned value in Just.

catchAndExitFailure :: 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.

recover :: 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.

recoverOrVoid :: 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)

Converting error values to oops-style error handling

onLeft :: forall x m a. Monad m => (x -> m a) -> m (Either x a) -> m a Source #

Handle the Left constructor of the returned Either

onNothing :: forall m a. Monad m => m a -> m (Maybe a) -> m a Source #

Handle the Nothing constructor of the returned Maybe

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

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

onNothingThrow :: forall e es m a. MonadError (Variant es) m => CouldBe es e => e -> m (Maybe a) -> m a Source #

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

hoistEither :: forall x e m a. MonadError (Variant e) m => e `CouldBe` 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.

hoistMaybe :: forall e es m a. MonadError (Variant es) m => CouldBe es e => e -> Maybe a -> m a Source #

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

Converting exceptions to oops-style error handling

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

Catch an exception of the specified type x and throw it as an error

onException :: forall x m a. MonadCatch m => Exception x => (x -> m a) -> m a -> m a Source #

Catch an exception of the specified type x and call the the handler h