{-# LANGUAGE TemplateHaskell #-}
module Calamity.HTTP.Internal.Types (
RestError (..),
RateLimitState (..),
DiscordResponseType (..),
Bucket (..),
BucketState (..),
GatewayResponse,
BotGatewayResponse,
) where
import Calamity.HTTP.Internal.Route
import Control.Concurrent.Event (Event)
import Control.Concurrent.STM.TVar (TVar)
import Data.Aeson
import Data.Aeson qualified as Aeson
import Data.ByteString qualified as B
import Data.ByteString.Lazy qualified as LB
import Data.Text as T
import Data.Time
import Optics.TH
import StmContainers.Map qualified as SC
data RestError
=
HTTPError
{ RestError -> Int
status :: Int
, RestError -> Maybe Value
response :: Maybe Value
}
|
InternalClientError T.Text
deriving (Int -> RestError -> ShowS
[RestError] -> ShowS
RestError -> String
(Int -> RestError -> ShowS)
-> (RestError -> String)
-> ([RestError] -> ShowS)
-> Show RestError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RestError -> ShowS
showsPrec :: Int -> RestError -> ShowS
$cshow :: RestError -> String
show :: RestError -> String
$cshowList :: [RestError] -> ShowS
showList :: [RestError] -> ShowS
Show)
data BucketState = BucketState
{ BucketState -> Maybe UTCTime
resetTime :: Maybe UTCTime
, BucketState -> Int
resetKey :: Int
, BucketState -> Int
remaining :: Int
, BucketState -> Int
limit :: Int
, BucketState -> Int
ongoing :: Int
}
deriving (Int -> BucketState -> ShowS
[BucketState] -> ShowS
BucketState -> String
(Int -> BucketState -> ShowS)
-> (BucketState -> String)
-> ([BucketState] -> ShowS)
-> Show BucketState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BucketState -> ShowS
showsPrec :: Int -> BucketState -> ShowS
$cshow :: BucketState -> String
show :: BucketState -> String
$cshowList :: [BucketState] -> ShowS
showList :: [BucketState] -> ShowS
Show)
newtype Bucket = Bucket
{ Bucket -> TVar BucketState
state :: TVar BucketState
}
data RateLimitState = RateLimitState
{ RateLimitState -> Map RouteKey ByteString
bucketKeys :: SC.Map RouteKey B.ByteString
, RateLimitState -> Map ByteString Bucket
buckets :: SC.Map B.ByteString Bucket
, RateLimitState -> Event
globalLock :: Event
}
data DiscordResponseType
=
Good
LB.ByteString
(Maybe (BucketState, B.ByteString))
|
Ratelimited
UTCTime
Bool
(Maybe (BucketState, B.ByteString))
|
ServerError Int
|
ClientError Int LB.ByteString
|
InternalResponseError T.Text
newtype GatewayResponse = GatewayResponse
{ GatewayResponse -> Text
url :: T.Text
}
deriving stock (Int -> GatewayResponse -> ShowS
[GatewayResponse] -> ShowS
GatewayResponse -> String
(Int -> GatewayResponse -> ShowS)
-> (GatewayResponse -> String)
-> ([GatewayResponse] -> ShowS)
-> Show GatewayResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GatewayResponse -> ShowS
showsPrec :: Int -> GatewayResponse -> ShowS
$cshow :: GatewayResponse -> String
show :: GatewayResponse -> String
$cshowList :: [GatewayResponse] -> ShowS
showList :: [GatewayResponse] -> ShowS
Show)
instance Aeson.FromJSON GatewayResponse where
parseJSON :: Value -> Parser GatewayResponse
parseJSON = String
-> (Object -> Parser GatewayResponse)
-> Value
-> Parser GatewayResponse
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"GatewayResponse" ((Object -> Parser GatewayResponse)
-> Value -> Parser GatewayResponse)
-> (Object -> Parser GatewayResponse)
-> Value
-> Parser GatewayResponse
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Text -> GatewayResponse
GatewayResponse (Text -> GatewayResponse) -> Parser Text -> Parser GatewayResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
data BotGatewayResponse = BotGatewayResponse
{ BotGatewayResponse -> Text
url :: T.Text
, BotGatewayResponse -> Int
shards :: Int
}
deriving (Int -> BotGatewayResponse -> ShowS
[BotGatewayResponse] -> ShowS
BotGatewayResponse -> String
(Int -> BotGatewayResponse -> ShowS)
-> (BotGatewayResponse -> String)
-> ([BotGatewayResponse] -> ShowS)
-> Show BotGatewayResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BotGatewayResponse -> ShowS
showsPrec :: Int -> BotGatewayResponse -> ShowS
$cshow :: BotGatewayResponse -> String
show :: BotGatewayResponse -> String
$cshowList :: [BotGatewayResponse] -> ShowS
showList :: [BotGatewayResponse] -> ShowS
Show)
instance Aeson.FromJSON BotGatewayResponse where
parseJSON :: Value -> Parser BotGatewayResponse
parseJSON = String
-> (Object -> Parser BotGatewayResponse)
-> Value
-> Parser BotGatewayResponse
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Aeson.withObject String
"BotGatewayResponse" ((Object -> Parser BotGatewayResponse)
-> Value -> Parser BotGatewayResponse)
-> (Object -> Parser BotGatewayResponse)
-> Value
-> Parser BotGatewayResponse
forall a b. (a -> b) -> a -> b
$ \Object
v ->
Text -> Int -> BotGatewayResponse
BotGatewayResponse
(Text -> Int -> BotGatewayResponse)
-> Parser Text -> Parser (Int -> BotGatewayResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"url"
Parser (Int -> BotGatewayResponse)
-> Parser Int -> Parser BotGatewayResponse
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser Int
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"shards"
$(makeFieldLabelsNoPrefix ''Bucket)
$(makeFieldLabelsNoPrefix ''BucketState)
$(makeFieldLabelsNoPrefix ''RateLimitState)
$(makeFieldLabelsNoPrefix ''GatewayResponse)
$(makeFieldLabelsNoPrefix ''BotGatewayResponse)