Safe Haskell | None |
---|---|
Language | Haskell2010 |
Defines capabilities for actions that may fail or throw exceptions, and optionally may catch exceptions.
Monads based on IO
can use the underlying IO
exception mechanism
to that end. The details of synchronous and asynchronous exception
handling depend on the strategy used.
See MonadThrow
, SafeExceptions
, MonadUnliftIO
.
The associated tag can be used to select the exception type, or to select a layer in monad transformer stacks. Note, that it is illegal to have multiple tags refer to overlapping exception types in the same layer. Consider the following example
newtype M a = M (IO a) deriving (HasThrow "foo" IOException) via MonadUnliftIO IO deriving (HasThrow "bar" SomeException) via MonadUnliftIO IO
In this case the tags "foo"
and "bar"
refer to overlapping exception
types in the same layer, because catch @"bar"
may also catch an exception
thrown under "foo"
.
Synopsis
- class Monad m => HasThrow (tag :: k) (e :: *) (m :: * -> *) | tag m -> e where
- throw :: forall tag e m a. HasThrow tag e m => e -> m a
- class HasThrow tag e m => HasCatch (tag :: k) (e :: *) (m :: * -> *) | tag m -> e where
- catch_ :: Proxy# tag -> m a -> (e -> m a) -> m a
- catchJust_ :: Proxy# tag -> (e -> Maybe b) -> m a -> (b -> m a) -> m a
- catch :: forall tag e m a. HasCatch tag e m => m a -> (e -> m a) -> m a
- catchJust :: forall tag e m a b. HasCatch tag e m => (e -> Maybe b) -> m a -> (b -> m a) -> m a
- wrapError :: forall innertag t (cs :: [Capability]) inner m a. (forall x. Coercible (t m x) (m x), HasCatch innertag inner (t m), All cs m) => (forall m'. All (HasCatch innertag inner ': cs) m' => m' a) -> m a
- type HasThrow' (tag :: k) = HasThrow tag (TypeOf k tag)
- type HasCatch' (tag :: k) = HasCatch tag (TypeOf k tag)
- type family TypeOf k (s :: k) :: *
- newtype MonadError m (a :: *) = MonadError (m a)
- newtype MonadThrow (e :: *) m (a :: *) = MonadThrow (m a)
- newtype MonadCatch (e :: *) m (a :: *) = MonadCatch (m a)
- newtype SafeExceptions (e :: *) m (a :: *) = SafeExceptions (m a)
- newtype MonadUnliftIO (e :: *) m (a :: *) = MonadUnliftIO (m a)
- module Capability.Accessors
- class (Typeable e, Show e) => Exception e where
- toException :: e -> SomeException
- fromException :: SomeException -> Maybe e
- displayException :: e -> String
- class Typeable (a :: k)
Relational capabilities
class Monad m => HasThrow (tag :: k) (e :: *) (m :: * -> *) | tag m -> e where Source #
Capability to throw exceptions of type e
under tag
.
HasThrow
/HasCatch
capabilities at different tags should be independent.
See HasCatch
.
Instances
(HasThrow tag e m, MonadTrans t, Monad (t m)) => HasThrow (tag :: k) e (Lift (t m)) Source # | Lift one layer in a monad transformer stack. |
MonadError e m => HasThrow (tag :: k) e (MonadError m) Source # | |
Defined in Capability.Error throw_ :: Proxy# tag -> e -> MonadError m a Source # | |
(Exception e, MonadThrow m) => HasThrow (tag :: k) e (MonadThrow e m) Source # | |
Defined in Capability.Error throw_ :: Proxy# tag -> e -> MonadThrow e m a Source # | |
(Exception e, MonadThrow m) => HasThrow (tag :: k) e (SafeExceptions e m) Source # | |
Defined in Capability.Error throw_ :: Proxy# tag -> e -> SafeExceptions e m a Source # | |
(Exception e, MonadIO m) => HasThrow (tag :: k) e (MonadUnliftIO e m) Source # | |
Defined in Capability.Error throw_ :: Proxy# tag -> e -> MonadUnliftIO e m a Source # | |
(Exception e, MonadThrow m) => HasThrow (tag :: k) e (MonadCatch e m) Source # | |
Defined in Capability.Error throw_ :: Proxy# tag -> e -> MonadCatch e m a Source # | |
HasThrow oldtag e m => HasThrow (newtag :: k1) e (Rename oldtag m) Source # | Rename the tag. |
(forall x. Coercible (m x) (t2 (t1 m) x), Monad m, HasThrow tag e (t2 (t1 m))) => HasThrow (tag :: k) e ((t2 :.: t1) m) Source # | Compose two accessors. |
(AsConstructor' ctor sum e, HasThrow oldtag sum m) => HasThrow (ctor :: Symbol) e (Ctor ctor oldtag m) Source # | Wrap the exception |
throw :: forall tag e m a. HasThrow tag e m => e -> m a Source #
Throw an exception in the specified exception capability.
class HasThrow tag e m => HasCatch (tag :: k) (e :: *) (m :: * -> *) | tag m -> e where Source #
Capability to catch exceptions of type e
under tag
.
HasThrow
/HasCatch
capabilities at different tags should be independent.
In particular, the following program should throw SomeError
and not
return ()
.
> example ::
> (HasThrow Left SomeError m, HasCatch Right SomeError m)
> => m ()
> example =
> catch Left
> (throw
Right SomeError)
> _ -> pure ()
See wrapError
for a way to combine multiple exception types into one.
catch_ :: Proxy# tag -> m a -> (e -> m a) -> m a Source #
For technical reasons, this method needs an extra proxy argument.
You only need it if you are defining new instances of HasReader
.
Otherwise, you will want to use catch
.
See catch
for more documentation.
catchJust_ :: Proxy# tag -> (e -> Maybe b) -> m a -> (b -> m a) -> m a Source #
Instances
(HasCatch tag e m, MonadTransControl t, Monad (t m)) => HasCatch (tag :: k) e (Lift (t m)) Source # | Lift one layer in a monad transformer stack. |
MonadError e m => HasCatch (tag :: k) e (MonadError m) Source # | |
Defined in Capability.Error catch_ :: Proxy# tag -> MonadError m a -> (e -> MonadError m a) -> MonadError m a Source # catchJust_ :: Proxy# tag -> (e -> Maybe b) -> MonadError m a -> (b -> MonadError m a) -> MonadError m a Source # | |
(Exception e, MonadCatch m) => HasCatch (tag :: k) e (MonadCatch e m) Source # | |
Defined in Capability.Error catch_ :: Proxy# tag -> MonadCatch e m a -> (e -> MonadCatch e m a) -> MonadCatch e m a Source # catchJust_ :: Proxy# tag -> (e -> Maybe b) -> MonadCatch e m a -> (b -> MonadCatch e m a) -> MonadCatch e m a Source # | |
(Exception e, MonadCatch m) => HasCatch (tag :: k) e (SafeExceptions e m) Source # | |
Defined in Capability.Error catch_ :: Proxy# tag -> SafeExceptions e m a -> (e -> SafeExceptions e m a) -> SafeExceptions e m a Source # catchJust_ :: Proxy# tag -> (e -> Maybe b) -> SafeExceptions e m a -> (b -> SafeExceptions e m a) -> SafeExceptions e m a Source # | |
(Exception e, MonadUnliftIO m) => HasCatch (tag :: k) e (MonadUnliftIO e m) Source # | |
Defined in Capability.Error catch_ :: Proxy# tag -> MonadUnliftIO e m a -> (e -> MonadUnliftIO e m a) -> MonadUnliftIO e m a Source # catchJust_ :: Proxy# tag -> (e -> Maybe b) -> MonadUnliftIO e m a -> (b -> MonadUnliftIO e m a) -> MonadUnliftIO e m a Source # | |
HasCatch oldtag e m => HasCatch (newtag :: k1) e (Rename oldtag m) Source # | Rename the tag. Apply cautiously. E.g. the following code produces colliding instances,
where exceptions thrown in newtype Bad a = Bad (IO a) deriving (Functor, Applicative, Monad) deriving ( HasThrow "Foo" m , HasCatch "Foo" m ) via Rename () (MonadUnliftIO SomeError IO) deriving ( HasThrow "Bar" m , HasCatch "Bar" m ) via Rename () (MonadUnliftIO SomeError IO) |
(forall x. Coercible (m x) (t2 (t1 m) x), Monad m, HasCatch tag e (t2 (t1 m))) => HasCatch (tag :: k) e ((t2 :.: t1) m) Source # | Compose two accessors. |
(AsConstructor' ctor sum e, HasCatch oldtag sum m) => HasCatch (ctor :: Symbol) e (Ctor ctor oldtag m) Source # | Catch an exception of type |
catch :: forall tag e m a. HasCatch tag e m => m a -> (e -> m a) -> m a Source #
Provide a handler for exceptions thrown in the given action in the given exception capability.
catchJust :: forall tag e m a b. HasCatch tag e m => (e -> Maybe b) -> m a -> (b -> m a) -> m a Source #
wrapError :: forall innertag t (cs :: [Capability]) inner m a. (forall x. Coercible (t m x) (m x), HasCatch innertag inner (t m), All cs m) => (forall m'. All (HasCatch innertag inner ': cs) m' => m' a) -> m a Source #
Wrap exceptions inner
originating from the given action according to
the accessor t
. Retain arbitrary capabilities listed in cs
.
Example:
wrapError @"ComponentError" @(Ctor "ComponentError" "AppError") @'[] component component :: HasError "ComponentError" ComponentError m => m () data AppError = ComponentError ComponentError
This function is experimental and subject to change. See https://github.com/tweag/capability/issues/46.
Functional capabilities
type family TypeOf k (s :: k) :: * Source #
Type family associating a tag to the corresponding type. It is intended to simplify constraint declarations, by removing the need to redundantly specify the type associated to a tag.
It is poly-kinded, which allows users to define their own kind of tags.
Standard haskell types can also be used as tags by specifying the *
kind
when defining the type family instance.
Defining TypeOf
instances for Symbol
s (typelevel string
literals) is discouraged. Since symbols all belong to the same global
namespace, such instances could conflict with others defined in external
libraries. More generally, as for typeclasses, TypeOf
instances should
always be defined in the same module as the tag type to prevent issues due to
orphan instances.
Example:
import Capability.Reader data Foo data Bar type instance TypeOf * Foo = Int type instance TypeOf * Bar = String -- Same as: foo :: HasReader Foo Int M => … foo :: HasReader' Foo m => … foo = …
Strategies
newtype MonadError m (a :: *) Source #
Derive 'HasError from m
's MonadError
instance.
MonadError (m a) |
Instances
newtype MonadThrow (e :: *) m (a :: *) Source #
Derive HasThrow
from m
's MonadThrow
instance.
MonadThrow (m a) |
Instances
newtype MonadCatch (e :: *) m (a :: *) Source #
Derive 'HasCatch from m
's 'Control.Monad.Catch.MonadCatch instance.
MonadCatch (m a) |
Instances
newtype SafeExceptions (e :: *) m (a :: *) Source #
Derive HasError
using the functionality from the safe-exceptions
package.
SafeExceptions (m a) |
Instances
newtype MonadUnliftIO (e :: *) m (a :: *) Source #
Derive HasError
using the functionality from the unliftio
package.
MonadUnliftIO (m a) |
Instances
Modifiers
module Capability.Accessors
Re-exported
class (Typeable e, Show e) => Exception e where #
Any type that you wish to throw or catch as an exception must be an
instance of the Exception
class. The simplest case is a new exception
type directly below the root:
data MyException = ThisException | ThatException deriving Show instance Exception MyException
The default method definitions in the Exception
class do what we need
in this case. You can now throw and catch ThisException
and
ThatException
as exceptions:
*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException)) Caught ThisException
In more complicated examples, you may wish to define a whole hierarchy of exceptions:
--------------------------------------------------------------------- -- Make the root exception type for all the exceptions in a compiler data SomeCompilerException = forall e . Exception e => SomeCompilerException e instance Show SomeCompilerException where show (SomeCompilerException e) = show e instance Exception SomeCompilerException compilerExceptionToException :: Exception e => e -> SomeException compilerExceptionToException = toException . SomeCompilerException compilerExceptionFromException :: Exception e => SomeException -> Maybe e compilerExceptionFromException x = do SomeCompilerException a <- fromException x cast a --------------------------------------------------------------------- -- Make a subhierarchy for exceptions in the frontend of the compiler data SomeFrontendException = forall e . Exception e => SomeFrontendException e instance Show SomeFrontendException where show (SomeFrontendException e) = show e instance Exception SomeFrontendException where toException = compilerExceptionToException fromException = compilerExceptionFromException frontendExceptionToException :: Exception e => e -> SomeException frontendExceptionToException = toException . SomeFrontendException frontendExceptionFromException :: Exception e => SomeException -> Maybe e frontendExceptionFromException x = do SomeFrontendException a <- fromException x cast a --------------------------------------------------------------------- -- Make an exception type for a particular frontend compiler exception data MismatchedParentheses = MismatchedParentheses deriving Show instance Exception MismatchedParentheses where toException = frontendExceptionToException fromException = frontendExceptionFromException
We can now catch a MismatchedParentheses
exception as
MismatchedParentheses
, SomeFrontendException
or
SomeCompilerException
, but not other types, e.g. IOException
:
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException)) Caught MismatchedParentheses *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: IOException)) *** Exception: MismatchedParentheses
Nothing
toException :: e -> SomeException #
fromException :: SomeException -> Maybe e #
displayException :: e -> String #
Render this exception value in a human-friendly manner.
Default implementation:
.show
Since: base-4.8.0.0