keter-rate-limiting-plugin-0.2.0.0: Simple Keter rate limiting plugin.
Copyright(c) 2025 Oleksandr Zhabenko
LicenseMIT
Maintaineroleksandr.zhabenko@yahoo.com
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Keter.RateLimiter.WAI

Description

This file is a ported to Haskell language code with some simplifications of rack-attack https://github.com/rack/rack-attack/blob/main/lib/rack/attack.rb and is based on the structure of the original code of rack-attack, Copyright (c) 2016 by Kickstarter, PBC, under the MIT License. Oleksandr Zhabenko added several implementations of the window algorithm: tinyLRU, sliding window, token bucket window, leaky bucket window alongside with the initial count algorithm using AI chatbots. IP Zone functionality added to allow separate caches per IP zone.

Overview ========

This module provides WAI middleware for declarative, IP-zone-aware rate limiting with multiple algorithms:

  • Fixed Window
  • Sliding Window
  • Token Bucket
  • Leaky Bucket
  • TinyLRU

Key points ----------

  • Plugin-friendly construction: build an environment once (Env) from RateLimiterConfig and produce a pure WAI Middleware. This matches common WAI patterns and avoids per-request setup or global mutable state.
  • Concurrency model: all shared structures inside Env use STM TVar, not IORef. This ensures thread-safe updates under GHC's lightweight (green) threads.
  • Zone-specific caches: per-IP-zone caches are stored in a HashMap keyed by zone identifiers. Zones are derived from a configurable strategy (ZoneBy), with a default.
  • No global caches in Keter: you can build one Env per compiled middleware chain and cache that chain externally (e.g., per-vhost + middleware-list), preserving counters/windows across requests.

Quick start -----------

1) Declarative configuration (e.g., parsed from JSON/YAML):

let cfg = RateLimiterConfig
      { rlZoneBy = ZoneDefault
      , rlThrottles =
          [ RLThrottle "api"   1000 3600 FixedWindow IdIP Nothing
          , RLThrottle "login" 5    300  TokenBucket IdIP (Just 600)
          ]
      }

2) Build Env once and obtain a pure Middleware:

env <- buildEnvFromConfig cfg
let mw = buildRateLimiterWithEnv env
app = mw baseApplication

Alternatively:

mw <- buildRateLimiter cfg  -- convenience: Env creation + Middleware
app = mw baseApplication

Usage patterns --------------

Declarative approach (recommended):

import Keter.RateLimiter.WAI
import Keter.RateLimiter.Cache (Algorithm(..))

main = do
  let config = RateLimiterConfig
        { rlZoneBy = ZoneIP
        , rlThrottles = 
            [ RLThrottle "api" 100 3600 FixedWindow IdIP Nothing
            ]
        }
  middleware <- buildRateLimiter config
  let app = middleware baseApp
  run 8080 app

Programmatic approach (advanced):

import Keter.RateLimiter.WAI
import Keter.RateLimiter.Cache (Algorithm(..))

main = do
  env initConfig (\req - "zone1")
  let throttleConfig = ThrottleConfig
        { throttleLimit = 100
        , throttlePeriod = 3600
        , throttleAlgorithm = FixedWindow
        , throttleIdentifierBy = IdIP
        , throttleTokenBucketTTL = Nothing
        }
  env' <- addThrottle env "api" throttleConfig
  let middleware = buildRateLimiterWithEnv env'
      app = middleware baseApp
  run 8080 app

Configuration reference -----------------------

Client identification strategies (IdentifierBy):

  • IdIP - Identify by client IP address
  • IdIPAndPath - Identify by IP address and request path
  • IdIPAndUA - Identify by IP address and User-Agent header
  • IdHeader headerName - Identify by custom header value
  • IdCookie cookieName - Identify by cookie value
  • IdHeaderAndIP headerName - Identify by header value combined with IP

Zone derivation strategies (ZoneBy):

  • ZoneDefault - All requests use the same cache (no zone separation)
  • ZoneIP - Separate zones by client IP address
  • ZoneHeader headerName - Separate zones by custom header value

Rate limiting algorithms:

  • FixedWindow - Traditional fixed-window counting
  • SlidingWindow - Precise sliding-window with timestamp tracking
  • TokenBucket - Allow bursts up to capacity, refill over time
  • LeakyBucket - Smooth rate limiting with configurable leak rate
  • TinyLRU - Least-recently-used eviction for memory efficiency
Synopsis

Environment & Configuration

data Env Source #

Thread-safe, shared state for rate limiting.

Concurrency model

  • Uses TVar from STM for in-memory HashMaps.
  • Safe for green-threaded request handlers.
  • No global variables: construct Env in your wiring/bootstrap and reuse it.

Constructors

Env 

Fields

data ThrottleConfig Source #

Runtime throttle parameters assembled from declarative configuration.

See RLThrottle for the declarative counterpart.

Constructors

ThrottleConfig 

Fields

Instances

Instances details
Generic ThrottleConfig Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Associated Types

type Rep ThrottleConfig 
Instance details

Defined in Keter.RateLimiter.WAI

type Rep ThrottleConfig = D1 ('MetaData "ThrottleConfig" "Keter.RateLimiter.WAI" "keter-rate-limiting-plugin-0.2.0.0-H4WU5a5Xu20FyQxdNRgnJy" 'False) (C1 ('MetaCons "ThrottleConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "throttleLimit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "throttlePeriod") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "throttleAlgorithm") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Algorithm) :*: (S1 ('MetaSel ('Just "throttleIdentifierBy") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IdentifierBy) :*: S1 ('MetaSel ('Just "throttleTokenBucketTTL") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))))))
Show ThrottleConfig Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Eq ThrottleConfig Source # 
Instance details

Defined in Keter.RateLimiter.WAI

type Rep ThrottleConfig Source # 
Instance details

Defined in Keter.RateLimiter.WAI

type Rep ThrottleConfig = D1 ('MetaData "ThrottleConfig" "Keter.RateLimiter.WAI" "keter-rate-limiting-plugin-0.2.0.0-H4WU5a5Xu20FyQxdNRgnJy" 'False) (C1 ('MetaCons "ThrottleConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "throttleLimit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "throttlePeriod") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "throttleAlgorithm") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Algorithm) :*: (S1 ('MetaSel ('Just "throttleIdentifierBy") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IdentifierBy) :*: S1 ('MetaSel ('Just "throttleTokenBucketTTL") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))))))

data IdentifierBy Source #

How to identify clients for throttling.

Instances

Instances details
FromJSON IdentifierBy Source # 
Instance details

Defined in Keter.RateLimiter.WAI

ToJSON IdentifierBy Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Generic IdentifierBy Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Associated Types

type Rep IdentifierBy 
Instance details

Defined in Keter.RateLimiter.WAI

type Rep IdentifierBy = D1 ('MetaData "IdentifierBy" "Keter.RateLimiter.WAI" "keter-rate-limiting-plugin-0.2.0.0-H4WU5a5Xu20FyQxdNRgnJy" 'False) ((C1 ('MetaCons "IdIP" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IdHeader" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HeaderName)) :+: C1 ('MetaCons "IdCookie" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) :+: (C1 ('MetaCons "IdIPAndPath" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IdIPAndUA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IdHeaderAndIP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HeaderName)))))
Show IdentifierBy Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Eq IdentifierBy Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Hashable IdentifierBy Source # 
Instance details

Defined in Keter.RateLimiter.WAI

type Rep IdentifierBy Source # 
Instance details

Defined in Keter.RateLimiter.WAI

type Rep IdentifierBy = D1 ('MetaData "IdentifierBy" "Keter.RateLimiter.WAI" "keter-rate-limiting-plugin-0.2.0.0-H4WU5a5Xu20FyQxdNRgnJy" 'False) ((C1 ('MetaCons "IdIP" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IdHeader" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HeaderName)) :+: C1 ('MetaCons "IdCookie" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) :+: (C1 ('MetaCons "IdIPAndPath" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IdIPAndUA" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IdHeaderAndIP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HeaderName)))))

data ZoneBy Source #

How to derive IP zones from requests.

Instances

Instances details
FromJSON ZoneBy Source # 
Instance details

Defined in Keter.RateLimiter.WAI

ToJSON ZoneBy Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Generic ZoneBy Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Associated Types

type Rep ZoneBy 
Instance details

Defined in Keter.RateLimiter.WAI

type Rep ZoneBy = D1 ('MetaData "ZoneBy" "Keter.RateLimiter.WAI" "keter-rate-limiting-plugin-0.2.0.0-H4WU5a5Xu20FyQxdNRgnJy" 'False) (C1 ('MetaCons "ZoneDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ZoneIP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ZoneHeader" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HeaderName))))

Methods

from :: ZoneBy -> Rep ZoneBy x #

to :: Rep ZoneBy x -> ZoneBy #

Show ZoneBy Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Eq ZoneBy Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Methods

(==) :: ZoneBy -> ZoneBy -> Bool #

(/=) :: ZoneBy -> ZoneBy -> Bool #

type Rep ZoneBy Source # 
Instance details

Defined in Keter.RateLimiter.WAI

type Rep ZoneBy = D1 ('MetaData "ZoneBy" "Keter.RateLimiter.WAI" "keter-rate-limiting-plugin-0.2.0.0-H4WU5a5Xu20FyQxdNRgnJy" 'False) (C1 ('MetaCons "ZoneDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ZoneIP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ZoneHeader" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HeaderName))))

data RLThrottle Source #

Declarative throttle rule (parsed from JSON/YAML).

Instances

Instances details
FromJSON RLThrottle Source # 
Instance details

Defined in Keter.RateLimiter.WAI

ToJSON RLThrottle Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Generic RLThrottle Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Associated Types

type Rep RLThrottle 
Instance details

Defined in Keter.RateLimiter.WAI

type Rep RLThrottle = D1 ('MetaData "RLThrottle" "Keter.RateLimiter.WAI" "keter-rate-limiting-plugin-0.2.0.0-H4WU5a5Xu20FyQxdNRgnJy" 'False) (C1 ('MetaCons "RLThrottle" 'PrefixI 'True) ((S1 ('MetaSel ('Just "rlName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "rlLimit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "rlPeriod") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) :*: (S1 ('MetaSel ('Just "rlAlgo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Algorithm) :*: (S1 ('MetaSel ('Just "rlIdBy") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IdentifierBy) :*: S1 ('MetaSel ('Just "rlTokenBucketTTL") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))))))
Show RLThrottle Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Eq RLThrottle Source # 
Instance details

Defined in Keter.RateLimiter.WAI

type Rep RLThrottle Source # 
Instance details

Defined in Keter.RateLimiter.WAI

type Rep RLThrottle = D1 ('MetaData "RLThrottle" "Keter.RateLimiter.WAI" "keter-rate-limiting-plugin-0.2.0.0-H4WU5a5Xu20FyQxdNRgnJy" 'False) (C1 ('MetaCons "RLThrottle" 'PrefixI 'True) ((S1 ('MetaSel ('Just "rlName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "rlLimit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "rlPeriod") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int))) :*: (S1 ('MetaSel ('Just "rlAlgo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Algorithm) :*: (S1 ('MetaSel ('Just "rlIdBy") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 IdentifierBy) :*: S1 ('MetaSel ('Just "rlTokenBucketTTL") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Int))))))

data RateLimiterConfig Source #

Top-level configuration: zone strategy and throttle rules.

Constructors

RateLimiterConfig 

Instances

Instances details
FromJSON RateLimiterConfig Source # 
Instance details

Defined in Keter.RateLimiter.WAI

ToJSON RateLimiterConfig Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Generic RateLimiterConfig Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Associated Types

type Rep RateLimiterConfig 
Instance details

Defined in Keter.RateLimiter.WAI

type Rep RateLimiterConfig = D1 ('MetaData "RateLimiterConfig" "Keter.RateLimiter.WAI" "keter-rate-limiting-plugin-0.2.0.0-H4WU5a5Xu20FyQxdNRgnJy" 'False) (C1 ('MetaCons "RateLimiterConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "rlZoneBy") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ZoneBy) :*: S1 ('MetaSel ('Just "rlThrottles") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [RLThrottle])))
Show RateLimiterConfig Source # 
Instance details

Defined in Keter.RateLimiter.WAI

Eq RateLimiterConfig Source # 
Instance details

Defined in Keter.RateLimiter.WAI

type Rep RateLimiterConfig Source # 
Instance details

Defined in Keter.RateLimiter.WAI

type Rep RateLimiterConfig = D1 ('MetaData "RateLimiterConfig" "Keter.RateLimiter.WAI" "keter-rate-limiting-plugin-0.2.0.0-H4WU5a5Xu20FyQxdNRgnJy" 'False) (C1 ('MetaCons "RateLimiterConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "rlZoneBy") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ZoneBy) :*: S1 ('MetaSel ('Just "rlThrottles") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [RLThrottle])))

initConfig Source #

Arguments

:: (Request -> IPZoneIdentifier)

Request -> zone label

-> IO Env 

Initialize an empty environment with a zone-derivation function.

Populates the default zone lazily as needed; a default cache is allocated immediately for the default zone to keep fast-path lookups cheap.

addThrottle :: Env -> Text -> ThrottleConfig -> IO Env Source #

Add or replace a named throttle configuration.

STM-backed insertion for concurrency safety.

Middleware

attackMiddleware :: Env -> Application -> Application Source #

Low-level middleware: apply throttling using an existing Env.

If any throttle denies the request, a 429 response is returned. Otherwise, app is invoked.

buildRateLimiter :: RateLimiterConfig -> IO Middleware Source #

Convenience: build an Env from config and return the Middleware.

Suitable if you don't need to retain the Env for administrative operations.

buildRateLimiterWithEnv :: Env -> Middleware Source #

Produce a pure Middleware from an existing Env.

This is the recommended way to integrate with WAI/Keter: the middleware is a pure function, while the state is already encapsulated in Env.

buildEnvFromConfig :: RateLimiterConfig -> IO Env Source #

Build Env once from a declarative RateLimiterConfig.

Use this at wiring time; the returned Env is stable and reused across requests.

Manual Control & Inspection

instrument :: Env -> Request -> IO Bool Source #

Inspect all active throttles in Env for the given request.

Returns True if the request should be blocked under any rule.

cacheResetAll :: Env -> IO () Source #

Reset all caches across all known zones.

Useful in tests or administrative endpoints.

Helpers for configuration

registerThrottle :: Env -> RLThrottle -> IO Env Source #

Register a single throttle rule into an Env.

mkIdentifier :: IdentifierBy -> Request -> IO (Maybe Text) Source #

Build a request-identifier function from a declarative spec.

mkZoneFn :: ZoneBy -> Request -> IPZoneIdentifier Source #

Derive IP zone function from a declarative spec.

getClientIPPure :: Request -> IPZoneIdentifier Source #

Extract client IP with header precedence: X-Forwarded-For, X-Real-IP, then socket.

hdr :: Text -> HeaderName Source #

Construct a case-insensitive header name from Text.

fromHeaderName :: HeaderName -> ByteString Source #

Extract original bytes from a case-insensitive header name.