servant-rate-limit-0.1.0.0: Rate limiting for Servant
Safe HaskellNone
LanguageHaskell2010

Servant.RateLimit.Types

Synopsis

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

Instances details
HasClient m api => HasClient m (RateLimit st p :> api) Source # 
Instance details

Defined in Servant.RateLimit.Client

Associated Types

type Client m (RateLimit st p :> api) #

Methods

clientWithRoute :: Proxy m -> Proxy (RateLimit st p :> api) -> Request -> Client m (RateLimit st p :> api) #

hoistClientMonad :: Proxy m -> Proxy (RateLimit st p :> api) -> (forall x. mon x -> mon' x) -> Client mon (RateLimit st p :> api) -> Client mon' (RateLimit st p :> api) #

(HasServer api ctx, HasContextEntry ctx (Backend key), HasRateLimitStrategy strategy, HasRateLimitPolicy policy, key ~ RateLimitPolicyKey policy) => HasServer (RateLimit strategy policy :> api :: Type) ctx Source # 
Instance details

Defined in Servant.RateLimit.Server

Associated Types

type ServerT (RateLimit strategy policy :> api) m #

Methods

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 # 
Instance details

Defined in Servant.RateLimit.Client

type Client m (RateLimit st p :> api) = Client m api
type ServerT (RateLimit strategy policy :> api :: Type) m Source # 
Instance details

Defined in Servant.RateLimit.Server

type ServerT (RateLimit strategy policy :> api :: Type) m = ServerT api m

Rate-limiting strategies

data FixedWindow (secs :: Nat) (capacity :: Nat) Source #

A type-level description for the parameters of the fixedWindow strategy.

Instances

Instances details
(KnownNat secs, KnownNat capacity) => HasRateLimitStrategy (FixedWindow secs capacity) Source # 
Instance details

Defined in Servant.RateLimit.Types

Methods

strategyValue :: Backend key -> (Request -> IO key) -> Strategy Source #

data SlidingWindow (secs :: Nat) (capacity :: Nat) Source #

A type-level description for the parameters of the slidingWindow strategy.

Instances

Instances details
(KnownNat secs, KnownNat capacity) => HasRateLimitStrategy (SlidingWindow secs capacity) Source # 
Instance details

Defined in Servant.RateLimit.Types

Methods

strategyValue :: Backend key -> (Request -> IO key) -> Strategy Source #

class HasRateLimitStrategy strategy where Source #

A class of types which are type-level descriptions of rate-limiting strategies.

Methods

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

Instances details
(KnownNat secs, KnownNat capacity) => HasRateLimitStrategy (SlidingWindow secs capacity) Source # 
Instance details

Defined in Servant.RateLimit.Types

Methods

strategyValue :: Backend key -> (Request -> IO key) -> Strategy Source #

(KnownNat secs, KnownNat capacity) => HasRateLimitStrategy (FixedWindow secs capacity) Source # 
Instance details

Defined in Servant.RateLimit.Types

Methods

strategyValue :: Backend key -> (Request -> IO key) -> Strategy Source #

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

Instances details
KnownSymbol prefix => HasRateLimitPolicy (IPAddressPolicy prefix) Source # 
Instance details

Defined in Servant.RateLimit.Types

Associated Types

type RateLimitPolicyKey (IPAddressPolicy prefix) Source #

type RateLimitPolicyKey (IPAddressPolicy prefix) Source # 
Instance details

Defined in Servant.RateLimit.Types

class HasRateLimitPolicy policy where Source #

A class of types which are type-level descriptions of rate-limiting policies.

Associated Types

type RateLimitPolicyKey policy :: Type Source #

Methods

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

Instances details
KnownSymbol prefix => HasRateLimitPolicy (IPAddressPolicy prefix) Source # 
Instance details

Defined in Servant.RateLimit.Types

Associated Types

type RateLimitPolicyKey (IPAddressPolicy prefix) Source #