{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE DataKinds #-}
module Keter.RateLimiter.CacheWithZone
(
incStoreWithZone
, readCacheWithZone
, writeCacheWithZone
, deleteCacheWithZone
, allowFixedWindowRequest
) where
import Data.Aeson (ToJSON, FromJSON)
import Data.Text (Text)
import Keter.RateLimiter.Cache
allowFixedWindowRequest
:: Cache (InMemoryStore 'FixedWindow)
-> Text
-> Text
-> Text
-> Int
-> Int
-> IO Bool
allowFixedWindowRequest :: Cache (InMemoryStore 'FixedWindow)
-> Text -> Text -> Text -> Int -> Int -> IO Bool
allowFixedWindowRequest Cache (InMemoryStore 'FixedWindow)
cache Text
throttleName Text
ipZone Text
userKey Int
limit Int
period = do
Int
count <- Cache (InMemoryStore 'FixedWindow)
-> Text -> Text -> Text -> Int -> IO Int
forall store v.
(CacheStore store v IO, FromJSON v, ToJSON v, Num v, Ord v) =>
Cache store -> Text -> Text -> Text -> Int -> IO v
incStoreWithZone Cache (InMemoryStore 'FixedWindow)
cache Text
throttleName Text
ipZone Text
userKey Int
period
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ Int
count Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
limit
incStoreWithZone
:: (CacheStore store v IO, FromJSON v, ToJSON v, Num v, Ord v)
=> Cache store
-> Text
-> Text
-> Text
-> Int
-> IO v
incStoreWithZone :: forall store v.
(CacheStore store v IO, FromJSON v, ToJSON v, Num v, Ord v) =>
Cache store -> Text -> Text -> Text -> Int -> IO v
incStoreWithZone Cache store
cache Text
throttleName Text
ipZone Text
userKey Int
expiresIn = do
let key :: Text
key = Text -> Algorithm -> Text -> Text -> Text
makeCacheKey Text
throttleName (Cache store -> Algorithm
forall store. Cache store -> Algorithm
cacheAlgorithm Cache store
cache) Text
ipZone Text
userKey
prefix :: Text
prefix = Algorithm -> Text
algorithmPrefix (Cache store -> Algorithm
forall store. Cache store -> Algorithm
cacheAlgorithm Cache store
cache)
store -> Text -> Text -> Int -> IO v
forall store v (m :: * -> *).
(CacheStore store v m, FromJSON v, ToJSON v, Ord v, Num v) =>
store -> Text -> Text -> Int -> m v
incStore (Cache store -> store
forall store. Cache store -> store
cacheStore Cache store
cache) Text
prefix Text
key Int
expiresIn
readCacheWithZone
:: (CacheStore store v IO)
=> Cache store
-> Text
-> Text
-> Text
-> IO (Maybe v)
readCacheWithZone :: forall store v.
CacheStore store v IO =>
Cache store -> Text -> Text -> Text -> IO (Maybe v)
readCacheWithZone Cache store
cache Text
throttleName Text
ipZone Text
userKey = do
let key :: Text
key = Text -> Algorithm -> Text -> Text -> Text
makeCacheKey Text
throttleName (Cache store -> Algorithm
forall store. Cache store -> Algorithm
cacheAlgorithm Cache store
cache) Text
ipZone Text
userKey
prefix :: Text
prefix = Algorithm -> Text
algorithmPrefix (Cache store -> Algorithm
forall store. Cache store -> Algorithm
cacheAlgorithm Cache store
cache)
store -> Text -> Text -> IO (Maybe v)
forall store v (m :: * -> *).
CacheStore store v m =>
store -> Text -> Text -> m (Maybe v)
readStore (Cache store -> store
forall store. Cache store -> store
cacheStore Cache store
cache) Text
prefix Text
key
writeCacheWithZone
:: (CacheStore store v IO)
=> Cache store
-> Text
-> Text
-> Text
-> v
-> Int
-> IO ()
writeCacheWithZone :: forall store v.
CacheStore store v IO =>
Cache store -> Text -> Text -> Text -> v -> Int -> IO ()
writeCacheWithZone Cache store
cache Text
throttleName Text
ipZone Text
userKey v
val Int
expiresIn = do
let key :: Text
key = Text -> Algorithm -> Text -> Text -> Text
makeCacheKey Text
throttleName (Cache store -> Algorithm
forall store. Cache store -> Algorithm
cacheAlgorithm Cache store
cache) Text
ipZone Text
userKey
prefix :: Text
prefix = Algorithm -> Text
algorithmPrefix (Cache store -> Algorithm
forall store. Cache store -> Algorithm
cacheAlgorithm Cache store
cache)
store -> Text -> Text -> v -> Int -> IO ()
forall store v (m :: * -> *).
CacheStore store v m =>
store -> Text -> Text -> v -> Int -> m ()
writeStore (Cache store -> store
forall store. Cache store -> store
cacheStore Cache store
cache) Text
prefix Text
key v
val Int
expiresIn
deleteCacheWithZone
:: (CacheStore store v IO)
=> Cache store
-> Text
-> Text
-> Text
-> IO ()
deleteCacheWithZone :: forall store v.
CacheStore store v IO =>
Cache store -> Text -> Text -> Text -> IO ()
deleteCacheWithZone Cache store
cache Text
throttleName Text
ipZone Text
userKey = do
let key :: Text
key = Text -> Algorithm -> Text -> Text -> Text
makeCacheKey Text
throttleName (Cache store -> Algorithm
forall store. Cache store -> Algorithm
cacheAlgorithm Cache store
cache) Text
ipZone Text
userKey
prefix :: Text
prefix = Algorithm -> Text
algorithmPrefix (Cache store -> Algorithm
forall store. Cache store -> Algorithm
cacheAlgorithm Cache store
cache)
store -> Text -> Text -> IO ()
forall store v (m :: * -> *).
CacheStore store v m =>
store -> Text -> Text -> m ()
deleteStore (Cache store -> store
forall store. Cache store -> store
cacheStore Cache store
cache) Text
prefix Text
key