-- | Types for the http lib
module Calamity.HTTP.Internal.Types
    ( RestError(..)
    , RateLimitState(..)
    , DiscordResponseType(..)
    , GatewayResponse
    , BotGatewayResponse ) where

import           Calamity.HTTP.Internal.Route
import           Calamity.Internal.AesonThings

import           Control.Concurrent.Event      ( Event )
import           Control.Concurrent.STM.Lock   ( Lock )

import           Data.Aeson
import qualified Data.ByteString.Lazy          as LB
import           Data.Text.Lazy

import           GHC.Generics

import qualified StmContainers.Map             as SC

data RestError
  -- | An error response from discord
  = HTTPError
      { RestError -> Int
status   :: Int
      , RestError -> Maybe Value
response :: Maybe Value
      }
  -- | Something failed while making the request (after retrying a few times)
  | InternalClientError 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 RateLimitState = RateLimitState
  { RateLimitState -> Map Route Lock
rateLimits :: SC.Map Route Lock
  , 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 -- ^ A good response
  | ExhaustedBucket -- ^ We got a response but also exhausted the bucket
      LB.ByteString Int -- ^ Retry after (milliseconds)
  | Ratelimited -- ^ We hit a 429, no response and ratelimited
      Int -- ^ Retry after (milliseconds)
      Bool -- ^ Global ratelimit
  | ServerError Int -- ^ Discord's error, we should retry (HTTP 5XX)
  | ClientError Int LB.ByteString -- ^ Our error, we should fail
  | InternalResponseError Text -- ^ Something went wrong with the http client

newtype GatewayResponse = GatewayResponse
  { GatewayResponse -> Text
url :: 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    :: 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