{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
module Keter.RateLimiter.Types
(
TokenBucketState(..)
, LeakyBucketState(..)
) where
import Data.Aeson (ToJSON, FromJSON(..), withObject, (.:))
import Control.Monad (when)
import GHC.Generics (Generic)
data TokenBucketState = TokenBucketState
{ TokenBucketState -> Int
tokens :: Int
, TokenBucketState -> Int
lastUpdate :: Int
} deriving (Int -> TokenBucketState -> ShowS
[TokenBucketState] -> ShowS
TokenBucketState -> String
(Int -> TokenBucketState -> ShowS)
-> (TokenBucketState -> String)
-> ([TokenBucketState] -> ShowS)
-> Show TokenBucketState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TokenBucketState -> ShowS
showsPrec :: Int -> TokenBucketState -> ShowS
$cshow :: TokenBucketState -> String
show :: TokenBucketState -> String
$cshowList :: [TokenBucketState] -> ShowS
showList :: [TokenBucketState] -> ShowS
Show, TokenBucketState -> TokenBucketState -> Bool
(TokenBucketState -> TokenBucketState -> Bool)
-> (TokenBucketState -> TokenBucketState -> Bool)
-> Eq TokenBucketState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TokenBucketState -> TokenBucketState -> Bool
== :: TokenBucketState -> TokenBucketState -> Bool
$c/= :: TokenBucketState -> TokenBucketState -> Bool
/= :: TokenBucketState -> TokenBucketState -> Bool
Eq, (forall x. TokenBucketState -> Rep TokenBucketState x)
-> (forall x. Rep TokenBucketState x -> TokenBucketState)
-> Generic TokenBucketState
forall x. Rep TokenBucketState x -> TokenBucketState
forall x. TokenBucketState -> Rep TokenBucketState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TokenBucketState -> Rep TokenBucketState x
from :: forall x. TokenBucketState -> Rep TokenBucketState x
$cto :: forall x. Rep TokenBucketState x -> TokenBucketState
to :: forall x. Rep TokenBucketState x -> TokenBucketState
Generic)
instance ToJSON TokenBucketState
instance FromJSON TokenBucketState where
parseJSON :: Value -> Parser TokenBucketState
parseJSON = String
-> (Object -> Parser TokenBucketState)
-> Value
-> Parser TokenBucketState
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TokenBucketState" ((Object -> Parser TokenBucketState)
-> Value -> Parser TokenBucketState)
-> (Object -> Parser TokenBucketState)
-> Value
-> Parser TokenBucketState
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Int
tokens <- Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tokens"
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int
tokens Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0) (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ String -> Parser ()
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"tokens must be non-negative"
Int
lastUpdate <- Object
o Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"lastUpdate"
TokenBucketState -> Parser TokenBucketState
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return TokenBucketState { Int
tokens :: Int
tokens :: Int
tokens, Int
lastUpdate :: Int
lastUpdate :: Int
lastUpdate }
data LeakyBucketState = LeakyBucketState
{ LeakyBucketState -> Double
level :: Double
, LeakyBucketState -> Double
lastTime :: Double
} deriving (Int -> LeakyBucketState -> ShowS
[LeakyBucketState] -> ShowS
LeakyBucketState -> String
(Int -> LeakyBucketState -> ShowS)
-> (LeakyBucketState -> String)
-> ([LeakyBucketState] -> ShowS)
-> Show LeakyBucketState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LeakyBucketState -> ShowS
showsPrec :: Int -> LeakyBucketState -> ShowS
$cshow :: LeakyBucketState -> String
show :: LeakyBucketState -> String
$cshowList :: [LeakyBucketState] -> ShowS
showList :: [LeakyBucketState] -> ShowS
Show, LeakyBucketState -> LeakyBucketState -> Bool
(LeakyBucketState -> LeakyBucketState -> Bool)
-> (LeakyBucketState -> LeakyBucketState -> Bool)
-> Eq LeakyBucketState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LeakyBucketState -> LeakyBucketState -> Bool
== :: LeakyBucketState -> LeakyBucketState -> Bool
$c/= :: LeakyBucketState -> LeakyBucketState -> Bool
/= :: LeakyBucketState -> LeakyBucketState -> Bool
Eq, (forall x. LeakyBucketState -> Rep LeakyBucketState x)
-> (forall x. Rep LeakyBucketState x -> LeakyBucketState)
-> Generic LeakyBucketState
forall x. Rep LeakyBucketState x -> LeakyBucketState
forall x. LeakyBucketState -> Rep LeakyBucketState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. LeakyBucketState -> Rep LeakyBucketState x
from :: forall x. LeakyBucketState -> Rep LeakyBucketState x
$cto :: forall x. Rep LeakyBucketState x -> LeakyBucketState
to :: forall x. Rep LeakyBucketState x -> LeakyBucketState
Generic)
instance ToJSON LeakyBucketState
instance FromJSON LeakyBucketState where
parseJSON :: Value -> Parser LeakyBucketState
parseJSON = String
-> (Object -> Parser LeakyBucketState)
-> Value
-> Parser LeakyBucketState
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"LeakyBucketState" ((Object -> Parser LeakyBucketState)
-> Value -> Parser LeakyBucketState)
-> (Object -> Parser LeakyBucketState)
-> Value
-> Parser LeakyBucketState
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Double
level <- Object
o Object -> Key -> Parser Double
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"level"
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Double
level Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
< Double
0) (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ String -> Parser ()
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"level must be non-negative"
Bool -> Parser () -> Parser ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Double
level Double -> Double -> Bool
forall a. Ord a => a -> a -> Bool
> Double
1000000) (Parser () -> Parser ()) -> Parser () -> Parser ()
forall a b. (a -> b) -> a -> b
$ String -> Parser ()
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"level must not exceed 1000000"
Double
lastTime <- Object
o Object -> Key -> Parser Double
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"lastTime"
LeakyBucketState -> Parser LeakyBucketState
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return LeakyBucketState { Double
level :: Double
level :: Double
level, Double
lastTime :: Double
lastTime :: Double
lastTime }