Copyright | Ozgun Ataman <ozgun.ataman@soostone.com> |
---|---|
License | BSD3 |
Maintainer | Ozgun Ataman |
Stability | provisional |
Safe Haskell | Safe-Inferred |
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.
Synopsis
- newtype RetryPolicyM m = RetryPolicyM {
- getRetryPolicyM :: RetryStatus -> m (Maybe Int)
- type RetryPolicy = forall m. Monad m => RetryPolicyM m
- retryPolicy :: Monad m => (RetryStatus -> Maybe Int) -> RetryPolicyM m
- retryPolicyDefault :: Monad m => RetryPolicyM m
- natTransformRetryPolicy :: (forall a. m a -> n a) -> RetryPolicyM m -> RetryPolicyM n
- data RetryAction
- toRetryAction :: Bool -> RetryAction
- data RetryStatus = RetryStatus {
- rsIterNumber :: !Int
- rsCumulativeDelay :: !Int
- rsPreviousDelay :: !(Maybe Int)
- defaultRetryStatus :: RetryStatus
- applyPolicy :: Monad m => RetryPolicyM m -> RetryStatus -> m (Maybe RetryStatus)
- applyAndDelay :: MonadIO m => RetryPolicyM m -> RetryStatus -> m (Maybe 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
- retryingDynamic :: MonadIO m => RetryPolicyM m -> (RetryStatus -> b -> m RetryAction) -> (RetryStatus -> m b) -> m b
- recovering :: (MonadIO m, MonadMask m) => RetryPolicyM m -> [RetryStatus -> Handler m Bool] -> (RetryStatus -> m a) -> m a
- recoveringDynamic :: (MonadIO m, MonadMask m) => RetryPolicyM m -> [RetryStatus -> Handler m RetryAction] -> (RetryStatus -> m a) -> m a
- stepping :: (MonadIO m, MonadMask m) => RetryPolicyM m -> [RetryStatus -> Handler m Bool] -> (RetryStatus -> m ()) -> (RetryStatus -> m a) -> RetryStatus -> m (Maybe a)
- recoverAll :: (MonadIO m, MonadMask m) => RetryPolicyM m -> (RetryStatus -> m a) -> m a
- skipAsyncExceptions :: MonadIO m => [RetryStatus -> Handler m Bool]
- logRetries :: (Monad m, Exception e) => (e -> m Bool) -> (Bool -> e -> RetryStatus -> m ()) -> RetryStatus -> Handler m Bool
- defaultLogMsg :: Exception e => Bool -> e -> RetryStatus -> String
- retryOnError :: (Functor m, MonadIO m, MonadError e m) => RetryPolicyM m -> (RetryStatus -> e -> m Bool) -> (RetryStatus -> m a) -> m a
- resumeRetrying :: MonadIO m => RetryStatus -> RetryPolicyM m -> (RetryStatus -> b -> m Bool) -> (RetryStatus -> m b) -> m b
- resumeRetryingDynamic :: MonadIO m => RetryStatus -> RetryPolicyM m -> (RetryStatus -> b -> m RetryAction) -> (RetryStatus -> m b) -> m b
- resumeRecovering :: (MonadIO m, MonadMask m) => RetryStatus -> RetryPolicyM m -> [RetryStatus -> Handler m Bool] -> (RetryStatus -> m a) -> m a
- resumeRecoveringDynamic :: (MonadIO m, MonadMask m) => RetryStatus -> RetryPolicyM m -> [RetryStatus -> Handler m RetryAction] -> (RetryStatus -> m a) -> m a
- resumeRecoverAll :: (MonadIO m, MonadMask m) => RetryStatus -> RetryPolicyM m -> (RetryStatus -> m a) -> m a
- constantDelay :: Monad m => Int -> RetryPolicyM m
- exponentialBackoff :: Monad m => Int -> RetryPolicyM m
- fullJitterBackoff :: MonadIO m => Int -> RetryPolicyM m
- fibonacciBackoff :: Monad m => Int -> RetryPolicyM m
- limitRetries :: Int -> RetryPolicy
- limitRetriesByDelay :: Monad m => Int -> RetryPolicyM m -> RetryPolicyM m
- limitRetriesByCumulativeDelay :: Monad m => Int -> RetryPolicyM m -> RetryPolicyM m
- 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 50000 <> limitRetries 5
Naturally, mempty
will retry immediately (delay 0) for an
unlimited number of retries, forming the identity for the Monoid
.
The default retry policy retryPolicyDefault
implements a constant 50ms delay, up to 5 times:
> retryPolicyDefault = constantDelay 50000 <> limitRetries 5
For anything more complex, just define your own RetryPolicyM
:
> myPolicy = retryPolicy $ \ rs -> if rsIterNumber rs > 10 then Just 1000 else Just 10000
Since 0.7.
RetryPolicyM | |
|
Instances
Monad m => Monoid (RetryPolicyM m) Source # | |
Defined in Control.Retry mempty :: RetryPolicyM m # mappend :: RetryPolicyM m -> RetryPolicyM m -> RetryPolicyM m # mconcat :: [RetryPolicyM m] -> RetryPolicyM m # | |
Monad m => Semigroup (RetryPolicyM m) Source # | |
Defined in Control.Retry (<>) :: RetryPolicyM m -> RetryPolicyM m -> RetryPolicyM m # sconcat :: NonEmpty (RetryPolicyM m) -> RetryPolicyM m # stimes :: Integral b => b -> RetryPolicyM m -> RetryPolicyM m # |
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 :: Monad m => (RetryStatus -> Maybe Int) -> RetryPolicyM m Source #
Helper for making simplified policies that don't use the monadic context.
retryPolicyDefault :: Monad m => RetryPolicyM m Source #
Default retry policy
natTransformRetryPolicy :: (forall a. m a -> n a) -> RetryPolicyM m -> RetryPolicyM n Source #
Applies a natural transformation to a policy to run a RetryPolicy
meant for the monad m
in the monad n
provided a transformation
from m
to n
is available. A common case is if you have a pure
policy, RetryPolicyM Identity
and want to use it to govern an
IO
computation you could write:
purePolicyInIO :: RetryPolicyM Identity -> RetryPolicyM IO purePolicyInIO = natTransformRetryPolicy (pure . runIdentity)
data RetryAction Source #
How to handle a failed action.
DontRetry | Don't retry (regardless of what the |
ConsultPolicy | Retry if the |
ConsultPolicyOverrideDelay Int | Retry if the |
Instances
toRetryAction :: Bool -> RetryAction Source #
Convert a boolean answer to the question "Should we retry?" into
a RetryAction
.
data RetryStatus Source #
Datatype with stats about retries made thus far.
RetryStatus | |
|
Instances
defaultRetryStatus :: RetryStatus Source #
Initial, default retry status. Use fields or lenses to update.
applyPolicy :: Monad m => RetryPolicyM m -> RetryStatus -> m (Maybe RetryStatus) Source #
applyAndDelay :: MonadIO m => RetryPolicyM m -> RetryStatus -> m (Maybe RetryStatus) Source #
Apply policy and delay by its amount if it results in a retry. Return updated status.
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 retryPolicyDefault (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 | |
=> RetryPolicyM m | |
-> (RetryStatus -> b -> m RetryAction) | An action to check whether the result should be retried.
The returned |
-> (RetryStatus -> m b) | Action to run |
-> m b |
Same as retrying
, but with the ability to override
the delay of the retry policy based on information
obtained after initiation.
For example, if the action to run is a HTTP request that turns out to fail with a status code 429 ("too many requests"), the response may contain a "Retry-After" HTTP header which specifies the number of seconds the client should wait until performing the next request. This function allows overriding the delay calculated by the given retry policy with the delay extracted from this header value.
In other words, given an arbitrary RetryPolicyM
rp
, the
following invocation will always delay by 1000 microseconds:
retryingDynamic rp (\_ _ -> return $ ConsultPolicyOverrideDelay 1000) f
Note that a RetryPolicy
s decision to not perform a retry
cannot be overridden. Ie. when to stop retrying is always decided
by the retry policy, regardless of the returned RetryAction
value.
:: (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 use
recoverAll
:: (MonadIO m, MonadMask m) | |
=> RetryPolicyM m | Just use |
-> [RetryStatus -> Handler m RetryAction] | Should a given exception be retried? Action will be
retried if this returns either |
-> (RetryStatus -> m a) | Action to perform |
-> m a |
The difference between this and recovering
is the same as
the difference between retryingDynamic
and retrying
.
:: (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 ()) | Action to run with updated status upon failure. |
-> (RetryStatus -> m a) | Main action to perform with current status. |
-> RetryStatus | Current status of this step |
-> m (Maybe a) |
A version of recovering
that tries to run the action only a
single time. The control will return immediately upon both success
and failure. Useful for implementing retry logic in distributed
queues and similar external-interfacing systems.
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 not 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 retryPolicyDefault f
Running action Running action Running action Running action Running action Running action *** Exception: this is an error
skipAsyncExceptions :: MonadIO m => [RetryStatus -> Handler m Bool] Source #
List of pre-made handlers that will skip retries on
AsyncException
and SomeAsyncException
. Append your handlers to
this list as a convenient way to make sure you're not catching
async exceptions like user interrupt.
:: (Monad m, Exception e) | |
=> (e -> m Bool) | Test for whether action is to be retried |
-> (Bool -> e -> RetryStatus -> 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
.
defaultLogMsg :: Exception e => Bool -> e -> RetryStatus -> String Source #
For use with logRetries
.
:: (Functor m, MonadIO m, MonadError e m) | |
=> RetryPolicyM m | Policy |
-> (RetryStatus -> e -> m Bool) | Should an error be retried? |
-> (RetryStatus -> m a) | Action to perform |
-> m a |
Resumable variants
:: MonadIO m | |
=> RetryStatus | |
-> 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 |
A variant of retrying
that allows specifying the initial
RetryStatus
so that the retrying operation may pick up where it left
off in regards to its retry policy.
resumeRetryingDynamic Source #
:: MonadIO m | |
=> RetryStatus | |
-> RetryPolicyM m | |
-> (RetryStatus -> b -> m RetryAction) | An action to check whether the result should be retried.
The returned |
-> (RetryStatus -> m b) | Action to run |
-> m b |
A variant of retryingDynamic
that allows specifying the initial
RetryStatus
so that a retrying operation may pick up where it left off
in regards to its retry policy.
:: (MonadIO m, MonadMask m) | |
=> RetryStatus | |
-> 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 |
A variant of recovering
that allows specifying the initial
RetryStatus
so that a recovering operation may pick up where it left
off in regards to its retry policy.
resumeRecoveringDynamic Source #
:: (MonadIO m, MonadMask m) | |
=> RetryStatus | |
-> RetryPolicyM m | Just use |
-> [RetryStatus -> Handler m RetryAction] | Should a given exception be retried? Action will be
retried if this returns either |
-> (RetryStatus -> m a) | Action to perform |
-> m a |
A variant of recoveringDynamic
that allows specifying the initial
RetryStatus
so that a recovering operation may pick up where it left
off in regards to its retry policy.
resumeRecoverAll :: (MonadIO m, MonadMask m) => RetryStatus -> RetryPolicyM m -> (RetryStatus -> m a) -> m a Source #
A variant of recoverAll
that allows specifying the initial
RetryStatus
so that a recovering operation may pick up where it left
off in regards to its retry policy.
Retry Policies
:: Monad m | |
=> Int | Base delay in microseconds |
-> RetryPolicyM m |
Implement a constant delay with unlimited retries.
:: Monad m | |
=> Int | Base delay in microseconds |
-> RetryPolicyM m |
Grow delay exponentially each iteration. Each delay will increase by a factor of two.
:: MonadIO m | |
=> Int | Base delay in microseconds |
-> RetryPolicyM m |
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)
:: Monad m | |
=> Int | Base delay in microseconds |
-> RetryPolicyM m |
Implement Fibonacci backoff.
:: Int | Maximum number of retries. |
-> RetryPolicy |
Retry immediately, but only up to n
times.
Policy Transformers
:: Monad m | |
=> Int | Time-delay limit in microseconds. |
-> RetryPolicyM m | |
-> RetryPolicyM m |
Add an upperbound to a policy such that once the given time-delay
amount *per try* has been reached or exceeded, the policy will stop
retrying and fail. If you need to stop retrying once *cumulative*
delay reaches a time-delay amount, use
limitRetriesByCumulativeDelay
limitRetriesByCumulativeDelay Source #
:: Monad m | |
=> Int | Time-delay limit in microseconds. |
-> RetryPolicyM m | |
-> RetryPolicyM m |
Add an upperbound to a policy such that once the cumulative delay over all retries has reached or exceeded the given limit, 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.