| Safe Haskell | Safe-Inferred |
|---|
Control.Proxy.Safe.Core
Description
Exception handling and resource management integrated with proxies
- module Control.Proxy.Trans.Either
- module Control.Exception
- type ExceptionP = EitherP SomeException
- throw :: (Monad m, Proxy p, Exception e) => e -> ExceptionP p a' a b' b m r
- catch :: (Exception e, Monad m, Proxy p) => ExceptionP p a' a b' b m r -> (e -> ExceptionP p a' a b' b m r) -> ExceptionP p a' a b' b m r
- handle :: (Exception e, Monad m, Proxy p) => (e -> ExceptionP p a' a b' b m r) -> ExceptionP p a' a b' b m r -> ExceptionP p a' a b' b m r
- data SafeIO r
- runSafeIO :: SafeIO (Either SomeException r) -> IO r
- runSaferIO :: SafeIO (Either SomeException r) -> IO r
- trySafeIO :: SafeIO e -> IO e
- trySaferIO :: SafeIO e -> IO e
- class Proxy p => CheckP p where
- try :: p a' a b' b IO r -> ExceptionP p a' a b' b SafeIO r
- tryIO :: Proxy p => IO r -> ExceptionP p a' a b' b SafeIO r
- onAbort :: (Monad m, Proxy p) => (forall x. SafeIO x -> m x) -> IO r' -> ExceptionP p a' a b' b m r -> ExceptionP p a' a b' b m r
- finally :: (Monad m, Proxy p) => (forall x. SafeIO x -> m x) -> IO r' -> ExceptionP p a' a b' b m r -> ExceptionP p a' a b' b m r
- bracket :: (Monad m, Proxy p) => (forall x. SafeIO x -> m x) -> IO h -> (h -> IO r') -> (h -> ExceptionP p a' a b' b m r) -> ExceptionP p a' a b' b m r
- bracket_ :: (Monad m, Proxy p) => (forall x. SafeIO x -> m x) -> IO r1 -> IO r2 -> ExceptionP p a' a b' b m r -> ExceptionP p a' a b' b m r
- bracketOnAbort :: (Monad m, Proxy p) => (forall x. SafeIO x -> m x) -> IO h -> (h -> IO r') -> (h -> ExceptionP p a' a b' b m r) -> ExceptionP p a' a b' b m r
- unsafeCloseU :: Proxy p => r -> ExceptionP p a' a b' b SafeIO r
- unsafeCloseD :: Proxy p => r -> ExceptionP p a' a b' b SafeIO r
- unsafeClose :: Proxy p => r -> ExceptionP p a' a b' b SafeIO r
- tryK :: CheckP p => (q -> p a' a b' b IO r) -> q -> ExceptionP p a' a b' b SafeIO r
Exception Handling
This library checks and stores all exceptions using the EitherP proxy
transformer. The ExceptionP type synonym simplifies type signatures.
Use runEitherP / runEitherK from the re-exported
Control.Proxy.Trans.Either to convert ExceptionP back to the base monad.
This module does not re-export throw, catch, and handle from
Control.Proxy.Trans.Either and instead defines new versions similar to the
API from Control.Exception. If you want the old versions you will need to
import them qualified.
This module only re-exports SomeException and Exception from
Control.Exception.
module Control.Proxy.Trans.Either
module Control.Exception
type ExceptionP = EitherP SomeExceptionSource
A proxy transformer that stores exceptions using EitherP
throw :: (Monad m, Proxy p, Exception e) => e -> ExceptionP p a' a b' b m rSource
Analogous to throwIO from Control.Exception
Arguments
| :: (Exception e, Monad m, Proxy p) | |
| => ExceptionP p a' a b' b m r | Original computation |
| -> (e -> ExceptionP p a' a b' b m r) | Handler |
| -> ExceptionP p a' a b' b m r |
Analogous to catch from Control.Exception
Arguments
| :: (Exception e, Monad m, Proxy p) | |
| => (e -> ExceptionP p a' a b' b m r) | Handler |
| -> ExceptionP p a' a b' b m r | Original computation |
| -> ExceptionP p a' a b' b m r |
Analogous to handle from Control.Exception
Safe IO
runSaferIO :: SafeIO (Either SomeException r) -> IO rSource
Convert back to the IO monad, running all dropped finalizers at the very
end and rethrowing any checked exceptions
This uses uninterruptibleMask to mask asynchronous exceptions and only
unmasks them during try or tryIO.
trySaferIO :: SafeIO e -> IO eSource
Convert back to the IO monad, running all dropped finalizers at the very
end and preserving exceptions as Lefts
This uses uninterruptibleMask to mask asynchronous exceptions and only
unmasks them during try or tryIO.
Checked Exceptions
The following try functions are the only way to convert IO actions to
SafeIO. These functions check all exceptions, including asynchronous
exceptions, and store them in the ExceptionP proxy transformer.
class Proxy p => CheckP p whereSource
Use try to retroactively check all exceptions for proxies that implement
CheckP.
try is almost a proxy morphism (See Control.Proxy.Morph from pipes
for the full list of laws). The only exception is the following law:
try (return x) = return x
The left-hand side unmasks asynchronous exceptions and checks them
immediately, whereas the right-hand side delays asynchronous exceptions
until the next try or tryIO block.
Methods
try :: p a' a b' b IO r -> ExceptionP p a' a b' b SafeIO rSource
Finalization
Arguments
| :: (Monad m, Proxy p) | |
| => (forall x. SafeIO x -> m x) | Monad morphism |
| -> IO r' | Action to run on abort |
| -> ExceptionP p a' a b' b m r | Guarded computation |
| -> ExceptionP p a' a b' b m r |
Similar to onException from Control.Exception, except this also
protects against:
- premature termination, and
- exceptions in other proxy stages.
The first argument lifts onAbort to work with other base monads. Use
id if your base monad is already SafeIO.
(onAbort morph fin) is a monad morphism:
onAbort morph fin $ do x <- m = do x <- onAbort morph fin m
f x onAbort morph fin (f x)
onAbort morph fin (return x) = return x
onAbort ensures finalizers are called from inside to out:
onAbort morph fin1 . onAbort morph fin2 = onAbort morph (fin2 >> fin1) onAbort morph (return ()) = id
Arguments
| :: (Monad m, Proxy p) | |
| => (forall x. SafeIO x -> m x) | Monad morphism |
| -> IO r' | Guaranteed final action |
| -> ExceptionP p a' a b' b m r | Guarded computation |
| -> ExceptionP p a' a b' b m r |
Arguments
| :: (Monad m, Proxy p) | |
| => (forall x. SafeIO x -> m x) | Monad morphism |
| -> IO h | Acquire resource |
| -> (h -> IO r') | Release resource |
| -> (h -> ExceptionP p a' a b' b m r) | Use resource |
| -> ExceptionP p a' a b' b m r |
Analogous to bracket from Control.Exception
The first argument lifts bracket to work with other base monads. Use id
if your base monad is already SafeIO.
bracket guarantees that if the resource acquisition completes, then the
resource will be released.
bracket morph before after p = do
h <- hoist morph $ tryIO before
finally morph (after h) (p h)
Arguments
| :: (Monad m, Proxy p) | |
| => (forall x. SafeIO x -> m x) | Monad morphism |
| -> IO r1 | Acquire resource |
| -> IO r2 | Release resource |
| -> ExceptionP p a' a b' b m r | Use resource |
| -> ExceptionP p a' a b' b m r |
Arguments
| :: (Monad m, Proxy p) | |
| => (forall x. SafeIO x -> m x) | Monad morphism |
| -> IO h | Acquire resource |
| -> (h -> IO r') | Release resource |
| -> (h -> ExceptionP p a' a b' b m r) | Use resource |
| -> ExceptionP p a' a b' b m r |
Analogous to bracketOnError from Control.Exception
The first argument lifts bracketOnAbort to work with any base monad. Use
id if your base monad is already SafeIO.
bracketOnAbort morph before after p = do
h <- hoist morph $ tryIO before
onAbort morph (after h) (p h)
Prompt Finalization
This implementation will not promptly finalize a Proxy if another
composed Proxy prematurely terminates. However, the implementation will
still save the dropped finalizer and run it when the Session completes
in order to guarantee deterministic finalization.
To see why, consider the following Proxy assembly:
p1 >-> ((p2 >-> p3) >=> p4)
Now ask yourself the question, "If p3 prematurely terminates, should it
promptly finalize p1?"
If you answered "yes", then you would have a bug if p4 were to
request, which would restore control to p1 after we already finalized
it.
If you answered "no", then consider the case where p2 = idT and
p4 = return:
p1 >-> ((idT >-> p3) >=> return) p1 >-> (idT >-> p3) -- f >=> return = f p1 >-> p3 -- idT >-> p = p
Answering "no" means that p3 would be unable to promptly finalize a
Proxy immediately upstream of it.
There is a solution that permits perfectly prompt finalization, but it requires indexed monads to guarantee the necessary safety through the type system. In the absence of indexed monads, the next best solution is to let you promptly finalize things yourself, but then you must prove that this finalization is safe and that all upstream pipes are unreachable.
The following two unsafe operations allow you to trade safety for prompt finalization. Use them if you desire prompter finalization guarantees and if you can prove their usage is safe. However, this proof is not trivial.
For example, you might suppose that the following usage of unsafeCloseU is
safe because it never requests after closing upstream, nor does it
terminate:
falseSenseOfSecurity () = do
x <- request ()
unsafeCloseU ()
forever $ respond x
However, this is not safe, as the following counter-example demonstrates:
p1 >-> ((falseSenseOfSecurity >-> request) >=> request)
falseSenseOfSecurity will finalize the upstream p1, but then will
abort when the downstream request terminates, and then the second
request will illegally access p1 after we already finalized it.
In other words, you cannot prove any prompt finalization is safe unless you
control the entire Session. Therefore, do not use the following unsafe
operations in Proxy libraries. Only the end user assembling the
final Session may safely insert these calls.
unsafeCloseU :: Proxy p => r -> ExceptionP p a' a b' b SafeIO rSource
unsafeCloseU calls all finalizers registered upstream of the current
Proxy.
unsafeCloseD :: Proxy p => r -> ExceptionP p a' a b' b SafeIO rSource
unsafeCloseD calls all finalizers registered downstream of the current
Proxy.
unsafeClose :: Proxy p => r -> ExceptionP p a' a b' b SafeIO rSource
unsafeClose calls all registered finalizers
unsafeClose is a Kleisli arrow so that you can easily seal terminating
proxies if there is a risk of delayed finalization:
(producer >-> (takeB_ 10 >=> unsafeClose) >-> consumer) >=> later
Deprecated
To be removed in version 2.0.0