Copyright | Ozgun Ataman <ozgun.ataman@soostone.com> |
---|---|
License | BSD3 |
Maintainer | Ozgun Ataman |
Stability | provisional |
Safe Haskell | Safe |
Language | Haskell2010 |
This module exposes combinators that can wrap arbitrary monadic actions. They run the action and potentially retry running it with some configurable delay for a configurable number of times.
The express purpose of this library is to make it easier to work with IO and especially network IO actions that often experience temporary failure that warrant retrying of the original action. For example, a database query may time out for a while, in which case we should delay a bit and retry the query.
- newtype RetryPolicyM m = RetryPolicyM {
- getRetryPolicyM :: RetryStatus -> m (Maybe Int)
- type RetryPolicy = forall m. Monad m => RetryPolicyM m
- retryPolicy :: (RetryStatus -> Maybe Int) -> RetryPolicy
- data RetryStatus
- rsIterNumber :: RetryStatus -> Int
- rsCumulativeDelay :: RetryStatus -> Int
- rsPreviousDelay :: RetryStatus -> Maybe Int
- defaultRetryStatus :: RetryStatus
- rsIterNumberL :: Lens' RetryStatus Int
- rsCumulativeDelayL :: Lens' RetryStatus Int
- rsPreviousDelayL :: Lens' RetryStatus (Maybe Int)
- retrying :: MonadIO m => RetryPolicyM m -> (RetryStatus -> b -> m Bool) -> (RetryStatus -> m b) -> m b
- recovering :: (MonadIO m, MonadMask m) => RetryPolicyM m -> [RetryStatus -> Handler m Bool] -> (RetryStatus -> m a) -> m a
- recoverAll :: (MonadIO m, MonadMask m) => RetryPolicyM m -> (RetryStatus -> m a) -> m a
- logRetries :: (Monad m, Show e, Exception e) => (e -> m Bool) -> (Bool -> String -> m ()) -> RetryStatus -> Handler m Bool
- constantDelay :: Int -> RetryPolicy
- exponentialBackoff :: Int -> RetryPolicy
- fullJitterBackoff :: MonadIO m => Int -> RetryPolicyM m
- fibonacciBackoff :: Int -> RetryPolicy
- limitRetries :: Int -> RetryPolicy
- limitRetriesByDelay :: Int -> RetryPolicy -> RetryPolicy
- capDelay :: Monad m => Int -> RetryPolicyM m -> RetryPolicyM m
- simulatePolicy :: Monad m => Int -> RetryPolicyM m -> m [(Int, Maybe Int)]
- simulatePolicyPP :: Int -> RetryPolicyM IO -> IO ()
Types and Operations
newtype RetryPolicyM m Source
A RetryPolicyM
is a function that takes an RetryStatus
and
possibly returns a delay in microseconds. Iteration numbers start
at zero and increase by one on each retry. A *Nothing* return value from
the function implies we have reached the retry limit.
Please note that RetryPolicyM
is a Monoid
. You can collapse
multiple strategies into one using mappend
or <>
. The semantics
of this combination are as follows:
- If either policy returns
Nothing
, the combined policy returnsNothing
. This can be used toinhibit
after a number of retries, for example. - If both policies return a delay, the larger delay will be used. This is quite natural when combining multiple policies to achieve a certain effect.
Example:
One can easily define an exponential backoff policy with a limited number of retries:
> limitedBackoff = exponentialBackoff 50 <> limitRetries 5
Naturally, mempty
will retry immediately (delay 0) for an
unlimited number of retries, forming the identity for the Monoid
.
The default under def
implements a constant 50ms delay, up to 5 times:
> def = constantDelay 50000 <> limitRetries 5
For anything more complex, just define your own RetryPolicyM
:
> myPolicy = retryPolicy $ \ rs -> if rsIterNumber n > 10 then Just 1000 else Just 10000
Since 0.7.
RetryPolicyM | |
|
Monad m => Monoid (RetryPolicyM m) Source | |
Monad m => Default (RetryPolicyM m) Source |
type RetryPolicy = forall m. Monad m => RetryPolicyM m Source
Simplified RetryPolicyM
without any use of the monadic context in
determining policy. Mostly maintains backwards compatitibility with
type signatures pre-0.7.
retryPolicy :: (RetryStatus -> Maybe Int) -> RetryPolicy Source
Helper for making simplified policies that don't use the monadic context.
data RetryStatus Source
Datatype with stats about retries made thus far. The constructor is deliberately not exported to make additional fields easier to add in a backward-compatible manner. To read or modify fields in RetryStatus, use the accessors or lenses below. Note that if you don't want to use lenses, the exported field names can be used for updates:
> retryStatus { rsIterNumber = newIterNumber } > retryStatus & rsIterNumberL .~ newIterNumber
Fields for RetryStatus
rsIterNumber :: RetryStatus -> Int Source
Iteration number, where 0 is the first try
rsCumulativeDelay :: RetryStatus -> Int Source
Delay incurred so far from retries in microseconds
rsPreviousDelay :: RetryStatus -> Maybe Int Source
Previous attempt's delay. Will always be Nothing on first run.
defaultRetryStatus :: RetryStatus Source
Initial, default retry status. Exported mostly to allow user code to test their handlers and retry policies. Use fields or lenses to update.
Lenses for RetryStatus
rsIterNumberL :: Lens' RetryStatus Int Source
rsCumulativeDelayL :: Lens' RetryStatus Int Source
rsPreviousDelayL :: Lens' RetryStatus (Maybe Int) Source
Applying Retry Policies
:: MonadIO m | |
=> RetryPolicyM m | |
-> (RetryStatus -> b -> m Bool) | An action to check whether the result should be retried. If True, we delay and retry the operation. |
-> (RetryStatus -> m b) | Action to run |
-> m b |
Retry combinator for actions that don't raise exceptions, but
signal in their type the outcome has failed. Examples are the
Maybe
, Either
and EitherT
monads.
Let's write a function that always fails and watch this combinator retry it 5 additional times following the initial run:
>>>
import Data.Maybe
>>>
let f _ = putStrLn "Running action" >> return Nothing
>>>
retrying def (const $ return . isNothing) f
Running action Running action Running action Running action Running action Running action Nothing
Note how the latest failing result is returned after all retries have been exhausted.
:: (MonadIO m, MonadMask m) | |
=> RetryPolicyM m | Just use |
-> [RetryStatus -> Handler m Bool] | Should a given exception be retried? Action will be retried if this returns True *and* the policy allows it. This action will be consulted first even if the policy later blocks it. |
-> (RetryStatus -> m a) | Action to perform |
-> m a |
Run an action and recover from a raised exception by potentially
retrying the action a number of times. Note that if you're going to
use a handler for SomeException
, you should add explicit cases
*earlier* in the list of handlers to reject AsyncException
and
SomeAsyncException
, as catching these can cause thread and
program hangs. recoverAll
already does this for you so if you
just plan on catching SomeException
, you may as well ues
recoverAll
recoverAll :: (MonadIO m, MonadMask m) => RetryPolicyM m -> (RetryStatus -> m a) -> m a Source
Retry ALL exceptions that may be raised. To be used with caution;
this matches the exception on SomeException
. Note that this
handler explicitly does not handle AsyncException
nor
SomeAsyncException
(for versions of base >= 4.7). It is not a
good idea to catch async exceptions as it can result in hanging
threads and programs. Note that if you just throw an exception to
this thread that does not descend from SomeException, recoverAll
will catch it.
See how the action below is run once and retried 5 more times before finally failing for good:
>>>
let f _ = putStrLn "Running action" >> error "this is an error"
>>>
recoverAll def f
Running action Running action Running action Running action Running action Running action *** Exception: this is an error
:: (Monad m, Show e, Exception e) | |
=> (e -> m Bool) | Test for whether action is to be retried |
-> (Bool -> String -> m ()) | How to report the generated warning message. Boolean is whether it's being retried or crashed. |
-> RetryStatus | Retry number |
-> Handler m Bool |
Helper function for constructing handler functions of the form required
by recovering
.
Retry Policies
:: Int | Base delay in microseconds |
-> RetryPolicy |
Implement a constant delay with unlimited retries.
:: Int | First delay in microseconds |
-> RetryPolicy |
Grow delay exponentially each iteration. Each delay will increase by a factor of two.
fullJitterBackoff :: MonadIO m => Int -> RetryPolicyM m Source
FullJitter exponential backoff as explained in AWS Architecture Blog article.
http://www.awsarchitectureblog.com/2015/03/backoff.html
temp = min(cap, base * 2 ** attempt)
sleep = temp 2 + random_between(0, temp 2)
:: Int | Maximum number of retries. |
-> RetryPolicy |
Retry immediately, but only up to n
times.
Policy Transformers
:: Int | Time-delay limit in microseconds. |
-> RetryPolicy | |
-> RetryPolicy |
Add an upperbound to a policy such that once the given time-delay amount has been reached or exceeded, the policy will stop retrying and fail.
:: Monad m | |
=> Int | A maximum delay in microseconds |
-> RetryPolicyM m | |
-> RetryPolicyM m |
Set a time-upperbound for any delays that may be directed by the
given policy. This function does not terminate the retrying. The policy
`capDelay maxDelay (exponentialBackoff n)` will never stop retrying. It
will reach a state where it retries forever with a delay of maxDelay
between each one. To get termination you need to use one of the
limitRetries
function variants.
Development Helpers
simulatePolicy :: Monad m => Int -> RetryPolicyM m -> m [(Int, Maybe Int)] Source
Run given policy up to N iterations and gather results. In the
pair, the Int
is the iteration number and the Maybe Int
is the
delay in microseconds.
simulatePolicyPP :: Int -> RetryPolicyM IO -> IO () Source
Run given policy up to N iterations and pretty print results on the console.