Safe Haskell | Safe-Infered |
---|
- throw :: (Monad m, Exception e) => e -> Pipe a b m r
- catch :: (Monad m, Exception e) => Pipe a b m r -> (e -> Pipe a b m r) -> Pipe a b m r
- bracket :: Monad m => m r -> (r -> m y) -> (r -> Pipe a b m x) -> Pipe a b m x
- bracket_ :: Monad m => m r -> m y -> Pipe a b m x -> Pipe a b m x
- bracketOnError :: Monad m => m r -> (r -> m y) -> (r -> Pipe a b m x) -> Pipe a b m x
- finally :: Monad m => Pipe a b m r -> m s -> Pipe a b m r
- onException :: Monad m => Pipe a b m r -> Pipe a b m s -> Pipe a b m r
Documentation
throw :: (Monad m, Exception e) => e -> Pipe a b m rSource
Throw an exception within the Pipe
monad.
An exception thrown with throw
can be caught by catch
with any base
monad.
If the exception is not caught in the Pipeline
at all, it will be rethrown
as a normal Haskell exception when using runPipe
. Note that runPurePipe
returns the exception in an Either
value, instead.
:: (Monad m, Exception e) | |
=> Pipe a b m r |
|
-> (e -> Pipe a b m r) | handler function |
-> Pipe a b m r |
Catch an exception within the Pipe
monad.
This function takes a Pipe
, runs it, and if an exception is raised it
executes the handler, passing it the value of the exception. Otherwise, the
result is returned as normal.
For example, given a Pipe
:
reader :: Pipe () String IO ()
we can use catch
to resume after an exception. For example:
safeReader :: Pipe () (Either SomeException String) IO () safeReader = catch (reader >+> 'Pipe' Right) $ \e -> do yield $ Left e
Note that only the initial monadic actions contained in a handler are
guaranteed to be executed. Anything else is subject to the usual
termination rule of Pipe
s: if a Pipe
at either side terminates, the
whole pipeline terminates.
:: Monad m | |
=> m r | action to acquire resource |
-> (r -> m y) | action to release resource |
-> (r -> Pipe a b m x) |
|
-> Pipe a b m x |
Allocate a resource within the base monad, run a Pipe
, then ensure the
resource is released.
The typical example is reading from a file:
bracket (openFile "filename" ReadMode) hClose (\handle -> do line <- lift $ hGetLine handle yield line ...)
:: Monad m | |
=> m r | action to run first |
-> m y | action to run last |
-> Pipe a b m x |
|
-> Pipe a b m x |
A variant of bracket
where the return value from the allocation action
is not required.
A specialized variant of bracket
with just a computation to run
afterwards.