Copyright | (c) Ivan Lazar Miljenovic |
---|---|
License | 3-Clause BSD-style |
Maintainer | Ivan.Miljenovic@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data GraphvizException
- mapException :: (Exception e1, Exception e2) => (e1 -> e2) -> a -> a
- throw :: forall (r :: RuntimeRep) (a :: TYPE r) e. Exception e => e -> a
- throwIO :: Exception e => e -> IO a
- handle :: Exception e => (e -> IO a) -> IO a -> IO a
- bracket :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c
Documentation
data GraphvizException Source #
Exceptions that arise from using this library fall into four categories:
- Unable to parse provided Dot code.
- Dot code is not valid UTF-8.
- An error when trying to run an external program (e.g.
dot
). - Treating a non-custom Attribute as a custom one.
Instances
Exception GraphvizException Source # | |
Defined in Data.GraphViz.Exception | |
Show GraphvizException Source # | |
Defined in Data.GraphViz.Exception showsPrec :: Int -> GraphvizException -> ShowS # show :: GraphvizException -> String # showList :: [GraphvizException] -> ShowS # | |
Eq GraphvizException Source # | |
Defined in Data.GraphViz.Exception (==) :: GraphvizException -> GraphvizException -> Bool # (/=) :: GraphvizException -> GraphvizException -> Bool # | |
Ord GraphvizException Source # | |
Defined in Data.GraphViz.Exception compare :: GraphvizException -> GraphvizException -> Ordering # (<) :: GraphvizException -> GraphvizException -> Bool # (<=) :: GraphvizException -> GraphvizException -> Bool # (>) :: GraphvizException -> GraphvizException -> Bool # (>=) :: GraphvizException -> GraphvizException -> Bool # max :: GraphvizException -> GraphvizException -> GraphvizException # min :: GraphvizException -> GraphvizException -> GraphvizException # |
Re-exported for convenience.
mapException :: (Exception e1, Exception e2) => (e1 -> e2) -> a -> a #
This function maps one exception into another as proposed in the paper "A semantics for imprecise exceptions".
throw :: forall (r :: RuntimeRep) (a :: TYPE r) e. Exception e => e -> a #
Throw an exception. Exceptions may be thrown from purely
functional code, but may only be caught within the IO
monad.
throwIO :: Exception e => e -> IO a #
A variant of throw
that can only be used within the IO
monad.
Although throwIO
has a type that is an instance of the type of throw
, the
two functions are subtly different:
throw e `seq` x ===> throw e throwIO e `seq` x ===> x
The first example will cause the exception e
to be raised,
whereas the second one won't. In fact, throwIO
will only cause
an exception to be raised when it is used within the IO
monad.
The throwIO
variant should be used in preference to throw
to
raise an exception within the IO
monad because it guarantees
ordering with respect to other IO
operations, whereas throw
does not.
handle :: Exception e => (e -> IO a) -> IO a -> IO a #
A version of catch
with the arguments swapped around; useful in
situations where the code for the handler is shorter. For example:
do handle (\NonTermination -> exitWith (ExitFailure 1)) $ ...
:: IO a | computation to run first ("acquire resource") |
-> (a -> IO b) | computation to run last ("release resource") |
-> (a -> IO c) | computation to run in-between |
-> IO c |
When you want to acquire a resource, do some work with it, and
then release the resource, it is a good idea to use bracket
,
because bracket
will install the necessary exception handler to
release the resource in the event that an exception is raised
during the computation. If an exception is raised, then bracket
will
re-raise the exception (after performing the release).
A common example is opening a file:
bracket (openFile "filename" ReadMode) (hClose) (\fileHandle -> do { ... })
The arguments to bracket
are in this order so that we can partially apply
it, e.g.:
withFile name mode = bracket (openFile name mode) hClose
Bracket wraps the release action with mask
, which is sufficient to ensure
that the release action executes to completion when it does not invoke any
interruptible actions, even in the presence of asynchronous exceptions. For
example, hClose
is uninterruptible when it is not racing other uses of the
handle. Similarly, closing a socket (from "network" package) is also
uninterruptible under similar conditions. An example of an interruptible
action is killThread
. Completion of interruptible release actions can be
ensured by wrapping them in in uninterruptibleMask_
, but this risks making
the program non-responsive to Control-C
, or timeouts. Another option is to
run the release action asynchronously in its own thread:
void $ uninterruptibleMask_ $ forkIO $ do { ... }
The resource will be released as soon as possible, but the thread that invoked bracket will not block in an uninterruptible state.