Copyright | (c) 2019 Composewell Technologies |
---|---|
License | BSD-3-Clause |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- before :: (IsStream t, Monad m) => m b -> t m a -> t m a
- after_ :: (IsStream t, Monad m) => m b -> t m a -> t m a
- after :: (IsStream t, MonadIO m, MonadBaseControl IO m) => m b -> t m a -> t m a
- bracket_ :: (IsStream t, MonadCatch m) => m b -> (b -> m c) -> (b -> t m a) -> t m a
- bracket :: (IsStream t, MonadAsync m, MonadCatch m) => m b -> (b -> m c) -> (b -> t m a) -> t m a
- bracket' :: (IsStream t, MonadAsync m, MonadCatch m) => m b -> (b -> m c) -> (b -> m d) -> (b -> m e) -> (b -> t m a) -> t m a
- onException :: (IsStream t, MonadCatch m) => m b -> t m a -> t m a
- finally_ :: (IsStream t, MonadCatch m) => m b -> t m a -> t m a
- finally :: (IsStream t, MonadAsync m, MonadCatch m) => m b -> t m a -> t m a
- ghandle :: (IsStream t, MonadCatch m, Exception e) => (e -> t m a -> t m a) -> t m a -> t m a
- handle :: (IsStream t, MonadCatch m, Exception e) => (e -> t m a) -> t m a -> t m a
- retry :: (IsStream t, MonadCatch m, Exception e, Ord e) => Map e Int -> (e -> t m a) -> t m a -> t m a
Documentation
before :: (IsStream t, Monad m) => m b -> t m a -> t 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)
Since: 0.7.0
after_ :: (IsStream t, Monad m) => m b -> t m a -> t 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:
after_ action xs = xs <> 'nilM' action
Pre-release
bracket_ :: (IsStream t, MonadCatch m) => m b -> (b -> m c) -> (b -> t m a) -> t 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. - does not require a
MonadAsync
constraint. - has slightly better performance than
bracket
.
Inhibits stream fusion
Pre-release
bracket :: (IsStream t, MonadAsync m, MonadCatch m) => m b -> (b -> m c) -> (b -> t m a) -> t m a Source #
Run the alloc action m b
with async exceptions disabled but keeping
blocking operations interruptible (see mask
). Use the
output b
as input to b -> t m a
to generate an output stream.
b
is usually a resource under the state of monad m
, e.g. a file
handle, that requires a cleanup after use. The cleanup action b -> m 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.
bracket
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: bracket_
Inhibits stream fusion
Since: 0.7.0
bracket' :: (IsStream t, MonadAsync m, MonadCatch m) => m b -> (b -> m c) -> (b -> m d) -> (b -> m e) -> (b -> t m a) -> t m a Source #
Like bracket
but can use separate cleanup actions depending on the mode
of termination. bracket' 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.
Pre-release
onException :: (IsStream t, MonadCatch m) => m b -> t m a -> t m a Source #
Run the action m b
if the stream aborts due to an exception. The
exception is not caught, simply rethrown.
Inhibits stream fusion
Since: 0.7.0
finally_ :: (IsStream t, MonadCatch m) => m b -> t m a -> t m a Source #
Like finally
with following differences:
- action
m b
won't run if the stream is garbage collected after partial evaluation. - does not require a
MonadAsync
constraint. - has slightly better performance than
finally
.
Inhibits stream fusion
Pre-release
finally :: (IsStream t, MonadAsync m, MonadCatch m) => m b -> t m a -> t m a Source #
Run the action m b
whenever the stream t m a
stops normally, aborts
due to an exception or if it is garbage collected after a partial lazy
evaluation.
The semantics of running the action m b
are similar to the cleanup action
semantics described in bracket
.
finally release = bracket (return ()) (const release)
See also finally_
Inhibits stream fusion
Since: 0.7.0
ghandle :: (IsStream t, MonadCatch m, Exception e) => (e -> t m a -> t m a) -> t m a -> t 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
handle :: (IsStream t, MonadCatch m, Exception e) => (e -> t m a) -> t m a -> t m a Source #
When evaluating a stream if an exception occurs, stream evaluation aborts and the specified exception handler is run with the exception as argument.
Inhibits stream fusion
Since: 0.7.0
:: (IsStream t, MonadCatch m, Exception e, Ord e) | |
=> Map e Int | map from exception to retry count |
-> (e -> t m a) | default handler for those exceptions that are not in the map |
-> t m a | |
-> t m a |
retry
takes 3 arguments
- A map
m
whose keys are exceptions and values are the number of times to retry the action given that the exception occurs. - A handler
han
that decides how to handle an exception when the exception cannot be retried. - The stream itself that we want to run this mechanism on.
When evaluating a stream if an exception occurs,
- The stream evaluation aborts
- The exception is looked up in
m
a. If the exception exists and the mapped value is > 0 then,
i. The value is decreased by 1.
ii. The stream is resumed from where the exception was called, retrying the action.
b. If the exception exists and the mapped value is == 0 then the stream evaluation stops.
c. If the exception does not exist then we handle the exception using
han
.
Internal