{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Telegram.Bot.API.Methods.SetMyCommands where
import Data.Aeson (FromJSON (..), ToJSON (..))
import Data.Proxy
import Data.Text
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
data SetMyCommandsRequest = SetMyCommandsRequest
{ SetMyCommandsRequest -> [BotCommand]
setMyCommandsCommands :: [BotCommand]
, SetMyCommandsRequest -> Maybe BotCommandScope
setMyCommandsScope :: Maybe BotCommandScope
, SetMyCommandsRequest -> Maybe Text
setMyCommandsLanguageCode :: Maybe Text
}
deriving forall x. Rep SetMyCommandsRequest x -> SetMyCommandsRequest
forall x. SetMyCommandsRequest -> Rep SetMyCommandsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetMyCommandsRequest x -> SetMyCommandsRequest
$cfrom :: forall x. SetMyCommandsRequest -> Rep SetMyCommandsRequest x
Generic
instance ToJSON SetMyCommandsRequest where toJSON :: SetMyCommandsRequest -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance FromJSON SetMyCommandsRequest where parseJSON :: Value -> Parser SetMyCommandsRequest
parseJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON
type SetMyCommands = "setMyCommands"
:> ReqBody '[JSON] SetMyCommandsRequest
:> Post '[JSON] (Response Bool)
setMyCommands :: SetMyCommandsRequest -> ClientM (Response Bool)
setMyCommands :: SetMyCommandsRequest -> ClientM (Response Bool)
setMyCommands = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SetMyCommands)
makeDefault ''SetMyCommandsRequest