Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data RateLimit strategy policy
- data FixedWindow (dur :: TimePeriod) (capacity :: Nat)
- data SlidingWindow (dur :: TimePeriod) (capacity :: Nat)
- class HasRateLimitStrategy strategy where
- strategyValue :: Backend key -> (Request -> IO key) -> Strategy
- data IPAddressPolicy (prefix :: Symbol)
- class HasRateLimitPolicy policy where
- type RateLimitPolicyKey policy :: Type
- policyGetIdentifier :: Request -> IO (RateLimitPolicyKey policy)
- module Data.Time.TypeLevel
Servant combinator
data RateLimit strategy policy Source #
A generalised rate limiting combinator which combines type-level
descriptions of a rate-limiting strategy, such as FixedWindow
, with a
type-level description of a rate-limiting policy, such as IPAddressPolicy
.
Instances
HasClient m api => HasClient m (RateLimit st p :> api) Source # | |
Defined in Servant.RateLimit.Client | |
(HasServer api ctx, HasContextEntry ctx (Backend key), HasRateLimitStrategy strategy, HasRateLimitPolicy policy, key ~ RateLimitPolicyKey policy) => HasServer (RateLimit strategy policy :> api :: Type) ctx Source # | |
Defined in Servant.RateLimit.Server route :: Proxy (RateLimit strategy policy :> api) -> Context ctx -> Delayed env (Server (RateLimit strategy policy :> api)) -> Router env # hoistServerWithContext :: Proxy (RateLimit strategy policy :> api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (RateLimit strategy policy :> api) m -> ServerT (RateLimit strategy policy :> api) n # | |
type Client m (RateLimit st p :> api) Source # | |
Defined in Servant.RateLimit.Client | |
type ServerT (RateLimit strategy policy :> api :: Type) m Source # | |
Rate-limiting strategies
data FixedWindow (dur :: TimePeriod) (capacity :: Nat) Source #
A type-level description for the parameters of the fixedWindow
strategy.
Instances
(KnownDuration dur, KnownNat capacity, TimeUnit (DurationUnit dur)) => HasRateLimitStrategy (FixedWindow dur capacity) Source # | |
Defined in Servant.RateLimit.Types |
data SlidingWindow (dur :: TimePeriod) (capacity :: Nat) Source #
A type-level description for the parameters of the slidingWindow
strategy.
Instances
(KnownDuration dur, KnownNat capacity, TimeUnit (DurationUnit dur)) => HasRateLimitStrategy (SlidingWindow dur capacity) Source # | |
Defined in Servant.RateLimit.Types |
class HasRateLimitStrategy strategy where Source #
A class of types which are type-level descriptions of rate-limiting strategies.
strategyValue :: Backend key -> (Request -> IO key) -> Strategy Source #
strategyValue
backend getKey
is a function which, given a
backend
and a function getKey
used to compute the key using which
the client should be identified, returns a rate-limiting Strategy
.
Instances
(KnownDuration dur, KnownNat capacity, TimeUnit (DurationUnit dur)) => HasRateLimitStrategy (SlidingWindow dur capacity) Source # | |
Defined in Servant.RateLimit.Types | |
(KnownDuration dur, KnownNat capacity, TimeUnit (DurationUnit dur)) => HasRateLimitStrategy (FixedWindow dur capacity) Source # | |
Defined in Servant.RateLimit.Types |
Rate-limiting policies
data IPAddressPolicy (prefix :: Symbol) Source #
A simple rate-limiting policy which applies a rate-limiting strategy
based on the client's IP address. This policy is useful mainly for testing
purposes. For production use, you should implement your own policy based
on e.g. the current user, API key, etc. The prefix
parameter may be set
to the empty string if all API endpoints count towards the same rate limit,
but can be set to other values to have different rate limits for different
sets of endpoints.
Instances
KnownSymbol prefix => HasRateLimitPolicy (IPAddressPolicy prefix) Source # | |
Defined in Servant.RateLimit.Types type RateLimitPolicyKey (IPAddressPolicy prefix) Source # policyGetIdentifier :: Request -> IO (RateLimitPolicyKey (IPAddressPolicy prefix)) Source # | |
type RateLimitPolicyKey (IPAddressPolicy prefix) Source # | |
Defined in Servant.RateLimit.Types |
class HasRateLimitPolicy policy where Source #
A class of types which are type-level descriptions of rate-limiting policies.
type RateLimitPolicyKey policy :: Type Source #
policyGetIdentifier :: Request -> IO (RateLimitPolicyKey policy) Source #
policyGetIdentifier
request
computes the key that should be
used by the backend to identify the client to which the rate
limiting policy should be applied to. This could be as simple
as retrieving the IP address of the client from request
(as is the case with IPAddressPolicy
) or retrieving data from
the request
vault. The computation runs in IO
to allow policies
to perform arbitrary effects.
Instances
KnownSymbol prefix => HasRateLimitPolicy (IPAddressPolicy prefix) Source # | |
Defined in Servant.RateLimit.Types type RateLimitPolicyKey (IPAddressPolicy prefix) Source # policyGetIdentifier :: Request -> IO (RateLimitPolicyKey (IPAddressPolicy prefix)) Source # |
Re-exports
module Data.Time.TypeLevel