| Safe Haskell | Safe-Inferred | 
|---|
Pipes.Safe
Contents
Description
This module provides an orphan MonadCatch instance for Proxy of the
    form:
instance (MonadCatch m, MonadIO m) => MonadCatch (Proxy a' a b' b m) where
... so you can throw and catch exceptions within pipes using all
    MonadCatch operations.
This module also provides generalized versions of some MonadCatch
    operations so that you can also protect against premature termination of
    connected components.  For example, if you protect a readFile computation
    using bracket from this module:
 -- readFile.hs
 import Pipes
 import qualified Pipes.Prelude as P
 import Pipes.Safe
 import qualified System.IO as IO
 import Prelude hiding (readFile)
 readFile :: FilePath -> Producer' String (SafeT IO) ()
 readFile file = bracket
     (do h <- IO.openFile file IO.ReadMode
         putStrLn $ "{" ++ file ++ " open}"
         return h )
     (\h -> do
         IO.hClose h
         putStrLn $ "{" ++ file ++ " closed}" )
     P.fromHandle
... then this generalized bracket will guard against both exceptions and
    premature termination of other pipes:
>>>runSafeT $ runEffect $ readFile "readFile.hs" >-> P.take 4 >-> P.stdoutLn{readFile.hs open} -- readFile.hs import Pipes import qualified Pipes.Prelude as P import Pipes.Safe {readFile.hs closed}
Note that the MonadCatch instance for Proxy provides weaker versions of
    mask and uninterruptibleMask that do not completely prevent asynchronous
    exceptions.  Instead, they provide a weaker guarantee that asynchronous
    exceptions will only occur during awaits or yields and
    nowhere else.  For example, if you write:
 mask_ $ do
     x <- await
     lift $ print x
     lift $ print x
... then you may receive an asynchronous exception during the await,
    but you will not receive an asynchronous exception during or in between the
    two print statements.  This weaker guarantee suffices to provide
    asynchronous exception safety.
- data SafeT m r
- runSafeT :: (MonadCatch m, MonadIO m) => SafeT m r -> m r
- runSafeP :: (MonadCatch m, MonadIO m) => Effect (SafeT m) r -> Effect' m r
- data ReleaseKey
- class (MonadCatch m, MonadIO m, MonadIO (Base m)) => MonadSafe m  where- type Base m :: * -> *
- liftBase :: Base m r -> m r
- register :: Base m () -> m ReleaseKey
- release :: ReleaseKey -> m ()
 
- onException :: MonadSafe m => m a -> Base m b -> m a
- finally :: MonadSafe m => m a -> Base m b -> m a
- bracket :: MonadSafe m => Base m a -> (a -> Base m b) -> (a -> m c) -> m c
- bracket_ :: MonadSafe m => Base m a -> Base m b -> m c -> m c
- bracketOnError :: MonadSafe m => Base m a -> (a -> Base m b) -> (a -> m c) -> m c
- module Control.Monad.Catch
- module Control.Exception
SafeT
SafeT is a monad transformer that extends the base monad with the ability
    to register and release finalizers.
All unreleased finalizers are called at the end of the SafeT block, even
    in the event of exceptions.
Instances
| MonadTrans SafeT | |
| Monad m => Monad (SafeT m) | |
| Monad m => Functor (SafeT m) | |
| Monad m => Applicative (SafeT m) | |
| MonadCatch m => MonadCatch (SafeT m) | |
| MonadIO m => MonadIO (SafeT m) | |
| (MonadIO m, MonadCatch m) => MonadSafe (SafeT m) | 
runSafeT :: (MonadCatch m, MonadIO m) => SafeT m r -> m rSource
Run the SafeT monad transformer, executing all unreleased finalizers at
    the end of the computation
MonadSafe
data ReleaseKey Source
class (MonadCatch m, MonadIO m, MonadIO (Base m)) => MonadSafe m whereSource
Associated Types
The monad used to run resource management actions, corresponding to the
        monad directly beneath SafeT
Methods
liftBase :: Base m r -> m rSource
Lift an action from the Base monad
register :: Base m () -> m ReleaseKeySource
register a finalizer, ensuring that the finalizer gets called if the
        finalizer is not released before the end of the surrounding SafeT
        block.
release :: ReleaseKey -> m ()Source
release a registered finalizer
You can safely call release more than once on the same ReleaseKey.
        Every release after the first one does nothing.
Instances
| MonadSafe m => MonadSafe (CatchT m) | |
| MonadSafe m => MonadSafe (IdentityT m) | |
| (MonadIO m, MonadCatch m) => MonadSafe (SafeT m) | |
| MonadSafe m => MonadSafe (ReaderT i m) | |
| MonadSafe m => MonadSafe (StateT s m) | |
| MonadSafe m => MonadSafe (StateT s m) | |
| (MonadSafe m, Monoid w) => MonadSafe (WriterT w m) | |
| (MonadSafe m, Monoid w) => MonadSafe (WriterT w m) | |
| (MonadSafe m, Monoid w) => MonadSafe (RWST i w s m) | |
| (MonadSafe m, Monoid w) => MonadSafe (RWST i w s m) | |
| MonadSafe m => MonadSafe (Proxy a' a b' b m) | 
Utilities
These utilities let you supply a finalizer that runs in the Base monad
    (i.e. the monad directly beneath SafeT).  If you don't need to use the
    full power of the Base monad and you only need to use to use IO, then
    just wrap the finalizer in liftIO, like this:
myAction `finally` (liftIO myFinalizer)
This will lead to a simple inferred type with a single MonadSafe
    constraint:
(MonadSafe m) => ...
For examples of this, see the utilities in Pipes.Safe.Prelude.
If you omit the liftIO, the compiler will infer the following constraint
    instead:
(MonadSafe m, Base m ~ IO) => ...
This means that this function would require IO directly beneath the
    SafeT monad transformer, which might not be what you want.
onException :: MonadSafe m => m a -> Base m b -> m aSource
Analogous to onException from Control.Monad.Catch, except this also
    protects against premature termination
(`onException` io) is a monad morphism.
finally :: MonadSafe m => m a -> Base m b -> m aSource
Analogous to finally from Control.Monad.Catch, except this also
    protects against premature termination
bracket :: MonadSafe m => Base m a -> (a -> Base m b) -> (a -> m c) -> m cSource
Analogous to bracket from Control.Monad.Catch, except this also
    protects against premature termination
bracket_ :: MonadSafe m => Base m a -> Base m b -> m c -> m cSource
Analogous to bracket_ from Control.Monad.Catch, except this also
    protects against premature termination
bracketOnError :: MonadSafe m => Base m a -> (a -> Base m b) -> (a -> m c) -> m cSource
Analogous to bracketOnError from Control.Monad.Catch, except this also
    protects against premature termination
Re-exports
Control.Monad.Catch re-exports all functions except for the ones that
    conflict with the generalized versions provided here (i.e. bracket,
    finally, etc.).
Control.Exception re-exports Exception and SomeException.
module Control.Monad.Catch
module Control.Exception