Copyright | (c) 2019 Chris Coffey |
---|---|
License | MIT |
Maintainer | chris@foldl.io |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
This is a batteries mostly-included circuit breaker library. It provides automatic backoff behavior by preventing calls to a failing resource. For example, if a particular service is currently overloaded and begins failing to respond to requests, then the circuit breaker will detect those errors and prevent further calls from actually hitting the server in question. Once the service has had a chance to stabilize the circuit breaker will allow a "testing" call to pass through. If it succeeds, then all other calls are allowed to flow through. If it fails then it waits a bit longer before testing again.
Synopsis
- data CircuitBreaker (label :: Symbol) (dripFreq :: Nat) (errorThreshold :: Nat)
- newtype CircuitBreakerConf = CBConf {
- cbBreakers :: MVar (HashMap Text (MVar CircuitState))
- withBreaker :: (KnownSymbol label, KnownNat df, KnownNat et, Monad m, MonadUnliftIO m, MonadReader env m, HasCircuitConf env) => CircuitBreaker label df et -> m a -> m (Either CircutBreakerError a)
- data CircutBreakerError
- class HasCircuitConf env where
- getCircuitState :: env -> CircuitBreakerConf
- data CircuitState = CircuitState {}
- data CircuitAction
- = SkipClosed
- | Run
- newtype ErrorThreshold = ET Natural
- data CBCondition
- initialBreakerState :: MonadUnliftIO m => m CircuitBreakerConf
- breakerTransitionGuard :: MonadUnliftIO m => MVar CircuitState -> ErrorThreshold -> m CircuitAction
- breakerTryPerformAction :: MonadUnliftIO m => Text -> m a -> MVar CircuitState -> CircuitAction -> m (Either CircutBreakerError a)
- decrementErrorCount :: MonadUnliftIO m => MVar CircuitState -> m ()
Documentation
data CircuitBreaker (label :: Symbol) (dripFreq :: Nat) (errorThreshold :: Nat) Source #
The definition of a particular circuit breaker
newtype CircuitBreakerConf Source #
CBConf | |
|
Instances
HasCircuitConf CircuitBreakerConf Source # | |
Defined in System.CircuitBreaker |
withBreaker :: (KnownSymbol label, KnownNat df, KnownNat et, Monad m, MonadUnliftIO m, MonadReader env m, HasCircuitConf env) => CircuitBreaker label df et -> m a -> m (Either CircutBreakerError a) Source #
Brackets a computation with short-circuit logic. If an uncaught error occurs, then the circuit breaker opens, which causes all additional threads entering the wrapped code to fail until the specified timeout has expired. Once the timeout expires, a single thread may enter the protected region. If the call succeeds, then the circuit breaker allows all other traffic through. Otherwise, it resets the timeout, after which the above algorithm repeats.
Important Note: This does not catch errors. If an IO error is thrown, it will bubble up from this function. Internally, if the breaker is tripped, it will prevent further calls
data CircutBreakerError Source #
Instances
Eq CircutBreakerError Source # | |
Defined in System.CircuitBreaker (==) :: CircutBreakerError -> CircutBreakerError -> Bool # (/=) :: CircutBreakerError -> CircutBreakerError -> Bool # | |
Ord CircutBreakerError Source # | |
Defined in System.CircuitBreaker compare :: CircutBreakerError -> CircutBreakerError -> Ordering # (<) :: CircutBreakerError -> CircutBreakerError -> Bool # (<=) :: CircutBreakerError -> CircutBreakerError -> Bool # (>) :: CircutBreakerError -> CircutBreakerError -> Bool # (>=) :: CircutBreakerError -> CircutBreakerError -> Bool # max :: CircutBreakerError -> CircutBreakerError -> CircutBreakerError # min :: CircutBreakerError -> CircutBreakerError -> CircutBreakerError # | |
Show CircutBreakerError Source # | |
Defined in System.CircuitBreaker showsPrec :: Int -> CircutBreakerError -> ShowS # show :: CircutBreakerError -> String # showList :: [CircutBreakerError] -> ShowS # |
class HasCircuitConf env where Source #
A constraint that allows pullng the circuit breaker
getCircuitState :: env -> CircuitBreakerConf Source #
Instances
HasCircuitConf CircuitBreakerConf Source # | |
Defined in System.CircuitBreaker |
data CircuitState Source #
Instances
Show CircuitState Source # | |
Defined in System.CircuitBreaker showsPrec :: Int -> CircuitState -> ShowS # show :: CircuitState -> String # showList :: [CircuitState] -> ShowS # |
data CircuitAction Source #
Instances
Eq CircuitAction Source # | |
Defined in System.CircuitBreaker (==) :: CircuitAction -> CircuitAction -> Bool # (/=) :: CircuitAction -> CircuitAction -> Bool # | |
Show CircuitAction Source # | |
Defined in System.CircuitBreaker showsPrec :: Int -> CircuitAction -> ShowS # show :: CircuitAction -> String # showList :: [CircuitAction] -> ShowS # |
newtype ErrorThreshold Source #
data CBCondition Source #
The current condition of a CircutBreaker may be Active, Testing, or Waiting for the timeout to elapse.
Instances
initialBreakerState :: MonadUnliftIO m => m CircuitBreakerConf Source #
Initialize the storage for the process' circuit breakers
Exported for testing
breakerTransitionGuard :: MonadUnliftIO m => MVar CircuitState -> ErrorThreshold -> m CircuitAction Source #
Given the current state of the circuit breaker, determine what action should
be taken during the body of the bracket
.
Condition rules:
1) If the circuit breaker is in Active
then pass the call on
2) If the circuit breaker is in Testing
then fail the call
3) If the circuit breaker is in Waiting
and the timeout has not elapsed then fail the call
4) If the circuit breaker is in Waiting
and the timeout has elapsed then convert to Testing
and try the call
breakerTryPerformAction Source #
:: MonadUnliftIO m | |
=> Text | label |
-> m a | Action to perform |
-> MVar CircuitState | Pointer to the breaker state |
-> CircuitAction | |
-> m (Either CircutBreakerError a) |
Conditionally performs an action with in a circuit breaker, as determined by the current breaker state.
decrementErrorCount :: MonadUnliftIO m => MVar CircuitState -> m () Source #
Decrements a counter