| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
CheckedIO.Exception
Synopsis
- class (Typeable e, Show e) => Exception e where
- toException :: e -> SomeException
- fromException :: SomeException -> Maybe e
- displayException :: e -> String
- mapExceptionM :: forall e1 e2 m1 m2 a. (MonadCatchIO e1 m1, MonadRunAsIOE e2 m2) => (e1 -> e2) -> m1 a -> m2 a
- liftE :: forall e m1 m2 a. (MonadCatchIO e m1, MonadRunAsIO m2) => m1 a -> m2 a
- throw :: MonadRunIOE e m => e -> m a
- catch :: forall e1 e2 a. (Exception e1, Exception e2) => IOE e1 a -> (e1 -> IOE e2 a) -> IOE e2 a
- try :: forall e1 e2 a. (Exception e1, Exception e2) => IOE e1 a -> IOE e2 (Either e1 a)
- throwTo :: (Exception e, MonadRunIOE e' m) => ThreadId -> e -> m ()
- throwImprecise :: Exception e => e -> a
- class (Exception e1, Exception e2) => ConvertException e1 e2 where
- convertException :: e1 -> e2
- convertE :: ConvertException e1 e2 => IOE e1 a -> IOE e2 a
- data AnyException e
- data SomeSyncException = forall e.Exception e => SomeSyncException e
- data SomeException = Exception e => SomeException e
- data SomeAsyncException = Exception e => SomeAsyncException e
Documentation
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 MyExceptionThe 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 = frontendExceptionFromExceptionWe 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
Minimal complete definition
Nothing
Methods
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
Instances
mapExceptionM :: forall e1 e2 m1 m2 a. (MonadCatchIO e1 m1, MonadRunAsIOE e2 m2) => (e1 -> e2) -> m1 a -> m2 a Source #
liftE :: forall e m1 m2 a. (MonadCatchIO e m1, MonadRunAsIO m2) => m1 a -> m2 a Source #
Lift an exception to SomeSyncException, useful for converting to IO.
liftE = mapExceptionM SomeSyncException
Example
foo :: String -> IOE MyException Int bar :: IO Int bar = liftE $ foo "hello world"
Synchronous exceptions
throw :: MonadRunIOE e m => e -> m a Source #
Throw the given exception.
catch :: forall e1 e2 a. (Exception e1, Exception e2) => IOE e1 a -> (e1 -> IOE e2 a) -> IOE e2 a Source #
Handle the exception tracked in IOE if one is thrown.
try :: forall e1 e2 a. (Exception e1, Exception e2) => IOE e1 a -> IOE e2 (Either e1 a) Source #
Get an Either containing either the result or the exception thrown.
Asynchronous exceptions
throwTo :: (Exception e, MonadRunIOE e' m) => ThreadId -> e -> m () Source #
Throw the given exception as an asynchronous exception to the given thread.
Imprecise exceptions
throwImprecise :: Exception e => e -> a Source #
Throw an imprecise exception in a pure context.
Warning: Because the exception isn't tracked at the type level, this
should be reserved for unrecoverable errors that aren't expected to be
handled. Also, if this value is not evaluated before uncheckIOE is
called, it'll remain wrapped in AnyException.
Converting exceptions
class (Exception e1, Exception e2) => ConvertException e1 e2 where Source #
A type class for converting one exception type to another.
Methods
convertException :: e1 -> e2 Source #
Instances
| Exception e => ConvertException e e Source # | |
Defined in CheckedIO.Exception Methods convertException :: e -> e Source # | |
Exception supertypes
data AnyException e Source #
All exceptions floating around IOE (synchronous
or otherwise) will be an AnyException SomeException.
Instances
| Functor AnyException Source # | |
Defined in CheckedIO.Core Methods fmap :: (a -> b) -> AnyException a -> AnyException b # (<$) :: a -> AnyException b -> AnyException a # | |
| Exception (AnyException SomeException) Source # | |
Defined in CheckedIO.Core Methods toException :: AnyException SomeException -> SomeException # fromException :: SomeException -> Maybe (AnyException SomeException) # | |
| Show e => Show (AnyException e) Source # | |
Defined in CheckedIO.Core Methods showsPrec :: Int -> AnyException e -> ShowS # show :: AnyException e -> String # showList :: [AnyException e] -> ShowS # | |
data SomeSyncException Source #
Constructors
| forall e.Exception e => SomeSyncException e |
Instances
| Exception SomeSyncException Source # | |
Defined in CheckedIO.Core Methods toException :: SomeSyncException -> SomeException # | |
| Show SomeSyncException Source # | |
Defined in CheckedIO.Core Methods showsPrec :: Int -> SomeSyncException -> ShowS # show :: SomeSyncException -> String # showList :: [SomeSyncException] -> ShowS # | |
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.
Constructors
| Exception e => SomeException e |
Instances
| Exception SomeException | Since: base-3.0 |
Defined in GHC.Exception.Type Methods toException :: SomeException -> SomeException # fromException :: SomeException -> Maybe SomeException # displayException :: SomeException -> String # | |
| Show SomeException | Since: base-3.0 |
Defined in GHC.Exception.Type Methods showsPrec :: Int -> SomeException -> ShowS # show :: SomeException -> String # showList :: [SomeException] -> ShowS # | |
| Exception (AnyException SomeException) Source # | |
Defined in CheckedIO.Core Methods toException :: AnyException SomeException -> SomeException # fromException :: SomeException -> Maybe (AnyException SomeException) # | |
data SomeAsyncException #
Superclass for asynchronous exceptions.
Since: base-4.7.0.0
Constructors
| Exception e => SomeAsyncException e |
Instances
| Exception SomeAsyncException | Since: base-4.7.0.0 |
Defined in GHC.IO.Exception Methods toException :: SomeAsyncException -> SomeException # fromException :: SomeException -> Maybe SomeAsyncException # | |
| Show SomeAsyncException | Since: base-4.7.0.0 |
Defined in GHC.IO.Exception Methods showsPrec :: Int -> SomeAsyncException -> ShowS # show :: SomeAsyncException -> String # showList :: [SomeAsyncException] -> ShowS # | |