pipes-safe-2.2.5: Safety for the pipes ecosystem

Safe HaskellTrustworthy
LanguageHaskell98

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.

Synopsis

SafeT

data SafeT m r Source #

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 Source # 

Methods

lift :: Monad m => m a -> SafeT m a #

MonadBase b m => MonadBase b (SafeT m) Source # 

Methods

liftBase :: b α -> SafeT m α #

MonadBaseControl b m => MonadBaseControl b (SafeT m) Source # 

Associated Types

type StM (SafeT m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (SafeT m) b -> b a) -> SafeT m a #

restoreM :: StM (SafeT m) a -> SafeT m a #

MonadError e m => MonadError e (SafeT m) Source # 

Methods

throwError :: e -> SafeT m a #

catchError :: SafeT m a -> (e -> SafeT m a) -> SafeT m a #

MonadState s m => MonadState s (SafeT m) Source # 

Methods

get :: SafeT m s #

put :: s -> SafeT m () #

state :: (s -> (a, s)) -> SafeT m a #

MonadWriter w m => MonadWriter w (SafeT m) Source # 

Methods

writer :: (a, w) -> SafeT m a #

tell :: w -> SafeT m () #

listen :: SafeT m a -> SafeT m (a, w) #

pass :: SafeT m (a, w -> w) -> SafeT m a #

Monad m => Monad (SafeT m) Source # 

Methods

(>>=) :: SafeT m a -> (a -> SafeT m b) -> SafeT m b #

(>>) :: SafeT m a -> SafeT m b -> SafeT m b #

return :: a -> SafeT m a #

fail :: String -> SafeT m a #

Functor m => Functor (SafeT m) Source # 

Methods

fmap :: (a -> b) -> SafeT m a -> SafeT m b #

(<$) :: a -> SafeT m b -> SafeT m a #

MonadFix m => MonadFix (SafeT m) Source # 

Methods

mfix :: (a -> SafeT m a) -> SafeT m a #

Applicative m => Applicative (SafeT m) Source # 

Methods

pure :: a -> SafeT m a #

(<*>) :: SafeT m (a -> b) -> SafeT m a -> SafeT m b #

(*>) :: SafeT m a -> SafeT m b -> SafeT m b #

(<*) :: SafeT m a -> SafeT m b -> SafeT m a #

MonadIO m => MonadIO (SafeT m) Source # 

Methods

liftIO :: IO a -> SafeT m a #

Alternative m => Alternative (SafeT m) Source # 

Methods

empty :: SafeT m a #

(<|>) :: SafeT m a -> SafeT m a -> SafeT m a #

some :: SafeT m a -> SafeT m [a] #

many :: SafeT m a -> SafeT m [a] #

MonadPlus m => MonadPlus (SafeT m) Source # 

Methods

mzero :: SafeT m a #

mplus :: SafeT m a -> SafeT m a -> SafeT m a #

MonadThrow m => MonadThrow (SafeT m) Source # 

Methods

throwM :: Exception e => e -> SafeT m a #

MonadCatch m => MonadCatch (SafeT m) Source # 

Methods

catch :: Exception e => SafeT m a -> (e -> SafeT m a) -> SafeT m a #

MonadMask m => MonadMask (SafeT m) Source # 

Methods

mask :: ((forall a. SafeT m a -> SafeT m a) -> SafeT m b) -> SafeT m b #

uninterruptibleMask :: ((forall a. SafeT m a -> SafeT m a) -> SafeT m b) -> SafeT m b #

MonadCont m => MonadCont (SafeT m) Source # 

Methods

callCC :: ((a -> SafeT m b) -> SafeT m a) -> SafeT m a #

(MonadIO m, MonadCatch m, MonadMask m) => MonadSafe (SafeT m) Source # 

Associated Types

type Base (SafeT m :: * -> *) :: * -> * Source #

type Base (SafeT m) Source # 
type Base (SafeT m) = m
type StM (SafeT m) a Source # 
type StM (SafeT m) a = StM m a

runSafeT :: (MonadMask m, MonadIO m) => SafeT m r -> m r Source #

Run the SafeT monad transformer, executing all unreleased finalizers at the end of the computation

runSafeP :: (MonadMask m, MonadIO m) => Effect (SafeT m) r -> Effect' m r Source #

Run SafeT in the base monad, executing all unreleased finalizers at the end of the computation

Use runSafeP to safely flush all unreleased finalizers and ensure prompt finalization without exiting the Proxy monad.

MonadSafe

data ReleaseKey Source #

Token used to release a previously registered finalizer

class (MonadCatch m, MonadMask m, MonadIO m, MonadIO (Base m)) => MonadSafe m where Source #

MonadSafe lets you register and release finalizers that execute in a Base monad

Minimal complete definition

liftBase, register, release

Associated Types

type Base (m :: * -> *) :: * -> * Source #

The monad used to run resource management actions, corresponding to the monad directly beneath SafeT

Methods

liftBase :: Base m r -> m r Source #

Lift an action from the Base monad

register :: Base m () -> m ReleaseKey Source #

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) Source # 

Associated Types

type Base (CatchT m :: * -> *) :: * -> * Source #

(MonadIO m, MonadCatch m, MonadMask m) => MonadSafe (SafeT m) Source # 

Associated Types

type Base (SafeT m :: * -> *) :: * -> * Source #

MonadSafe m => MonadSafe (StateT s m) Source # 

Associated Types

type Base (StateT s m :: * -> *) :: * -> * Source #

Methods

liftBase :: Base (StateT s m) r -> StateT s m r Source #

register :: Base (StateT s m) () -> StateT s m ReleaseKey Source #

release :: ReleaseKey -> StateT s m () Source #

MonadSafe m => MonadSafe (StateT s m) Source # 

Associated Types

type Base (StateT s m :: * -> *) :: * -> * Source #

Methods

liftBase :: Base (StateT s m) r -> StateT s m r Source #

register :: Base (StateT s m) () -> StateT s m ReleaseKey Source #

release :: ReleaseKey -> StateT s m () Source #

(MonadSafe m, Monoid w) => MonadSafe (WriterT w m) Source # 

Associated Types

type Base (WriterT w m :: * -> *) :: * -> * Source #

Methods

liftBase :: Base (WriterT w m) r -> WriterT w m r Source #

register :: Base (WriterT w m) () -> WriterT w m ReleaseKey Source #

release :: ReleaseKey -> WriterT w m () Source #

(MonadSafe m, Monoid w) => MonadSafe (WriterT w m) Source # 

Associated Types

type Base (WriterT w m :: * -> *) :: * -> * Source #

Methods

liftBase :: Base (WriterT w m) r -> WriterT w m r Source #

register :: Base (WriterT w m) () -> WriterT w m ReleaseKey Source #

release :: ReleaseKey -> WriterT w m () Source #

MonadSafe m => MonadSafe (IdentityT * m) Source # 

Associated Types

type Base (IdentityT * m :: * -> *) :: * -> * Source #

MonadSafe m => MonadSafe (ReaderT * i m) Source # 

Associated Types

type Base (ReaderT * i m :: * -> *) :: * -> * Source #

Methods

liftBase :: Base (ReaderT * i m) r -> ReaderT * i m r Source #

register :: Base (ReaderT * i m) () -> ReaderT * i m ReleaseKey Source #

release :: ReleaseKey -> ReaderT * i m () Source #

(MonadSafe m, Monoid w) => MonadSafe (RWST i w s m) Source # 

Associated Types

type Base (RWST i w s m :: * -> *) :: * -> * Source #

Methods

liftBase :: Base (RWST i w s m) r -> RWST i w s m r Source #

register :: Base (RWST i w s m) () -> RWST i w s m ReleaseKey Source #

release :: ReleaseKey -> RWST i w s m () Source #

(MonadSafe m, Monoid w) => MonadSafe (RWST i w s m) Source # 

Associated Types

type Base (RWST i w s m :: * -> *) :: * -> * Source #

Methods

liftBase :: Base (RWST i w s m) r -> RWST i w s m r Source #

register :: Base (RWST i w s m) () -> RWST i w s m ReleaseKey Source #

release :: ReleaseKey -> RWST i w s m () Source #

MonadSafe m => MonadSafe (Proxy a' a b' b m) Source # 

Associated Types

type Base (Proxy a' a b' b m :: * -> *) :: * -> * Source #

Methods

liftBase :: Base (Proxy a' a b' b m) r -> Proxy a' a b' b m r Source #

register :: Base (Proxy a' a b' b m) () -> Proxy a' a b' b m ReleaseKey Source #

release :: ReleaseKey -> Proxy a' a b' b m () Source #

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 a Source #

Analogous to onException from Control.Monad.Catch, except this also protects against premature termination

(`onException` io) is a monad morphism.

tryP :: (MonadSafe m, Exception e) => Proxy a' a b' b m r -> Proxy a' a b' b m (Either e r) Source #

Transform a Proxy into one that catches any exceptions caused by its effects, and returns the resulting exception.

catchP :: (MonadSafe m, Exception e) => Proxy a' a b' b m r -> (e -> Proxy a' a b' b m r) -> Proxy a' a b' b m r Source #

Allows direct handling of exceptions raised by the effects in a Proxy.

finally :: MonadSafe m => m a -> Base m b -> m a Source #

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 c Source #

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 c Source #

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 c Source #

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.

Orphan instances

(MonadMask m, MonadIO m) => MonadMask (Proxy a' a b' b m) Source # 

Methods

mask :: ((forall c. Proxy a' a b' b m c -> Proxy a' a b' b m c) -> Proxy a' a b' b m b) -> Proxy a' a b' b m b #

uninterruptibleMask :: ((forall c. Proxy a' a b' b m c -> Proxy a' a b' b m c) -> Proxy a' a b' b m b) -> Proxy a' a b' b m b #