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