Copyright | (c) 2020 Composewell Technologies and Contributors |
---|---|
License | BSD-3-Clause |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- gbracket_ :: Monad m => m c -> (c -> m d) -> (c -> e -> Stream m b -> Stream m b) -> (forall s. m s -> m (Either e s)) -> (c -> Stream m b) -> Stream m b
- gbracket :: MonadIO m => IO c -> (c -> IO d1) -> (c -> e -> Stream m b -> IO (Stream m b)) -> (c -> IO d2) -> (forall s. m s -> m (Either e s)) -> (c -> Stream m b) -> Stream m b
- before :: Monad m => m b -> Stream m a -> Stream m a
- afterUnsafe :: Monad m => m b -> Stream m a -> Stream m a
- afterIO :: MonadIO m => IO b -> Stream m a -> Stream m a
- bracketUnsafe :: MonadCatch m => m b -> (b -> m c) -> (b -> Stream m a) -> Stream m a
- bracketIO3 :: (MonadIO m, MonadCatch m) => IO b -> (b -> IO c) -> (b -> IO d) -> (b -> IO e) -> (b -> Stream m a) -> Stream m a
- bracketIO :: (MonadIO m, MonadCatch m) => IO b -> (b -> IO c) -> (b -> Stream m a) -> Stream m a
- onException :: MonadCatch m => m b -> Stream m a -> Stream m a
- finallyUnsafe :: MonadCatch m => m b -> Stream m a -> Stream m a
- finallyIO :: (MonadIO m, MonadCatch m) => IO b -> Stream m a -> Stream m a
- ghandle :: (MonadCatch m, Exception e) => (e -> Stream m a -> Stream m a) -> Stream m a -> Stream m a
- handle :: (MonadCatch m, Exception e) => (e -> Stream m a) -> Stream m a -> Stream m a
Documentation
:: Monad m | |
=> m c | before |
-> (c -> m d) | after, on normal stop |
-> (c -> e -> Stream m b -> Stream m b) | on exception |
-> (forall s. m s -> m (Either e s)) | try (exception handling) |
-> (c -> Stream m b) | stream generator |
-> Stream m b |
Like gbracket
but with following differences:
- alloc action
m c
runs with async exceptions enabled - cleanup action
c -> m d
won't run if the stream is garbage collected after partial evaluation.
Inhibits stream fusion
Pre-release
:: MonadIO m | |
=> IO c | before |
-> (c -> IO d1) | on normal stop |
-> (c -> e -> Stream m b -> IO (Stream m b)) | on exception |
-> (c -> IO d2) | on GC without normal stop or exception |
-> (forall s. m s -> m (Either e s)) | try (exception handling) |
-> (c -> Stream m b) | stream generator |
-> Stream m b |
Run the alloc action m c
with async exceptions disabled but keeping
blocking operations interruptible (see mask
). Use the
output c
as input to c -> Stream m b
to generate an output stream. When
generating the stream use the supplied try
operation forall s. m s -> m
(Either e s)
to catch synchronous exceptions. If an exception occurs run
the exception handler c -> e -> Stream m b -> m (Stream m b)
. Note that
gbracket
does not rethrow the exception, it has to be done by the
exception handler if desired.
The cleanup action c -> m d
, runs whenever the stream ends normally, due
to a sync or async exception or if it gets garbage collected after a partial
lazy evaluation. See bracket
for the semantics of the cleanup action.
gbracket
can express all other exception handling combinators.
Inhibits stream fusion
Pre-release
before :: Monad m => m b -> Stream m a -> Stream m a Source #
Run the action m b
before the stream yields its first element.
Same as the following but more efficient due to fusion:
>>>
before action xs = Stream.nilM action <> xs
>>>
before action xs = Stream.concatMap (const xs) (Stream.fromEffect action)
afterUnsafe :: Monad m => m b -> Stream m a -> Stream m a Source #
Like after
, with following differences:
- action
m b
won't run if the stream is garbage collected after partial evaluation. - Monad
m
does not require any other constraints. - has slightly better performance than
after
.
Same as the following, but with stream fusion:
>>>
afterUnsafe action xs = xs <> Stream.nilM action
Pre-release
afterIO :: MonadIO m => IO b -> Stream m a -> Stream m a Source #
Run the action IO b
whenever the stream is evaluated to completion, or
if it is garbage collected after a partial lazy evaluation.
The semantics of the action IO b
are similar to the semantics of cleanup
action in bracketIO
.
See also afterUnsafe
bracketUnsafe :: MonadCatch m => m b -> (b -> m c) -> (b -> Stream m a) -> Stream m a Source #
Like bracket
but with following differences:
- alloc action
m b
runs with async exceptions enabled - cleanup action
b -> m c
won't run if the stream is garbage collected after partial evaluation. - has slightly better performance than
bracketIO
.
Inhibits stream fusion
Pre-release
bracketIO3 :: (MonadIO m, MonadCatch m) => IO b -> (b -> IO c) -> (b -> IO d) -> (b -> IO e) -> (b -> Stream m a) -> Stream m a Source #
Like bracketIO
but can use 3 separate cleanup actions depending on the
mode of termination:
- When the stream stops normally
- When the stream is garbage collected
- When the stream encounters an exception
bracketIO3 before onStop onGC onException action
runs action
using the
result of before
. If the stream stops, onStop
action is executed, if the
stream is abandoned onGC
is executed, if the stream encounters an
exception onException
is executed.
Inhibits stream fusion
Pre-release
bracketIO :: (MonadIO m, MonadCatch m) => IO b -> (b -> IO c) -> (b -> Stream m a) -> Stream m a Source #
Run the alloc action IO b
with async exceptions disabled but keeping
blocking operations interruptible (see mask
). Use the
output b
as input to b -> Stream m a
to generate an output stream.
b
is usually a resource under the IO monad, e.g. a file handle, that
requires a cleanup after use. The cleanup action b -> IO c
, runs whenever
the stream ends normally, due to a sync or async exception or if it gets
garbage collected after a partial lazy evaluation.
bracketIO
only guarantees that the cleanup action runs, and it runs with
async exceptions enabled. The action must ensure that it can successfully
cleanup the resource in the face of sync or async exceptions.
When the stream ends normally or on a sync exception, cleanup action runs immediately in the current thread context, whereas in other cases it runs in the GC context, therefore, cleanup may be delayed until the GC gets to run.
See also: bracketUnsafe
Inhibits stream fusion
onException :: MonadCatch m => m b -> Stream m a -> Stream m a Source #
Run the action m b
if the stream evaluation is aborted due to an
exception. The exception is not caught, simply rethrown.
Inhibits stream fusion
finallyUnsafe :: MonadCatch m => m b -> Stream m a -> Stream m a Source #
Like finally
with following differences:
- action
m b
won't run if the stream is garbage collected after partial evaluation. - has slightly better performance than
finallyIO
.
Inhibits stream fusion
Pre-release
finallyIO :: (MonadIO m, MonadCatch m) => IO b -> Stream m a -> Stream m a Source #
Run the action IO b
whenever the stream stream stops normally, aborts
due to an exception or if it is garbage collected after a partial lazy
evaluation.
The semantics of running the action IO b
are similar to the cleanup action
semantics described in bracketIO
.
>>>
finallyIO release = Stream.bracketIO (return ()) (const release)
See also finallyUnsafe
Inhibits stream fusion
ghandle :: (MonadCatch m, Exception e) => (e -> Stream m a -> Stream m a) -> Stream m a -> Stream m a Source #
Like handle
but the exception handler is also provided with the stream
that generated the exception as input. The exception handler can thus
re-evaluate the stream to retry the action that failed. The exception
handler can again call ghandle
on it to retry the action multiple times.
This is highly experimental. In a stream of actions we can map the stream with a retry combinator to retry each action on failure.
Inhibits stream fusion
Pre-release