Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Retry :: Effect
- runRetry :: IOE :> es => Eff (Retry ': es) a -> Eff es a
- newtype RetryPolicyM (m :: Type -> Type) = RetryPolicyM {
- getRetryPolicyM :: RetryStatus -> m (Maybe Int)
- retryPolicy :: forall (m :: Type -> Type). Monad m => (RetryStatus -> Maybe Int) -> RetryPolicyM m
- retryPolicyDefault :: forall (m :: Type -> Type). Monad m => RetryPolicyM m
- data RetryAction
- toRetryAction :: Bool -> RetryAction
- data RetryStatus = RetryStatus {
- rsIterNumber :: !Int
- rsCumulativeDelay :: !Int
- rsPreviousDelay :: !(Maybe Int)
- defaultRetryStatus :: RetryStatus
- applyPolicy :: Retry :> es => RetryPolicyM (Eff es) -> RetryStatus -> Eff es (Maybe RetryStatus)
- applyAndDelay :: Retry :> es => RetryPolicyM (Eff es) -> RetryStatus -> Eff es (Maybe RetryStatus)
- retrying :: Retry :> es => RetryPolicyM (Eff es) -> (RetryStatus -> b -> Eff es Bool) -> (RetryStatus -> Eff es b) -> Eff es b
- retryingDynamic :: Retry :> es => RetryPolicyM (Eff es) -> (RetryStatus -> b -> Eff es RetryAction) -> (RetryStatus -> Eff es b) -> Eff es b
- recovering :: Retry :> es => RetryPolicyM (Eff es) -> [RetryStatus -> Handler (Eff es) Bool] -> (RetryStatus -> Eff es a) -> Eff es a
- recoveringDynamic :: Retry :> es => RetryPolicyM (Eff es) -> [RetryStatus -> Handler (Eff es) RetryAction] -> (RetryStatus -> Eff es a) -> Eff es a
- stepping :: Retry :> es => RetryPolicyM (Eff es) -> [RetryStatus -> Handler (Eff es) Bool] -> (RetryStatus -> Eff es ()) -> (RetryStatus -> Eff es a) -> RetryStatus -> Eff es (Maybe a)
- recoverAll :: Retry :> es => RetryPolicyM (Eff es) -> (RetryStatus -> Eff es a) -> Eff es a
- skipAsyncExceptions :: Retry :> es => [RetryStatus -> Handler (Eff es) Bool]
- logRetries :: (Retry :> es, Exception e) => (e -> Eff es Bool) -> (Bool -> e -> RetryStatus -> Eff es ()) -> RetryStatus -> Handler (Eff es) Bool
- defaultLogMsg :: Exception e => Bool -> e -> RetryStatus -> String
- resumeRetrying :: Retry :> es => RetryStatus -> RetryPolicyM (Eff es) -> (RetryStatus -> b -> Eff es Bool) -> (RetryStatus -> Eff es b) -> Eff es b
- resumeRetryingDynamic :: Retry :> es => RetryStatus -> RetryPolicyM (Eff es) -> (RetryStatus -> b -> Eff es RetryAction) -> (RetryStatus -> Eff es b) -> Eff es b
- resumeRecovering :: Retry :> es => RetryStatus -> RetryPolicyM (Eff es) -> [RetryStatus -> Handler (Eff es) Bool] -> (RetryStatus -> Eff es a) -> Eff es a
- resumeRecoveringDynamic :: Retry :> es => RetryStatus -> RetryPolicyM (Eff es) -> [RetryStatus -> Handler (Eff es) RetryAction] -> (RetryStatus -> Eff es a) -> Eff es a
- resumeRecoverAll :: Retry :> es => RetryStatus -> RetryPolicyM (Eff es) -> (RetryStatus -> Eff es a) -> Eff es a
- constantDelay :: forall (m :: Type -> Type). Monad m => Int -> RetryPolicyM m
- exponentialBackoff :: forall (m :: Type -> Type). Monad m => Int -> RetryPolicyM m
- fullJitterBackoff :: forall (m :: Type -> Type). MonadIO m => Int -> RetryPolicyM m
- fibonacciBackoff :: forall (m :: Type -> Type). Monad m => Int -> RetryPolicyM m
- limitRetries :: Int -> RetryPolicy
- limitRetriesByDelay :: forall (m :: Type -> Type). Monad m => Int -> RetryPolicyM m -> RetryPolicyM m
- limitRetriesByCumulativeDelay :: forall (m :: Type -> Type). Monad m => Int -> RetryPolicyM m -> RetryPolicyM m
- capDelay :: forall (m :: Type -> Type). Monad m => Int -> RetryPolicyM m -> RetryPolicyM m
- simulatePolicy :: Monad m => Int -> RetryPolicyM m -> m [(Int, Maybe Int)]
- simulatePolicyPP :: Int -> RetryPolicyM IO -> IO ()
Effect
An empty effect to provide the retry requirements, e.g. MonadIO and MonadMask
Instances
type DispatchOf Retry Source # | |
Defined in Effectful.Retry | |
data StaticRep Retry Source # | |
Defined in Effectful.Retry |
Types and Operations
newtype RetryPolicyM (m :: Type -> Type) #
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) | |
Defined in Control.Retry mempty :: RetryPolicyM m # mappend :: RetryPolicyM m -> RetryPolicyM m -> RetryPolicyM m # mconcat :: [RetryPolicyM m] -> RetryPolicyM m # | |
Monad m => Semigroup (RetryPolicyM m) | |
Defined in Control.Retry (<>) :: RetryPolicyM m -> RetryPolicyM m -> RetryPolicyM m # sconcat :: NonEmpty (RetryPolicyM m) -> RetryPolicyM m # stimes :: Integral b => b -> RetryPolicyM m -> RetryPolicyM m # |
retryPolicy :: forall (m :: Type -> Type). Monad m => (RetryStatus -> Maybe Int) -> RetryPolicyM m #
Helper for making simplified policies that don't use the monadic context.
retryPolicyDefault :: forall (m :: Type -> Type). Monad m => RetryPolicyM m #
Default retry policy
data RetryAction #
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 #
Convert a boolean answer to the question "Should we retry?" into
a RetryAction
.
data RetryStatus #
Datatype with stats about retries made thus far.
RetryStatus | |
|
Instances
defaultRetryStatus :: RetryStatus #
Initial, default retry status. Use fields or lenses to update.
applyPolicy :: Retry :> es => RetryPolicyM (Eff es) -> RetryStatus -> Eff es (Maybe RetryStatus) Source #
applyAndDelay :: Retry :> es => RetryPolicyM (Eff es) -> RetryStatus -> Eff es (Maybe RetryStatus) Source #
Applying Retry Policies
retrying :: Retry :> es => RetryPolicyM (Eff es) -> (RetryStatus -> b -> Eff es Bool) -> (RetryStatus -> Eff es b) -> Eff es b Source #
retryingDynamic :: Retry :> es => RetryPolicyM (Eff es) -> (RetryStatus -> b -> Eff es RetryAction) -> (RetryStatus -> Eff es b) -> Eff es b Source #
recovering :: Retry :> es => RetryPolicyM (Eff es) -> [RetryStatus -> Handler (Eff es) Bool] -> (RetryStatus -> Eff es a) -> Eff es a Source #
recoveringDynamic :: Retry :> es => RetryPolicyM (Eff es) -> [RetryStatus -> Handler (Eff es) RetryAction] -> (RetryStatus -> Eff es a) -> Eff es a Source #
stepping :: Retry :> es => RetryPolicyM (Eff es) -> [RetryStatus -> Handler (Eff es) Bool] -> (RetryStatus -> Eff es ()) -> (RetryStatus -> Eff es a) -> RetryStatus -> Eff es (Maybe a) Source #
recoverAll :: Retry :> es => RetryPolicyM (Eff es) -> (RetryStatus -> Eff es a) -> Eff es a Source #
skipAsyncExceptions :: Retry :> es => [RetryStatus -> Handler (Eff es) Bool] Source #
logRetries :: (Retry :> es, Exception e) => (e -> Eff es Bool) -> (Bool -> e -> RetryStatus -> Eff es ()) -> RetryStatus -> Handler (Eff es) Bool Source #
defaultLogMsg :: Exception e => Bool -> e -> RetryStatus -> String #
For use with logRetries
.
Resumable variants
resumeRetrying :: Retry :> es => RetryStatus -> RetryPolicyM (Eff es) -> (RetryStatus -> b -> Eff es Bool) -> (RetryStatus -> Eff es b) -> Eff es b Source #
resumeRetryingDynamic :: Retry :> es => RetryStatus -> RetryPolicyM (Eff es) -> (RetryStatus -> b -> Eff es RetryAction) -> (RetryStatus -> Eff es b) -> Eff es b Source #
resumeRecovering :: Retry :> es => RetryStatus -> RetryPolicyM (Eff es) -> [RetryStatus -> Handler (Eff es) Bool] -> (RetryStatus -> Eff es a) -> Eff es a Source #
resumeRecoveringDynamic :: Retry :> es => RetryStatus -> RetryPolicyM (Eff es) -> [RetryStatus -> Handler (Eff es) RetryAction] -> (RetryStatus -> Eff es a) -> Eff es a Source #
resumeRecoverAll :: Retry :> es => RetryStatus -> RetryPolicyM (Eff es) -> (RetryStatus -> Eff es a) -> Eff es a Source #
Retry Policies
:: forall (m :: Type -> Type). Monad m | |
=> Int | Base delay in microseconds |
-> RetryPolicyM m |
Implement a constant delay with unlimited retries.
:: forall (m :: Type -> Type). Monad m | |
=> Int | Base delay in microseconds |
-> RetryPolicyM m |
Grow delay exponentially each iteration. Each delay will increase by a factor of two.
:: forall (m :: Type -> Type). 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)
:: forall (m :: Type -> Type). 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
:: forall (m :: Type -> Type). 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 #
:: forall (m :: Type -> Type). 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.
:: forall (m :: Type -> Type). 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)] #
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 () #
Run given policy up to N iterations and pretty print results on the console.