Copyright | (c) 2025 Oleksandr Zhabenko |
---|---|
License | MIT |
Maintainer | oleksandr.zhabenko@yahoo.com |
Stability | stable |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Keter.RateLimiter.Cache
Description
This file is a ported to Haskell language code with some simplifications of rack-attack https:/github.comrackrack-attackblobmainlibrackattack/cache.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: sliding window, token bucket window, leaky bucket window alongside with the initial count algorithm using AI chatbots. Also there is extended multiple IP zones and combined usage of the algorithms with convenient wrappers provided.
This implementation is released under the MIT License.
This module provides a unified cache abstraction layer that supports multiple rate limiting algorithms and storage backends. It uses advanced Haskell type system features including GADTs, DataKinds, and functional dependencies to provide type-safe, algorithm-specific storage while maintaining a common interface.
Architecture Overview
┌─────────────────┐ ┌──────────────────┐ ┌─────────────────┐ │ Algorithm │ │ Cache Layer │ │ Storage Backend│ │ │ │ │ │ │ │ • FixedWindow │◄───┤ • Type Safety │◄───┤ • InMemoryStore │ │ • SlidingWindow │ │ • Key Prefixing │ │ • Auto Purging │ │ • TokenBucket │ │ • Serialization │ │ • STM Based │ │ • LeakyBucket │ │ • Error Handling │ │ • Thread Safe │ │ • TinyLRU │ │ │ │ │ └─────────────────┘ └──────────────────┘ └─────────────────┘
Type-Level Algorithm Safety
The module uses DataKinds and GADTs to ensure compile-time type safety:
-- Algorithm types are promoted to type-level data Algorithm = FixedWindow | TokenBucket | ... -- Storage is parameterized by algorithm type data InMemoryStore (a :: Algorithm) where CounterStore :: TVar (C.Cache Text Text) -> InMemoryStore 'FixedWindow TokenBucketStore :: TVar (StmMap.Map Text TokenBucketEntry) -> InMemoryStore 'TokenBucket -- ... other algorithms
This prevents runtime errors like trying to use token bucket operations on a sliding window cache.
Supported Algorithms
Fixed Window
- Use Case: Simple request counting per time window
- Storage: JSON-serialized counters with TTL
- Performance: O(1) read/write operations
- Memory: Minimal overhead, automatic expiration
Sliding Window
- Use Case: Precise rate limiting with timestamp tracking
- Storage: Lists of request timestamps per key
- Performance: O(n) where n is requests in window
- Memory: Proportional to request frequency
Token Bucket
- Use Case: Bursty traffic with sustained rate limits
- Storage: Worker threads with STM-based state
- Performance: O(1) with background token refill
- Memory: Fixed per bucket, automatic cleanup
Leaky Bucket
- Use Case: Smooth rate limiting without bursts
- Storage: Continuous drain workers with STM state
- Performance: O(1) with background draining
- Memory: Fixed per bucket, automatic cleanup
TinyLRU
- Use Case: Bounded cache with LRU eviction
- Storage: In-memory LRU cache with expiration
- Performance: O(1) average case operations
- Memory: Bounded by cache size limit
Example Usage
Creating Algorithm-Specific Caches
import Keter.RateLimiter.Cache import Data.Proxy -- Type-safe cache creation tokenCache <- do store <- createInMemoryStore @'TokenBucket return $ newCache TokenBucket store fixedWindowCache <- do store <- createInMemoryStore @'FixedWindow return $ newCache FixedWindow store
Basic Operations
-- Write/Read operations (type-safe based on algorithm) writeCache tokenCache "user123" initialTokenState 3600 maybeState <- readCache tokenCache "user123" -- Increment operations for counter-based algorithms newCount <- incrementCache fixedWindowCache "api_key" 60
Advanced Usage with Custom Keys
-- Composite key generation let userKey = makeCacheKey "throttle1" TokenBucket "zone1" "user456" writeCache tokenCache userKey state 7200 -- Cleanup and reset cacheReset tokenCache -- Clear all entries clearInMemoryStore store -- Direct store cleanup
Thread Safety and Concurrency
All operations are thread-safe using Software Transactional Memory (STM):
- Atomic Operations: All read/write operations are atomic
- Lock-Free: No explicit locking, uses STM for coordination
- Concurrent Access: Multiple threads can safely access same cache
- Worker Threads: Token/Leaky bucket algorithms use background workers
- Auto-Purging: Background threads clean up expired entries
Performance Characteristics
Time Complexity
- Fixed Window: O(1) for all operations
- Sliding Window: O(n) for timestamp list operations
- Token Bucket: O(1) with background O(1) refill
- Leaky Bucket: O(1) with background O(1) drain
- TinyLRU: O(1) average case, O(n) worst case
Space Complexity
- Fixed Window: O(k) where k is number of active keys
- Sliding Window: O(k*n) where n is requests per window
- Token Bucket: O(k) with fixed per-bucket overhead
- Leaky Bucket: O(k) with fixed per-bucket overhead
- TinyLRU: O(min(k, cache_size)) bounded by cache limit
Error Handling
The module provides robust error handling:
- Serialization Errors: Graceful handling of JSON encode/decode failures
- Type Safety: Compile-time prevention of algorithm mismatches
- Resource Cleanup: Automatic cleanup of failed operations
- Thread Exceptions: Worker threads handle exceptions gracefully
Synopsis
- data Algorithm
- data Cache store = Cache {
- cacheAlgorithm :: Algorithm
- cacheStore :: store
- class MonadIO m => CacheStore store v (m :: Type -> Type) | store -> v where
- data InMemoryStore (a :: Algorithm) where
- CounterStore :: TVar (Cache Text Text) -> InMemoryStore 'FixedWindow
- TimestampStore :: TVar (Map Text [Double]) -> InMemoryStore 'SlidingWindow
- TokenBucketStore :: TVar (Map Text TokenBucketEntry) -> InMemoryStore 'TokenBucket
- LeakyBucketStore :: TVar (Map Text LeakyBucketEntry) -> InMemoryStore 'LeakyBucket
- TinyLRUStore :: forall s. TVar (TinyLRUCache s) -> InMemoryStore 'TinyLRU
- class ResettableStore store where
- resetStore :: store -> IO ()
- class CreateStore (a :: Algorithm) where
- createStore :: IO (InMemoryStore a)
- readCache :: CacheStore store v IO => Cache store -> Text -> IO (Maybe v)
- writeCache :: CacheStore store v IO => Cache store -> Text -> v -> Int -> IO ()
- deleteCache :: CacheStore store v IO => Cache store -> Text -> IO ()
- incrementCache :: (CacheStore store v IO, FromJSON v, ToJSON v, Ord v, Num v) => Cache store -> Text -> Int -> IO v
- newCache :: Algorithm -> store -> Cache store
- createInMemoryStore :: forall (a :: Algorithm). CreateStore a => IO (InMemoryStore a)
- clearInMemoryStore :: ResettableStore store => store -> IO ()
- cacheReset :: ResettableStore store => Cache store -> IO ()
- algorithmPrefix :: Algorithm -> Text
- makeCacheKey :: Text -> Algorithm -> Text -> Text -> Text
- secondsToTimeSpec :: Int -> IO TimeSpec
- startAutoPurge :: Cache Text v -> Integer -> IO ()
- startCustomPurgeTokenBucket :: Map Text TokenBucketEntry -> Integer -> Integer -> IO ThreadId
- startCustomPurgeLeakyBucket :: Map Text LeakyBucketEntry -> Integer -> Integer -> IO ThreadId
- startTokenBucketWorker :: TVar TokenBucketState -> TQueue (MVar Bool) -> Int -> Double -> TMVar () -> IO ()
- startLeakyBucketWorker :: TVar LeakyBucketState -> TQueue (TMVar Bool) -> Int -> Double -> IO ()
- createTokenBucketEntry :: TokenBucketState -> IO TokenBucketEntry
- createLeakyBucketEntry :: LeakyBucketState -> IO LeakyBucketEntry
- algoToText :: Algorithm -> Text
- parseAlgoText :: Text -> Parser Algorithm
Core Types
Algorithm Specification
Enumeration of supported rate limiting algorithms.
Each algorithm represents a different approach to rate limiting with distinct characteristics, use cases, and performance profiles. The type is promoted to the kind level using DataKinds for compile-time algorithm verification.
Algorithm Characteristics Comparison
Algorithm | Bursts | Precision | Memory | Use Case ---------------|--------|-----------|-----------|------------------------- FixedWindow | Yes | Low | Minimal | Simple API rate limiting SlidingWindow | Smooth | High | Variable | Precise traffic shaping TokenBucket | Yes | Medium | Fixed | Bursty API with sustained limits LeakyBucket | No | High | Fixed | Smooth streaming/bandwidth TinyLRU | NA | NA | Bounded | General caching with eviction
Detailed Algorithm Descriptions
- FixedWindow: Divides time into fixed intervals, counts requests per interval
- SlidingWindow: Maintains precise timestamps, allows smooth rate distribution
- TokenBucket: Accumulates tokens over time, consumes tokens per request
- LeakyBucket: Continuous leak rate, requests fill the bucket
- TinyLRU: Least-Recently-Used cache with size bounds and TTL
Constructors
FixedWindow | |
SlidingWindow | |
TokenBucket | |
LeakyBucket | |
TinyLRU |
Cache wrapper that combines an algorithm specification with a storage backend.
The cache type provides a unified interface while maintaining algorithm-specific behavior through the type system. It encapsulates both the algorithm logic and the underlying storage implementation.
Type Parameters
The store
parameter represents the storage backend type (e.g., InMemoryStore
, Redis, etc.)
The algorithm is captured in the store type for type safety
Example Usage
-- Create a token bucket cache tokenStore <- createInMemoryStore @'TokenBucket let tokenCache = Cache TokenBucket tokenStore -- Create a fixed window cache counterStore <- createInMemoryStore @'FixedWindow let counterCache = Cache FixedWindow counterStore
Constructors
Cache | |
Fields
|
Storage Abstraction
class MonadIO m => CacheStore store v (m :: Type -> Type) | store -> v where Source #
Typeclass abstracting cache storage backends with functional dependencies.
This typeclass provides a uniform interface for different storage implementations
while allowing each backend to specify its supported value types. The functional
dependency store -> v
ensures that each store type uniquely determines its
value type, providing additional type safety.
Design Principles
- Type Safety: Functional dependencies prevent type mismatches
- Flexibility: Support for different storage backends (memory, Redis, etc.)
- Performance: Allow backend-specific optimizations
- Consistency: Uniform interface across all implementations
Default Implementations
The typeclass provides sensible defaults for increment operations, but backends can override for performance optimizations:
-- Default increment: read, modify, write incStore store prefix key expires = do mval <- readStore store prefix key let newVal = maybe 1 (+1) mval writeStore store prefix key newVal expires return newVal
Atomicity Guarantees
Implementations should provide atomicity guarantees appropriate for their backend:
- STM-based stores: Full ACID transactions
- Memory stores: Process-level atomicity
- Distributed stores: Network-level consistency
Minimal complete definition
Methods
Arguments
:: store | Storage backend instance |
-> Text | Key prefix (algorithm-specific) |
-> Text | Full cache key |
-> m (Maybe v) | Retrieved value, or Nothing if not found |
Read a value from the store.
result <- readStore store "rate_limiter" "api_key_123" -- result: Maybe Int (for counter-based algorithms)
Arguments
:: store | Storage backend instance |
-> Text | Key prefix (algorithm-specific) |
-> Text | Full cache key |
-> v | Value to store |
-> Int | TTL in seconds |
-> m () |
Write a value to the store with expiration.
writeStore store "token_bucket" "user_456" bucketState 3600 -- Stores bucket state with 1-hour TTL
Arguments
:: store | Storage backend instance |
-> Text | Key prefix (algorithm-specific) |
-> Text | Full cache key |
-> m () |
Delete a key from the store.
deleteStore store "timestamps" "ip_192_168_1_1" -- Removes sliding window timestamps for IP
Arguments
:: store | Storage backend instance |
-> Text | Key prefix (algorithm-specific) |
-> Text | Full cache key |
-> Int | TTL in seconds for the incremented value |
-> m v | New value after increment |
Atomically increment a numeric value.
Provides atomic increment-or-initialize semantics. If the key doesn't exist, initializes to 1. If it exists, increments by 1. Essential for counter-based rate limiting algorithms.
newCount <- incStore store "rate_limiter" "api_throttle" 60 -- Returns new count after increment, with 60-second TTL
Instances
CacheStore (InMemoryStore 'FixedWindow) Int IO Source # | CacheStore instances CacheStore instance for FixedWindow algorithm using integer counters. Implements counter-based rate limiting with JSON serialization and TTL support. Uses Data.Cache for automatic expiration and efficient storage. Storage Format
AtomicityIncrement operations use STM for thread-safe atomic updates, ensuring accurate counting even under high concurrency. |
Defined in Keter.RateLimiter.Cache Methods readStore :: InMemoryStore 'FixedWindow -> Text -> Text -> IO (Maybe Int) Source # writeStore :: InMemoryStore 'FixedWindow -> Text -> Text -> Int -> Int -> IO () Source # deleteStore :: InMemoryStore 'FixedWindow -> Text -> Text -> IO () Source # incStore :: InMemoryStore 'FixedWindow -> Text -> Text -> Int -> IO Int Source # | |
CacheStore (InMemoryStore 'LeakyBucket) LeakyBucketState IO Source # | CacheStore instance for LeakyBucket algorithm. Similar to TokenBucket but for continuous drain semantics. Manages leaky bucket state and worker thread lifecycle. |
Defined in Keter.RateLimiter.Cache Methods readStore :: InMemoryStore 'LeakyBucket -> Text -> Text -> IO (Maybe LeakyBucketState) Source # writeStore :: InMemoryStore 'LeakyBucket -> Text -> Text -> LeakyBucketState -> Int -> IO () Source # deleteStore :: InMemoryStore 'LeakyBucket -> Text -> Text -> IO () Source # incStore :: InMemoryStore 'LeakyBucket -> Text -> Text -> Int -> IO LeakyBucketState Source # | |
CacheStore (InMemoryStore 'TinyLRU) Int IO Source # | CacheStore instance for TinyLRU algorithm. Provides bounded cache with least-recently-used eviction and TTL support. Automatically handles expiration and LRU ordering updates. |
Defined in Keter.RateLimiter.Cache Methods readStore :: InMemoryStore 'TinyLRU -> Text -> Text -> IO (Maybe Int) Source # writeStore :: InMemoryStore 'TinyLRU -> Text -> Text -> Int -> Int -> IO () Source # deleteStore :: InMemoryStore 'TinyLRU -> Text -> Text -> IO () Source # incStore :: InMemoryStore 'TinyLRU -> Text -> Text -> Int -> IO Int Source # | |
CacheStore (InMemoryStore 'TokenBucket) TokenBucketState IO Source # | CacheStore instance for TokenBucket algorithm. Provides access to token bucket state while maintaining the worker thread infrastructure. Read operations return current bucket state, write operations update state and manage worker lifecycle. |
Defined in Keter.RateLimiter.Cache Methods readStore :: InMemoryStore 'TokenBucket -> Text -> Text -> IO (Maybe TokenBucketState) Source # writeStore :: InMemoryStore 'TokenBucket -> Text -> Text -> TokenBucketState -> Int -> IO () Source # deleteStore :: InMemoryStore 'TokenBucket -> Text -> Text -> IO () Source # incStore :: InMemoryStore 'TokenBucket -> Text -> Text -> Int -> IO TokenBucketState Source # | |
CacheStore (InMemoryStore 'SlidingWindow) [Double] IO Source # | CacheStore instance for SlidingWindow algorithm using timestamp lists. Stores lists of request timestamps for precise sliding window calculations. Does not use TTL as timestamps are managed by the sliding window logic. |
Defined in Keter.RateLimiter.Cache Methods readStore :: InMemoryStore 'SlidingWindow -> Text -> Text -> IO (Maybe [Double]) Source # writeStore :: InMemoryStore 'SlidingWindow -> Text -> Text -> [Double] -> Int -> IO () Source # deleteStore :: InMemoryStore 'SlidingWindow -> Text -> Text -> IO () Source # incStore :: InMemoryStore 'SlidingWindow -> Text -> Text -> Int -> IO [Double] Source # |
data InMemoryStore (a :: Algorithm) where Source #
Algorithm-parameterized in-memory storage using GADTs.
This type uses GADTs (Generalized Algebraic Data Types) to provide compile-time guarantees that each algorithm uses appropriate storage structures. The phantom type parameter ensures that token bucket operations can't be used on sliding window stores, etc.
GADT Benefits
- Type Safety: Prevents algorithm/storage mismatches at compile time
- Performance: Specialized storage for each algorithm's needs
- Extensibility: Easy to add new algorithms with appropriate storage
- Documentation: Types serve as executable documentation
Storage Specialization
Each algorithm gets optimized storage:
- Counters: Simple key-value cache with TTL
- Timestamps: STM Map of timestamp lists
- Token Buckets: STM Map of worker entries with background threads
- Leaky Buckets: STM Map with continuous drain workers
- TinyLRU: Bounded LRU cache with automatic eviction
Memory Management
- Token and Leaky bucket stores include automatic purging
- TinyLRU provides bounded memory usage
- Counter stores use TTL-based expiration
- All stores support manual reset for cleanup
Constructors
CounterStore :: TVar (Cache Text Text) -> InMemoryStore 'FixedWindow | Counter-based storage for fixed window algorithm. Uses |
TimestampStore :: TVar (Map Text [Double]) -> InMemoryStore 'SlidingWindow | Timestamp list storage for sliding window algorithm. Maintains lists of request timestamps per key. Enables precise rate calculation by examining timestamps within the sliding time window. |
TokenBucketStore :: TVar (Map Text TokenBucketEntry) -> InMemoryStore 'TokenBucket | Token bucket entry storage with worker thread management. Each entry includes bucket state, request queue, and worker synchronization. Automatically starts purge threads to clean up inactive buckets. |
LeakyBucketStore :: TVar (Map Text LeakyBucketEntry) -> InMemoryStore 'LeakyBucket | Leaky bucket entry storage with continuous drain workers. Similar to token buckets but with continuous drain semantics. Each bucket has a worker thread that continuously drains at the specified rate. |
TinyLRUStore :: forall s. TVar (TinyLRUCache s) -> InMemoryStore 'TinyLRU | Bounded LRU cache storage. Provides fixed-size cache with least-recently-used eviction. Suitable for scenarios where memory bounds are more important than precise rate limiting. |
Instances
ResettableStore (InMemoryStore a) Source # | ResettableStore instances ResettableStore instances for all InMemoryStore variants. Provides uniform reset behavior across all algorithm-specific stores. Each implementation handles algorithm-specific cleanup requirements. |
Defined in Keter.RateLimiter.Cache Methods resetStore :: InMemoryStore a -> IO () Source # | |
CacheStore (InMemoryStore 'FixedWindow) Int IO Source # | CacheStore instances CacheStore instance for FixedWindow algorithm using integer counters. Implements counter-based rate limiting with JSON serialization and TTL support. Uses Data.Cache for automatic expiration and efficient storage. Storage Format
AtomicityIncrement operations use STM for thread-safe atomic updates, ensuring accurate counting even under high concurrency. |
Defined in Keter.RateLimiter.Cache Methods readStore :: InMemoryStore 'FixedWindow -> Text -> Text -> IO (Maybe Int) Source # writeStore :: InMemoryStore 'FixedWindow -> Text -> Text -> Int -> Int -> IO () Source # deleteStore :: InMemoryStore 'FixedWindow -> Text -> Text -> IO () Source # incStore :: InMemoryStore 'FixedWindow -> Text -> Text -> Int -> IO Int Source # | |
CacheStore (InMemoryStore 'LeakyBucket) LeakyBucketState IO Source # | CacheStore instance for LeakyBucket algorithm. Similar to TokenBucket but for continuous drain semantics. Manages leaky bucket state and worker thread lifecycle. |
Defined in Keter.RateLimiter.Cache Methods readStore :: InMemoryStore 'LeakyBucket -> Text -> Text -> IO (Maybe LeakyBucketState) Source # writeStore :: InMemoryStore 'LeakyBucket -> Text -> Text -> LeakyBucketState -> Int -> IO () Source # deleteStore :: InMemoryStore 'LeakyBucket -> Text -> Text -> IO () Source # incStore :: InMemoryStore 'LeakyBucket -> Text -> Text -> Int -> IO LeakyBucketState Source # | |
CacheStore (InMemoryStore 'TinyLRU) Int IO Source # | CacheStore instance for TinyLRU algorithm. Provides bounded cache with least-recently-used eviction and TTL support. Automatically handles expiration and LRU ordering updates. |
Defined in Keter.RateLimiter.Cache Methods readStore :: InMemoryStore 'TinyLRU -> Text -> Text -> IO (Maybe Int) Source # writeStore :: InMemoryStore 'TinyLRU -> Text -> Text -> Int -> Int -> IO () Source # deleteStore :: InMemoryStore 'TinyLRU -> Text -> Text -> IO () Source # incStore :: InMemoryStore 'TinyLRU -> Text -> Text -> Int -> IO Int Source # | |
CacheStore (InMemoryStore 'TokenBucket) TokenBucketState IO Source # | CacheStore instance for TokenBucket algorithm. Provides access to token bucket state while maintaining the worker thread infrastructure. Read operations return current bucket state, write operations update state and manage worker lifecycle. |
Defined in Keter.RateLimiter.Cache Methods readStore :: InMemoryStore 'TokenBucket -> Text -> Text -> IO (Maybe TokenBucketState) Source # writeStore :: InMemoryStore 'TokenBucket -> Text -> Text -> TokenBucketState -> Int -> IO () Source # deleteStore :: InMemoryStore 'TokenBucket -> Text -> Text -> IO () Source # incStore :: InMemoryStore 'TokenBucket -> Text -> Text -> Int -> IO TokenBucketState Source # | |
CacheStore (InMemoryStore 'SlidingWindow) [Double] IO Source # | CacheStore instance for SlidingWindow algorithm using timestamp lists. Stores lists of request timestamps for precise sliding window calculations. Does not use TTL as timestamps are managed by the sliding window logic. |
Defined in Keter.RateLimiter.Cache Methods readStore :: InMemoryStore 'SlidingWindow -> Text -> Text -> IO (Maybe [Double]) Source # writeStore :: InMemoryStore 'SlidingWindow -> Text -> Text -> [Double] -> Int -> IO () Source # deleteStore :: InMemoryStore 'SlidingWindow -> Text -> Text -> IO () Source # incStore :: InMemoryStore 'SlidingWindow -> Text -> Text -> Int -> IO [Double] Source # |
class ResettableStore store where Source #
Typeclass for storage backends that support complete reset operations.
Provides a way to clear all data from a store, useful for testing, maintenance, and emergency reset scenarios. Implementations should ensure thread safety and atomic reset behavior.
Use Cases
- Testing: Clean state between test runs
- Maintenance: Clear corrupted or stale data
- Memory Management: Recover from memory pressure
- Configuration Changes: Reset after algorithm parameter changes
Example
-- Reset all rate limiting data resetStore myTokenBucketStore -- Reset entire cache cacheReset myCache
Methods
resetStore :: store -> IO () Source #
Clear all entries from the store.
Should be atomic and thread-safe. After reset, the store should behave as if it were newly created.
Instances
ResettableStore (InMemoryStore a) Source # | ResettableStore instances ResettableStore instances for all InMemoryStore variants. Provides uniform reset behavior across all algorithm-specific stores. Each implementation handles algorithm-specific cleanup requirements. |
Defined in Keter.RateLimiter.Cache Methods resetStore :: InMemoryStore a -> IO () Source # |
class CreateStore (a :: Algorithm) where Source #
Typeclass for creating algorithm-specific storage instances.
Uses type-level programming to ensure each algorithm gets appropriate storage. The phantom type parameter prevents creation of incompatible store types.
Type-Level Dispatch
-- Compiler ensures correct store type tokenStore <- createStore @'TokenBucket -- Creates TokenBucketStore counterStore <- createStore @'FixedWindow -- Creates CounterStore -- This would be a compile error: -- tokenStore <- createStore @'SlidingWindow -- Type mismatch!
Automatic Services
Some storage types automatically start background services:
- Token/Leaky buckets: Auto-purge threads for inactive entries
- Counter stores: TTL-based expiration threads
- Timestamp stores: Manual cleanup required
- TinyLRU: Built-in eviction on size limits
Methods
createStore :: IO (InMemoryStore a) Source #
Create a new storage instance for the specified algorithm.
Initializes all necessary data structures and background services. The created store is immediately ready for use.
Instances
CreateStore 'FixedWindow Source # | Create store instances for each Algorithm. |
Defined in Keter.RateLimiter.Cache Methods createStore :: IO (InMemoryStore 'FixedWindow) Source # | |
CreateStore 'LeakyBucket Source # | |
Defined in Keter.RateLimiter.Cache Methods createStore :: IO (InMemoryStore 'LeakyBucket) Source # | |
CreateStore 'SlidingWindow Source # | |
Defined in Keter.RateLimiter.Cache Methods | |
CreateStore 'TinyLRU Source # | |
Defined in Keter.RateLimiter.Cache Methods createStore :: IO (InMemoryStore 'TinyLRU) Source # | |
CreateStore 'TokenBucket Source # | |
Defined in Keter.RateLimiter.Cache Methods createStore :: IO (InMemoryStore 'TokenBucket) Source # |
Cache Operations
Basic Operations
Arguments
:: CacheStore store v IO | |
=> Cache store | Cache instance with algorithm and storage |
-> Text | Unprefixed key (e.g., "user123", "api_key_abc") |
-> IO (Maybe v) | Retrieved value with algorithm-appropriate type |
Read from cache using the algorithm-prefixed key.
Automatically applies the appropriate key prefix based on the cache's algorithm, then delegates to the storage backend's read operation. This ensures consistent key namespacing across all cache operations.
Key Transformation
-- For a TokenBucket cache with key "user123": -- Actual key used: "token_bucket:token_bucket:user123" -- ^^^^^^^^^^^^ ^^^^^^^^^^^^^^^^^^^^ -- prefix prefixed key
Type Safety
The return type is determined by the storage backend's CacheStore instance, ensuring you get the correct value type for the algorithm:
- FixedWindow:
Maybe Int
(counter values) - TokenBucket:
Maybe TokenBucketState
(bucket state) - SlidingWindow:
Maybe [Double]
(timestamp lists)
Example
-- Read token bucket state maybeState <- readCache tokenCache "user456" case maybeState of Nothing -> putStrLn "No bucket exists for user" Just state -> putStrLn $ "User has " ++ show (tokens state) ++ " tokens"
Arguments
:: CacheStore store v IO | |
=> Cache store | Cache instance |
-> Text | Unprefixed key |
-> v | Value to store (type must match store's expectation) |
-> Int | TTL in seconds (time until expiration) |
-> IO () | No return value, throws on error |
Write to cache using the algorithm-prefixed key.
Stores a value with automatic key prefixing and TTL handling. The value type must match what the storage backend expects for the cache's algorithm.
TTL Behavior
- Absolute TTL: Expiration time calculated from current time
- Background Cleanup: Most stores have automatic cleanup threads
- Precision: Uses monotonic clock for accurate timing
- Consistency: TTL behavior consistent across all algorithms
Example
-- Store token bucket state for 1 hour let initialState = TokenBucketState 100 currentTime writeCache tokenCache "new_user" initialState 3600 -- Store counter value for 5 minutes writeCache counterCache "api_limit" (42 :: Int) 300
Arguments
:: CacheStore store v IO | |
=> Cache store | Cache instance |
-> Text | Unprefixed key to delete |
-> IO () | No return value, silent if key doesn't exist |
Delete a key from cache using the algorithm-prefixed key.
Removes an entry from the cache, including any associated resources (worker threads, background tasks, etc.). The operation is atomic and thread-safe.
Resource Cleanup
- Token/Leaky Buckets: Terminates associated worker threads
- Counters: Simple key removal
- Timestamps: Clears timestamp lists
- LRU: Updates LRU ordering and frees space
Example
-- Remove user's rate limiting state deleteCache tokenCache "inactive_user" -- Clear API key's counter deleteCache counterCache "expired_api_key"
Arguments
:: (CacheStore store v IO, FromJSON v, ToJSON v, Ord v, Num v) | |
=> Cache store | Cache instance (must support numeric values) |
-> Text | Unprefixed key to increment |
-> Int | TTL in seconds for the incremented value |
-> IO v | New value after increment |
Increment a numeric cache value or initialise it if missing.
Provides atomic increment-or-initialize semantics essential for counter-based rate limiting. If the key doesn't exist, initializes to 1. If it exists, increments by 1. The operation is atomic even under high concurrency.
Atomicity Guarantees
- STM-based stores: Full transaction isolation
- Memory stores: Process-level atomicity
- Distributed stores: Backend-specific consistency
Error Handling
- Type Mismatch: Returns error if existing value isn't numeric
- Serialization: Handles JSON encoding/decoding failures gracefully
- Overflow: Behavior depends on numeric type (Int, Double, etc.)
Example
-- Increment API request counter newCount <- incrementCache apiCache "requests_per_minute" 60 when (newCount > 1000) $ throwError "Rate limit exceeded" -- Initialize or increment user action count actionCount <- incrementCache userCache "daily_actions" 86400
Cache Management
Arguments
:: Algorithm | The rate limiting algorithm this cache implements |
-> store | The storage backend (must be compatible with algorithm) |
-> Cache store | Complete cache instance ready for use |
Create a new cache with a given Algorithm and store.
This is the primary constructor for cache instances. It combines an algorithm specification with a storage backend to create a fully functional cache. The algorithm parameter is used for key prefixing and operation validation.
Design Rationale
- Separation of Concerns: Algorithm logic separate from storage implementation
- Flexibility: Same algorithm can use different storage backends
- Type Safety: Algorithm-store compatibility enforced by types
- Testability: Easy to mock storage for testing
Example
-- Create a token bucket cache with in-memory storage store <- createInMemoryStore @'TokenBucket let cache = newCache TokenBucket store -- Later operations use the unified cache interface writeCache cache "user123" initialState 3600 result <- readCache cache "user123"
createInMemoryStore :: forall (a :: Algorithm). CreateStore a => IO (InMemoryStore a) Source #
Create a new in-memory store for a specific rate-limiting algorithm.
This function provides a convenient, type-safe way to create algorithm-specific storage. It uses TypeApplications to specify which algorithm's store to create, ensuring compile-time correctness.
Type Safety Example
-- These are all valid and type-safe: tokenStore <- createInMemoryStore @'TokenBucket counterStore <- createInMemoryStore @'FixedWindow lruStore <- createInMemoryStore @'TinyLRU -- This would be a compile error (typo): -- badStore <- createInMemoryStore @'TokenBuckett -- Not a valid algorithm
Background Services
Some algorithms automatically start background services:
- TokenBucket/LeakyBucket: Purge threads for cleanup (60s interval, 1h TTL)
- FixedWindow: TTL-based expiration threads
- SlidingWindow/TinyLRU: No automatic background services
Example Usage
import Data.Proxy main = do -- Create stores for different algorithms tokenStore <- createInMemoryStore @'TokenBucket slidingStore <- createInMemoryStore @'SlidingWindow -- Use in cache creation let tokenCache = newCache TokenBucket tokenStore let slidingCache = newCache SlidingWindow slidingStore
Arguments
:: ResettableStore store | |
=> store | Storage instance to clear |
-> IO () | No return value, completes when reset is done |
Clear all entries in an in-memory store.
Provides a direct interface to the ResettableStore functionality. Useful when you need to reset storage without going through the cache wrapper.
Use Cases
- Testing: Clean slate between test cases
- Maintenance: Clear corrupted state
- Memory Management: Free up memory during low usage
- Reconfiguration: Reset before changing algorithm parameters
Thread Safety
The operation is atomic and thread-safe, but concurrent operations may see the reset at different times. Consider coordinating with other threads if precise timing is required.
Example
-- Direct store reset clearInMemoryStore myTokenBucketStore -- Conditional reset based on memory usage when memoryPressure $ clearInMemoryStore store
Arguments
:: ResettableStore store | |
=> Cache store | Cache instance to reset |
-> IO () | No return value, completes when reset is done |
Reset all entries in a cache.
Clears all data from the cache's storage backend. This is a convenience wrapper around clearInMemoryStore that works at the cache level rather than the storage level.
Behavior
- Complete Reset: All keys and values are removed
- Background Services: Worker threads and purge threads continue running
- Algorithm State: Any algorithm-specific state is cleared
- Immediate Effect: Reset is visible to all threads immediately
Example
-- Reset entire token bucket cache cacheReset tokenBucketCache -- Reset counter cache for new time period cacheReset apiCounterCache
Utility Functions
Key Management
Map each algorithm to its unique cache key prefix.
Prefixes prevent key collisions between different algorithms and provide clear identification of cached data types. Each algorithm uses a distinct namespace within the same storage backend.
Prefix Usage Pattern
-- Fixed window counter for API key "abc123" Key: "rate_limiter:api:abc123" -- Token bucket state for user "user456" Key: "token_bucket:user:user456" -- Sliding window timestamps for IP "192.168.1.1" Key: "timestamps:ip:192.168.1.1"
Example
ghci> algorithmPrefix TokenBucket "token_bucket" ghci> algorithmPrefix FixedWindow "rate_limiter"
Arguments
:: Text | Throttle name (unique per rule) |
-> Algorithm | Rate limiting algorithm |
-> Text | IP zone or region identifier |
-> Text | User key (user ID, IP address, API key, etc.) |
-> Text | Complete hierarchical cache key |
Compose a unique cache key from throttle name, algorithm, IP zone, and user identifier.
Creates hierarchical cache keys that prevent collisions and enable efficient organization of rate limiting data. The key format follows a consistent pattern across all algorithms.
Key Format
<algorithm>:<throttleName>:<ipZone>:<userKey>
Use Cases
- Multi-tenant Applications: Separate rate limits per tenant
- Geographic Zones: Different limits for different regions
- Service Tiers: Varied limits based on user subscription level
- API Versioning: Separate limits for different API versions
Benefits
- Collision Prevention: Hierarchical structure prevents key conflicts
- Query Efficiency: Pattern-based queries and cleanup
- Debugging: Clear key structure aids troubleshooting
- Monitoring: Easy to aggregate metrics by zone or user type
Example
-- Create key for API rate limiting let key = makeCacheKey "api_limit" TokenBucket "us-east-1" "user123" -- Result: "TokenBucket:api_limit:us-east-1:user123" -- Create key for login attempts let key = makeCacheKey "login_attempts" FixedWindow "global" "192.168.1.1" -- Result: "FixedWindow:login_attempts:global:192.168.1.1"
Time Utilities
Convert seconds to TimeSpec for use with Data.Cache.
Calculates an absolute future time by adding the specified duration to the current monotonic time. Used for setting TTL values in cache operations.
Monotonic Time Benefits
- Clock Adjustments: Unaffected by system clock changes
- Precision: Nanosecond resolution for accurate timing
- Performance: Fast system call with minimal overhead
- Reliability: Guaranteed monotonic progression
Example
-- Create 5-minute expiration time expiryTime <- secondsToTimeSpec 300 -- Use with cache operations C.insertSTM key value cache (Just expiryTime)
Background Services
Auto-Purging
Arguments
:: Cache Text v | The cache instance to purge. Can contain any value type |
-> Integer | Purge interval in seconds. Determines how frequently expired entries are removed. Shorter intervals provide more responsive cleanup but use more CPU. Typical values: 60-3600 seconds. |
-> IO () | Returns immediately. The purge thread runs in background indefinitely. |
Start a background thread that periodically purges expired entries from a generic cache.
This function creates a self-regulating purge thread that maintains precise timing intervals regardless of purge operation duration. It uses monotonic clock measurements to ensure accurate scheduling even under system load.
Timing Algorithm
The purge cycle works as follows:
- Start Timer: Record monotonic timestamp before purge
- Purge Operation: Call
purgeExpired
on the cache - Calculate Remaining: Subtract elapsed time from target interval
- Precise Sleep: Wait for exactly the remaining time
- Repeat: Continue with next cycle
Timing Precision
The algorithm ensures that purge cycles happen at regular intervals:
Target Interval: |----10s----|----10s----|----10s----| Actual Timing: |--9s purge-|1s wait|--8s purge--|2s wait| Result: Consistent 10-second intervals maintained
Performance Considerations
- Non-blocking: Returns immediately after starting background thread
- Self-correcting: Adapts sleep time based on actual purge duration
- Memory efficient: Only maintains minimal state for timing
- CPU friendly: Sleeps for majority of time between purges
Example Usage
import qualified Data.Cache as C import Data.Text -- Create cache with 30-minute TTL cache <- C.newCache (Just $ C.minutes 30) -- Purge expired entries every 5 minutes (300 seconds) startAutoPurge cache 300 -- Cache now automatically maintains itself -- Memory usage remains bounded regardless of request patterns
Thread Safety: Safe to call concurrently. Each call creates independent purge thread.
Resource Usage: Creates one background thread with minimal memory footprint.
Error Handling: Thread continues running even if individual purge operations fail.
startCustomPurgeTokenBucket :: Map Text TokenBucketEntry -> Integer -> Integer -> IO ThreadId Source #
Start a specialized purge thread for token bucket entries in an STM map.
This function provides a convenient wrapper around startCustomPurge
specifically
configured for TokenBucketEntry
cleanup. It handles the complexities of extracting
timestamps from token bucket state and properly cleaning up worker threads.
Token Bucket Specific Behavior
- Timestamp Extraction: Uses
lastUpdate
field fromTokenBucketState
- Worker Cleanup: Attempts to acquire worker lock and terminate threads
- Resource Release: Removes entry from STM map and frees all resources
TTL Behavior
Token buckets are considered expired when:
currentTime - lastUpdateTime >= ttlSeconds
This means buckets are purged based on when they were last used for rate limiting, not when they were created. Active buckets are never purged regardless of age.
Example Scenarios
-- High-frequency API with 5-minute cleanup cycles tokenBuckets <- StmMap.newIO threadId <- startCustomPurgeTokenBucket tokenBuckets 300 3600 -- 5min interval, 1hr TTL -- Low-frequency batch processing with daily cleanup batchBuckets <- StmMap.newIO threadId <- startCustomPurgeTokenBucket batchBuckets 86400 604800 -- 1day interval, 1week TTL
Thread Management: Returns ThreadId
for thread control (e.g., killThread
).
Memory Impact: Prevents unbounded memory growth in applications with dynamic rate limiting keys.
Performance: O(n) scan of all buckets, but typically runs infrequently during low-traffic periods.
stmMap
- STM map containing token bucket entries keyed by identifier. Typically uses API keys, user IDs, or IP addresses as keys. Map is scanned atomically during each purge cycle.intervalSeconds
- Purge interval in seconds. How often to scan for expired buckets. Balance between cleanup responsiveness and CPU usage. Recommended: 300-3600 seconds depending on traffic patterns.ttlSeconds
- TTL (time-to-live) in seconds. Buckets unused for this duration are considered expired and eligible for removal. Should be much larger than typical request intervals. Recommended: 3600-86400 seconds.
Returns thread ID of the background purge thread.
Can be used with killThread
to stop purging.
startCustomPurgeLeakyBucket :: Map Text LeakyBucketEntry -> Integer -> Integer -> IO ThreadId Source #
Start a specialized purge thread for leaky bucket entries in an STM map.
Similar to startCustomPurgeTokenBucket
but configured for LeakyBucketEntry
cleanup.
Handles the specific requirements of leaky bucket timestamp extraction and worker
thread management.
Leaky Bucket Specific Behavior
- Timestamp Precision: Uses
Double
timestamp fromLeakyBucketState
for sub-second accuracy - Continuous Time Model: Supports fractional timestamps for precise drain calculations
- Worker Cleanup: Terminates continuous drain worker threads properly
TTL Calculation
Leaky buckets are expired when:
currentTime - lastTime >= fromIntegral ttlSeconds
The lastTime
field represents the most recent bucket level update, providing
more precise expiration timing than integer-based systems.
Use Cases
- Streaming Applications: Rate limiting for continuous data flows
- Real-time APIs: Sub-second precision rate limiting
- Traffic Shaping: Network bandwidth management with smooth rates
Example Configuration
-- Real-time streaming with frequent cleanup streamBuckets <- StmMap.newIO threadId <- startCustomPurgeLeakyBucket streamBuckets 60 900 -- 1min interval, 15min TTL -- Network traffic shaping with moderate cleanup trafficBuckets <- StmMap.newIO threadId <- startCustomPurgeLeakyBucket trafficBuckets 600 7200 -- 10min interval, 2hr TTL
Precision: Sub-second timestamp accuracy for fine-grained rate control.
Cleanup Behavior: More aggressive cleanup suitable for high-frequency, short-lived connections.
stmMap
- STM map containing leaky bucket entries keyed by identifier. Keys typically represent connections, streams, or data flows. All entries are scanned atomically during purge operations.intervalSeconds
- Purge interval in seconds. Frequency of expired entry cleanup. For high-frequency applications, shorter intervals (60-600s) provide more responsive cleanup.ttlSeconds
- TTL in seconds. Buckets inactive for this duration are purged. Should account for typical connection/stream lifetime patterns. Shorter TTL (900-3600s) suitable for transient connections.
Returns thread ID for background purge thread management. Thread runs continuously until explicitly terminated.
Worker Threads
startTokenBucketWorker Source #
Arguments
:: TVar TokenBucketState | Shared bucket state (tokens + last update time).
This |
-> TQueue (MVar Bool) | Request queue containing |
-> Int | Maximum bucket capacity (maximum tokens that can be stored). This sets the upper limit for burst traffic handling. Must be positive. |
-> Double | Token refill rate in tokens per second. Determines the long-term sustainable request rate. Must be positive. Can be fractional (e.g., 0.5 = 1 token per 2 seconds). |
-> TMVar () | Synchronization variable to signal when worker is ready.
The worker writes to this |
-> IO () | Returns immediately after forking the worker thread. The actual worker runs in the background indefinitely. |
Start a dedicated worker thread for processing token bucket requests.
The worker runs in an infinite loop, processing requests from the provided queue. Each request is handled atomically: the bucket state is read, tokens are refilled based on elapsed time, a token is consumed if available, and the new state is written back.
Worker Lifecycle
- Startup: Worker thread is forked and signals readiness via
TMVar
- Processing Loop: Worker waits for requests, processes them atomically
- Response: Results are sent back to clients via
MVar
Token Refill Algorithm
Tokens are refilled using the formula:
newTokens = min capacity (currentTokens + refillRate * elapsedSeconds)
This ensures:
- Tokens are added proportionally to elapsed time
- Bucket capacity is never exceeded
- Sub-second precision for refill calculations
Atomic Request Processing
Each request is processed in a single STM transaction that:
- Reads current bucket state (
tokens
,lastUpdate
) - Calculates elapsed time since last update
- Computes available tokens after refill
- Attempts to consume one token if available
- Updates bucket state with new token count and timestamp
- Returns allow/deny decision
Error Handling
The worker is designed to be resilient:
- Time calculation errors are handled by using
floor
for integer conversion - Negative elapsed time (clock adjustments) results in no refill
- Worker continues running even if individual requests fail
Examples
-- Create a bucket for API rate limiting: 1000 requests/hour = ~0.278 req/sec let capacity = 100 -- Allow bursts up to 100 requests refillRate = 1000.0 / 3600.0 -- 1000 requests per hour initialState <- newTVarIO $ TokenBucketState capacity now requestQueue <- newTBroadcastTQueueIO readySignal <- newEmptyTMVarIO startTokenBucketWorker initialState requestQueue capacity refillRate readySignal
Thread Safety: All state updates are atomic via STM transactions.
Resource Usage: Creates one background thread that runs indefinitely.
startLeakyBucketWorker Source #
Arguments
:: TVar LeakyBucketState | Shared bucket state |
-> TQueue (TMVar Bool) | Request queue with STM responses |
-> Int | Bucket capacity (maximum level) |
-> Double | Leak rate (requests drained per second) |
-> IO () | Returns immediately, worker runs in background |
Leaky bucket worker thread implementation.
Implements the continuous drain algorithm for leaky buckets. Processes requests from a queue and updates bucket state based on elapsed time and leak rate.
Algorithm Details
- Drain Calculation: level' = max(0, level - elapsed * leakRate)
- Request Processing: level'' = level' + requestSize (typically 1)
- Capacity Check: allowed = level'' <= capacity
- State Update: Apply leak even on denial for accurate timing
Example
-- Start worker for streaming rate limiter startLeakyBucketWorker stateVar queue 100 2.0 -- Capacity: 100 requests, Leak rate: 2 requests/second
Entry Creation
createTokenBucketEntry Source #
Arguments
:: TokenBucketState | Initial bucket state (tokens, timestamp) |
-> IO TokenBucketEntry | Complete entry ready for use |
Helper function to create a TokenBucketEntry with proper TMVar initialization.
Creates a complete token bucket entry with all necessary components: state storage, request queue, and worker synchronization. This ensures proper initialization of all STM components.
Entry Components
- State TVar: Atomic storage for bucket state (tokens, last update)
- Request Queue: TQueue for client-worker communication
- Worker Lock: TMVar for coordinating worker thread lifecycle
Example
-- Create entry for new user bucket now floor <$ getPOSIXTime let initialState = TokenBucketState 100 now -- 100 tokens, current time entry <- createTokenBucketEntry initialState -- Entry is ready for insertion into STM map atomically $ StmMap.insert entry "user123" bucketMap
createLeakyBucketEntry Source #
Arguments
:: LeakyBucketState | Initial bucket state (level, timestamp) |
-> IO LeakyBucketEntry | Complete entry ready for use |
Helper function to create a LeakyBucketEntry with proper TMVar initialization.
Similar to createTokenBucketEntry but for leaky bucket algorithm. Creates all necessary STM components for leaky bucket operation with continuous drain semantics.
Entry Components
- State TVar: Atomic storage for bucket level and last update time
- Request Queue: TQueue using TMVar for STM-based responses
- Worker Lock: TMVar for worker thread coordination
Example
-- Create entry for streaming connection now realToFrac <$ getPOSIXTime let initialState = LeakyBucketState 0.0 now -- Empty bucket, current time entry <- createLeakyBucketEntry initialState -- Entry ready for continuous drain processing atomically $ StmMap.insert entry "stream123" bucketMap
Algorithm utilities
Convert an Algorithm value to its canonical Text representation.
This function provides a standardized textual representation of rate limiting algorithms for serialization, logging, and configuration files. Each algorithm has exactly one canonical PascalCase representation matching the constructor names.
Output Format
FixedWindow → FixedWindow SlidingWindow → SlidingWindow TokenBucket → TokenBucket LeakyBucket → LeakyBucket TinyLRU → TinyLRU
Examples
-- Basic usage algoToText TokenBucket -- TokenBucket -- Configuration serialization data RateLimitConfig = RateLimitConfig { algorithm :: Text, limit :: Int, window :: Int } config = RateLimitConfig (algoToText SlidingWindow) 1000 3600 -- Logging logInfo $ "Using " <> algoToText currentAlgo <> " rate limiting"
This function is pure, thread-safe, and forms a reversible pair with parseAlgoText
.
Time complexity: O(1), Space complexity: O(1).
Parse a Text representation back into an Algorithm value.
Provides flexible parsing with case-insensitive matching and hyphenated format support. Returns an Aeson Parser for seamless JSON integration with rich error reporting.
Supported Formats
Algorithm │ Accepted Inputs (case-insensitive) ──────────────┼─────────────────────────────────── FixedWindow │ "fixedwindow", "fixed-window" SlidingWindow │ "slidingwindow", "sliding-window" TokenBucket │ "tokenbucket", "token-bucket" LeakyBucket │ "leakybucket", "leaky-bucket" TinyLRU │ "tinylru", "tiny-lru"
Examples
-- JSON parsing instance FromJSON RateLimitConfig where parseJSON = withObject RateLimitConfig $ \o -> RateLimitConfig $ (o .: "algorithm" >>= parseAlgoText) * o .: "limit" -- Configuration file (accepts flexible formats) parseAlgoText "token-bucket" -- Success TokenBucket parseAlgoText "SLIDING-WINDOW" -- Success SlidingWindow parseAlgoText "invalid" -- Error "Unknown algorithm: invalid"
Error Handling
Calls fail
with descriptive error messages for invalid inputs. In aeson's
Parser context, this provides rich error reporting with parsing context.
Round-trip Property
forall algo. parseAlgoText (algoToText algo) == Success algo
This function is pure, thread-safe, with O(1) time complexity after O(n) normalization.