{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Telegram.Bot.API.Methods.GetUserChatBoosts where

import Data.Aeson (FromJSON (..), ToJSON (..))
import Data.Proxy
import GHC.Generics (Generic)
import Servant.API
import Servant.Client hiding (Response)

import Telegram.Bot.API.Internal.Utils
import Telegram.Bot.API.MakingRequests
import Telegram.Bot.API.Types
import Telegram.Bot.API.Internal.TH

-- ** 'getUserChatBoosts'

type GetUserChatBoosts
  = "getUserChatBoosts"
  :> ReqBody '[JSON] GetUserChatBoostsRequest
  :> Post '[JSON] (Response UserChatBoosts)

-- | Use this method to get the list of boosts added to a chat by a user. Requires administrator rights in the chat. Returns a 'UserChatBoosts' object.
getUserChatBoosts :: GetUserChatBoostsRequest -> ClientM (Response UserChatBoosts)
getUserChatBoosts :: GetUserChatBoostsRequest -> ClientM (Response UserChatBoosts)
getUserChatBoosts = Proxy GetUserChatBoosts -> Client ClientM GetUserChatBoosts
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @GetUserChatBoosts)


-- | Request parameters for 'getUserChatBoosts'.
data GetUserChatBoostsRequest = GetUserChatBoostsRequest
  { GetUserChatBoostsRequest -> SomeChatId
getUserChatBoostsRequestChatId :: SomeChatId -- ^ Unique identifier for the chat or username of the channel (in the format @channelusername).
  , GetUserChatBoostsRequest -> UserId
getUserChatBoostsRequestUserId :: UserId -- ^ Unique identifier of the target user.
  } deriving ((forall x.
 GetUserChatBoostsRequest -> Rep GetUserChatBoostsRequest x)
-> (forall x.
    Rep GetUserChatBoostsRequest x -> GetUserChatBoostsRequest)
-> Generic GetUserChatBoostsRequest
forall x.
Rep GetUserChatBoostsRequest x -> GetUserChatBoostsRequest
forall x.
GetUserChatBoostsRequest -> Rep GetUserChatBoostsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
GetUserChatBoostsRequest -> Rep GetUserChatBoostsRequest x
from :: forall x.
GetUserChatBoostsRequest -> Rep GetUserChatBoostsRequest x
$cto :: forall x.
Rep GetUserChatBoostsRequest x -> GetUserChatBoostsRequest
to :: forall x.
Rep GetUserChatBoostsRequest x -> GetUserChatBoostsRequest
Generic)

instance ToJSON   GetUserChatBoostsRequest where toJSON :: GetUserChatBoostsRequest -> Value
toJSON = GetUserChatBoostsRequest -> Value
forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance FromJSON GetUserChatBoostsRequest where parseJSON :: Value -> Parser GetUserChatBoostsRequest
parseJSON = Value -> Parser GetUserChatBoostsRequest
forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON

makeDefault ''GetUserChatBoostsRequest