Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Monadic and General Iteratees: Messaging and exception handling.
Iteratees use an internal exception handling mechanism that is parallel to
that provided by Exception
. This allows the iteratee framework
to handle its own exceptions outside IO
.
Iteratee exceptions are divided into two categories, IterException
and
EnumException
. IterExceptions
are exceptions within an iteratee, and
EnumExceptions
are exceptions within an enumerator.
Enumerators can be constructed to handle an IterException
with
Data.Iteratee.Iteratee.enumFromCallbackCatch
. If the enumerator detects
an iteratee exception
, the enumerator calls the provided exception handler.
The enumerator is then able to continue feeding data to the iteratee,
provided the exception was successfully handled. If the handler could
not handle the exception, the IterException
is converted to an
EnumException
and processing aborts.
Exceptions can also be cleared by Data.Iteratee.Iteratee.checkErr
,
although in this case the iteratee continuation cannot be recovered.
When viewed as Resumable Exceptions, iteratee exceptions provide a means
for iteratees to send control messages to enumerators. The seek
implementation provides an example. Data.Iteratee.Iteratee.seek
stores
the current iteratee continuation and throws a SeekException
, which
inherits from IterException
. Data.Iteratee.IO.enumHandleRandom
is
constructed with enumFromCallbackCatch
and a handler that performs
an hSeek
. Upon receiving the SeekException
, enumHandleRandom
calls
the handler, checks that it executed properly, and then continues with
the stored continuation.
As the exception hierarchy is open, users can extend it with custom exceptions and exception handlers to implement sophisticated messaging systems based upon resumable exceptions.
Synopsis
- data IFException = Exception e => IFException e
- class (Typeable e, Show e) => Exception e where
- type FileOffset = COff
- data EnumException = Exception e => EnumException e
- data DivergentException = DivergentException
- newtype EnumStringException = EnumStringException String
- newtype EnumUnhandledIterException = EnumUnhandledIterException IterException
- class Exception e => IException e where
- data IterException = Exception e => IterException e
- newtype SeekException = SeekException FileOffset
- data EofException = EofException
- newtype IterStringException = IterStringException String
- enStrExc :: String -> EnumException
- iterStrExc :: String -> SomeException
- wrapIterExc :: IterException -> EnumException
- iterExceptionToException :: Exception e => e -> SomeException
- iterExceptionFromException :: Exception e => SomeException -> Maybe e
Exception types
data IFException Source #
Root of the Iteratee exception hierarchy. IFException
derives from
Control.Exception.SomeException
. EnumException
, IterException
,
and all inheritants are descendents of IFException
.
Exception e => IFException e |
Instances
Show IFException Source # | |
Defined in Bio.Iteratee.Exception showsPrec :: Int -> IFException -> ShowS # show :: IFException -> String # showList :: [IFException] -> ShowS # | |
Exception IFException Source # | |
Defined in Bio.Iteratee.Exception |
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
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
type FileOffset = COff #
Enumerator exceptions
data EnumException Source #
Exception e => EnumException e |
Instances
Show EnumException Source # | |
Defined in Bio.Iteratee.Exception showsPrec :: Int -> EnumException -> ShowS # show :: EnumException -> String # showList :: [EnumException] -> ShowS # | |
Exception EnumException Source # | |
Defined in Bio.Iteratee.Exception |
data DivergentException Source #
The iteratee
diverged upon receiving EOF
.
Instances
Show DivergentException Source # | |
Defined in Bio.Iteratee.Exception showsPrec :: Int -> DivergentException -> ShowS # show :: DivergentException -> String # showList :: [DivergentException] -> ShowS # | |
Exception DivergentException Source # | |
Defined in Bio.Iteratee.Exception |
newtype EnumStringException Source #
Create an enumerator exception from a String
.
Instances
Show EnumStringException Source # | |
Defined in Bio.Iteratee.Exception showsPrec :: Int -> EnumStringException -> ShowS # show :: EnumStringException -> String # showList :: [EnumStringException] -> ShowS # | |
Exception EnumStringException Source # | |
Defined in Bio.Iteratee.Exception |
newtype EnumUnhandledIterException Source #
The enumerator received an IterException
it could not handle.
Instances
Iteratee exceptions
class Exception e => IException e where Source #
A class for iteratee exceptions
. Only inheritants of IterException
should be instances of this class.
toIterException :: e -> IterException Source #
fromIterException :: IterException -> Maybe e Source #
Instances
IException IterStringException Source # | |
IException EofException Source # | |
Defined in Bio.Iteratee.Exception | |
IException SeekException Source # | |
Defined in Bio.Iteratee.Exception | |
IException IterException Source # | |
Defined in Bio.Iteratee.Exception |
data IterException Source #
Root of iteratee exceptions.
Exception e => IterException e |
Instances
Show IterException Source # | |
Defined in Bio.Iteratee.Exception showsPrec :: Int -> IterException -> ShowS # show :: IterException -> String # showList :: [IterException] -> ShowS # | |
Exception IterException Source # | |
Defined in Bio.Iteratee.Exception | |
IException IterException Source # | |
Defined in Bio.Iteratee.Exception |
newtype SeekException Source #
A seek request within an Iteratee
.
Instances
Show SeekException Source # | |
Defined in Bio.Iteratee.Exception showsPrec :: Int -> SeekException -> ShowS # show :: SeekException -> String # showList :: [SeekException] -> ShowS # | |
Exception SeekException Source # | |
Defined in Bio.Iteratee.Exception | |
IException SeekException Source # | |
Defined in Bio.Iteratee.Exception |
data EofException Source #
The Iteratee
needs more data but received EOF
.
Instances
Show EofException Source # | |
Defined in Bio.Iteratee.Exception showsPrec :: Int -> EofException -> ShowS # show :: EofException -> String # showList :: [EofException] -> ShowS # | |
Exception EofException Source # | |
Defined in Bio.Iteratee.Exception | |
IException EofException Source # | |
Defined in Bio.Iteratee.Exception |
newtype IterStringException Source #
An Iteratee exception
specified by a String
.
Instances
Show IterStringException Source # | |
Defined in Bio.Iteratee.Exception showsPrec :: Int -> IterStringException -> ShowS # show :: IterStringException -> String # showList :: [IterStringException] -> ShowS # | |
Exception IterStringException Source # | |
Defined in Bio.Iteratee.Exception | |
IException IterStringException Source # | |
Functions
enStrExc :: String -> EnumException Source #
Create an EnumException
from a string.
iterStrExc :: String -> SomeException Source #
Create an iteratee exception
from a string.
This convenience function wraps IterStringException
and toException
.
wrapIterExc :: IterException -> EnumException Source #
Convert an IterException
to an EnumException
. Meant to be used
within an Enumerator
to signify that it could not handle the
IterException
.
iterExceptionToException :: Exception e => e -> SomeException Source #
iterExceptionFromException :: Exception e => SomeException -> Maybe e Source #