retry-effectful-0.1.0.0: Adaptation of the retry library for the effectful ecosystem.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Effectful.Retry

Description

This module provides a Retry effect to adapt the retry library for the effectful ecosystem.

Synopsis

Effect

data Retry :: Effect Source #

An empty effect to provide the retry requirements, e.g. MonadIO and MonadMask

Instances

Instances details
type DispatchOf Retry Source # 
Instance details

Defined in Effectful.Retry

data StaticRep Retry Source # 
Instance details

Defined in Effectful.Retry

runRetry :: IOE :> es => Eff (Retry ': es) a -> Eff es a Source #

Peel the Retry effect.

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:

  1. If either policy returns Nothing, the combined policy returns Nothing. This can be used to inhibit after a number of retries, for example.
  2. 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.

Constructors

RetryPolicyM 

Instances

Instances details
Monad m => Monoid (RetryPolicyM m) 
Instance details

Defined in Control.Retry

Monad m => Semigroup (RetryPolicyM m) 
Instance details

Defined in Control.Retry

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.

Constructors

DontRetry

Don't retry (regardless of what the RetryPolicy says).

ConsultPolicy

Retry if the RetryPolicy says so, with the delay specified by the policy.

ConsultPolicyOverrideDelay Int

Retry if the RetryPolicy says so, but override the policy's delay (number of microseconds).

Instances

Instances details
Generic RetryAction 
Instance details

Defined in Control.Retry

Associated Types

type Rep RetryAction :: Type -> Type #

Read RetryAction 
Instance details

Defined in Control.Retry

Show RetryAction 
Instance details

Defined in Control.Retry

Eq RetryAction 
Instance details

Defined in Control.Retry

type Rep RetryAction 
Instance details

Defined in Control.Retry

type Rep RetryAction = D1 ('MetaData "RetryAction" "Control.Retry" "retry-0.9.3.0-BQnGInPtbrV6DNdCGLsy4a" 'False) (C1 ('MetaCons "DontRetry" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ConsultPolicy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConsultPolicyOverrideDelay" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))

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.

Constructors

RetryStatus 

Fields

Instances

Instances details
Generic RetryStatus 
Instance details

Defined in Control.Retry

Associated Types

type Rep RetryStatus :: Type -> Type #

Read RetryStatus 
Instance details

Defined in Control.Retry

Show RetryStatus 
Instance details

Defined in Control.Retry

Eq RetryStatus 
Instance details

Defined in Control.Retry

type Rep RetryStatus 
Instance details

Defined in Control.Retry

type Rep RetryStatus = D1 ('MetaData "RetryStatus" "Control.Retry" "retry-0.9.3.0-BQnGInPtbrV6DNdCGLsy4a" 'False) (C1 ('MetaCons "RetryStatus" 'PrefixI 'True) (S1 ('MetaSel ('Just "rsIterNumber") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "rsCumulativeDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "rsPreviousDelay") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int)))))

defaultRetryStatus :: RetryStatus #

Initial, default retry status. Use fields or lenses to update.

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 #

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 #

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 #

Retry Policies

constantDelay #

Arguments

:: forall (m :: Type -> Type). Monad m 
=> Int

Base delay in microseconds

-> RetryPolicyM m 

Implement a constant delay with unlimited retries.

exponentialBackoff #

Arguments

:: 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.

fullJitterBackoff #

Arguments

:: 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)

fibonacciBackoff #

Arguments

:: forall (m :: Type -> Type). Monad m 
=> Int

Base delay in microseconds

-> RetryPolicyM m 

Implement Fibonacci backoff.

limitRetries #

Arguments

:: Int

Maximum number of retries.

-> RetryPolicy 

Retry immediately, but only up to n times.

Policy Transformers

limitRetriesByDelay #

Arguments

:: 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 #

Arguments

:: 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.

capDelay #

Arguments

:: 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.