module Calamity.HTTP.Internal.Types
( RestError(..)
, RateLimitState(..)
, DiscordResponseType(..)
, Bucket(..)
, BucketState(..)
, GatewayResponse
, BotGatewayResponse ) where
import Calamity.HTTP.Internal.Route
import Calamity.Internal.AesonThings
import Control.Concurrent.Event ( Event )
import Control.Concurrent.STM.TVar ( TVar )
import Data.Time
import Data.Aeson
import qualified Data.ByteString.Lazy as LB
import qualified Data.ByteString as B
import Data.Text as T
import GHC.Generics
import qualified StmContainers.Map 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
showList :: [RestError] -> ShowS
$cshowList :: [RestError] -> ShowS
show :: RestError -> String
$cshow :: RestError -> String
showsPrec :: Int -> RestError -> ShowS
$cshowsPrec :: Int -> RestError -> ShowS
Show, (forall x. RestError -> Rep RestError x)
-> (forall x. Rep RestError x -> RestError) -> Generic RestError
forall x. Rep RestError x -> RestError
forall x. RestError -> Rep RestError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RestError x -> RestError
$cfrom :: forall x. RestError -> Rep RestError x
Generic )
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 ( (forall x. BucketState -> Rep BucketState x)
-> (forall x. Rep BucketState x -> BucketState)
-> Generic BucketState
forall x. Rep BucketState x -> BucketState
forall x. BucketState -> Rep BucketState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BucketState x -> BucketState
$cfrom :: forall x. BucketState -> Rep BucketState x
Generic, 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
showList :: [BucketState] -> ShowS
$cshowList :: [BucketState] -> ShowS
show :: BucketState -> String
$cshow :: BucketState -> String
showsPrec :: Int -> BucketState -> ShowS
$cshowsPrec :: Int -> BucketState -> ShowS
Show )
newtype Bucket = Bucket
{ Bucket -> TVar BucketState
state :: TVar BucketState
}
deriving ( (forall x. Bucket -> Rep Bucket x)
-> (forall x. Rep Bucket x -> Bucket) -> Generic Bucket
forall x. Rep Bucket x -> Bucket
forall x. Bucket -> Rep Bucket x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Bucket x -> Bucket
$cfrom :: forall x. Bucket -> Rep Bucket x
Generic )
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
}
deriving ( (forall x. RateLimitState -> Rep RateLimitState x)
-> (forall x. Rep RateLimitState x -> RateLimitState)
-> Generic RateLimitState
forall x. Rep RateLimitState x -> RateLimitState
forall x. RateLimitState -> Rep RateLimitState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RateLimitState x -> RateLimitState
$cfrom :: forall x. RateLimitState -> Rep RateLimitState x
Generic )
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 ( (forall x. GatewayResponse -> Rep GatewayResponse x)
-> (forall x. Rep GatewayResponse x -> GatewayResponse)
-> Generic GatewayResponse
forall x. Rep GatewayResponse x -> GatewayResponse
forall x. GatewayResponse -> Rep GatewayResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GatewayResponse x -> GatewayResponse
$cfrom :: forall x. GatewayResponse -> Rep GatewayResponse x
Generic, 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
showList :: [GatewayResponse] -> ShowS
$cshowList :: [GatewayResponse] -> ShowS
show :: GatewayResponse -> String
$cshow :: GatewayResponse -> String
showsPrec :: Int -> GatewayResponse -> ShowS
$cshowsPrec :: Int -> GatewayResponse -> ShowS
Show )
deriving ( Value -> Parser [GatewayResponse]
Value -> Parser GatewayResponse
(Value -> Parser GatewayResponse)
-> (Value -> Parser [GatewayResponse]) -> FromJSON GatewayResponse
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [GatewayResponse]
$cparseJSONList :: Value -> Parser [GatewayResponse]
parseJSON :: Value -> Parser GatewayResponse
$cparseJSON :: Value -> Parser GatewayResponse
FromJSON ) via CalamityJSON GatewayResponse
data BotGatewayResponse = BotGatewayResponse
{ BotGatewayResponse -> Text
url :: T.Text
, BotGatewayResponse -> Int
shards :: Int
}
deriving ( (forall x. BotGatewayResponse -> Rep BotGatewayResponse x)
-> (forall x. Rep BotGatewayResponse x -> BotGatewayResponse)
-> Generic BotGatewayResponse
forall x. Rep BotGatewayResponse x -> BotGatewayResponse
forall x. BotGatewayResponse -> Rep BotGatewayResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BotGatewayResponse x -> BotGatewayResponse
$cfrom :: forall x. BotGatewayResponse -> Rep BotGatewayResponse x
Generic, 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
showList :: [BotGatewayResponse] -> ShowS
$cshowList :: [BotGatewayResponse] -> ShowS
show :: BotGatewayResponse -> String
$cshow :: BotGatewayResponse -> String
showsPrec :: Int -> BotGatewayResponse -> ShowS
$cshowsPrec :: Int -> BotGatewayResponse -> ShowS
Show )
deriving ( Value -> Parser [BotGatewayResponse]
Value -> Parser BotGatewayResponse
(Value -> Parser BotGatewayResponse)
-> (Value -> Parser [BotGatewayResponse])
-> FromJSON BotGatewayResponse
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [BotGatewayResponse]
$cparseJSONList :: Value -> Parser [BotGatewayResponse]
parseJSON :: Value -> Parser BotGatewayResponse
$cparseJSON :: Value -> Parser BotGatewayResponse
FromJSON ) via CalamityJSON BotGatewayResponse