{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
module Telegram.Bot.API.Methods where

import Control.Monad.IO.Class
import Data.Aeson
import Data.Aeson.Text
import Data.Bool
import Data.Proxy
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import GHC.Generics (Generic)
import Servant.API
import Servant.Client hiding (Response)
import Servant.Multipart.API
import Servant.Multipart.Client
import System.FilePath

import Telegram.Bot.API.Internal.Utils
import Telegram.Bot.API.MakingRequests
import Telegram.Bot.API.Types
import Data.Maybe (catMaybes)
import Data.Functor ((<&>))

-- * Available methods

-- ** 'getMe'

type GetMe = "getMe" :> Get '[JSON] (Response User)

-- | A simple method for testing your bot's auth token.
-- Requires no parameters.
-- Returns basic information about the bot in form of a 'User' object.
getMe :: ClientM (Response User)
getMe :: ClientM (Response User)
getMe = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @GetMe)

-- ** 'deleteMessage'

-- | Notice that deleting by POST method was bugged, so we use GET
type DeleteMessage = "deleteMessage"
  :> RequiredQueryParam "chat_id" ChatId
  :> RequiredQueryParam "message_id" MessageId
  :> Get '[JSON] (Response Bool)

-- | Use this method to delete message in chat.
-- On success, the sent Bool is returned.
deleteMessage :: ChatId -> MessageId -> ClientM (Response Bool)
deleteMessage :: ChatId -> MessageId -> ClientM (Response Bool)
deleteMessage = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @DeleteMessage)

-- ** 'sendMessage'

type SendMessage
  = "sendMessage" :> ReqBody '[JSON] SendMessageRequest :> Post '[JSON] (Response Message)

-- | Use this method to send text messages.
-- On success, the sent 'Message' is returned.
sendMessage :: SendMessageRequest -> ClientM (Response Message)
sendMessage :: SendMessageRequest -> ClientM (Response Message)
sendMessage = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendMessage)

-- ** 'forwardMessage'
type ForwardMessage
  = "forwardMessage" :> ReqBody '[JSON] ForwardMessageRequest :> Post '[JSON] (Response Message)

-- | Use this method to forward messages of any kind.
-- On success, the sent 'Message' is returned.

forwardMessage :: ForwardMessageRequest -> ClientM (Response Message)
forwardMessage :: ForwardMessageRequest -> ClientM (Response Message)
forwardMessage = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @ForwardMessage)

-- | Additional interface options.
-- A JSON-serialized object for an inline keyboard, custom reply keyboard,
-- instructions to remove reply keyboard or to force a reply from the user.
data SomeReplyMarkup
  = SomeInlineKeyboardMarkup InlineKeyboardMarkup
  | SomeReplyKeyboardMarkup  ReplyKeyboardMarkup
  | SomeReplyKeyboardRemove  ReplyKeyboardRemove
  | SomeForceReply           ForceReply
  deriving (forall x. Rep SomeReplyMarkup x -> SomeReplyMarkup
forall x. SomeReplyMarkup -> Rep SomeReplyMarkup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SomeReplyMarkup x -> SomeReplyMarkup
$cfrom :: forall x. SomeReplyMarkup -> Rep SomeReplyMarkup x
Generic)

instance ToJSON   SomeReplyMarkup where toJSON :: SomeReplyMarkup -> Value
toJSON = forall a. (Generic a, GSomeJSON (Rep a)) => a -> Value
genericSomeToJSON
instance FromJSON SomeReplyMarkup where parseJSON :: Value -> Parser SomeReplyMarkup
parseJSON = forall a. (Generic a, GSomeJSON (Rep a)) => Value -> Parser a
genericSomeParseJSON

data ParseMode
  = Markdown
  | HTML
  | MarkdownV2
  deriving (forall x. Rep ParseMode x -> ParseMode
forall x. ParseMode -> Rep ParseMode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ParseMode x -> ParseMode
$cfrom :: forall x. ParseMode -> Rep ParseMode x
Generic)

instance ToJSON   ParseMode
instance FromJSON ParseMode

-- | Request parameters for 'sendMessage'.
data SendMessageRequest = SendMessageRequest
  { SendMessageRequest -> SomeChatId
sendMessageChatId                :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @\@channelusername@).
  , SendMessageRequest -> Text
sendMessageText                  :: Text -- ^ Text of the message to be sent.
  , SendMessageRequest -> Maybe ParseMode
sendMessageParseMode             :: Maybe ParseMode -- ^ Send 'MarkdownV2', 'HTML' or 'Markdown' (legacy), if you want Telegram apps to show bold, italic, fixed-width text or inline URLs in your bot's message.
  , SendMessageRequest -> Maybe [MessageEntity]
sendMessageEntities              :: Maybe [MessageEntity] -- ^ A JSON-serialized list of special entities that appear in message text, which can be specified instead of /parse_mode/.
  , SendMessageRequest -> Maybe Bool
sendMessageDisableWebPagePreview :: Maybe Bool -- ^ Disables link previews for links in this message.
  , SendMessageRequest -> Maybe Bool
sendMessageDisableNotification   :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , SendMessageRequest -> Maybe Bool
sendMessageProtectContent        :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving.
  , SendMessageRequest -> Maybe MessageId
sendMessageReplyToMessageId      :: Maybe MessageId -- ^ If the message is a reply, ID of the original message.
  , SendMessageRequest -> Maybe Bool
sendMessageAllowSendingWithoutReply :: Maybe Bool -- ^ Pass 'True', if the message should be sent even if the specified replied-to message is not found.
  , SendMessageRequest -> Maybe SomeReplyMarkup
sendMessageReplyMarkup           :: Maybe SomeReplyMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  } deriving (forall x. Rep SendMessageRequest x -> SendMessageRequest
forall x. SendMessageRequest -> Rep SendMessageRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendMessageRequest x -> SendMessageRequest
$cfrom :: forall x. SendMessageRequest -> Rep SendMessageRequest x
Generic)

instance ToJSON   SendMessageRequest where toJSON :: SendMessageRequest -> 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 SendMessageRequest where parseJSON :: Value -> Parser SendMessageRequest
parseJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON

-- | Request parameters for 'forwardMessage'.
data ForwardMessageRequest = ForwardMessageRequest
  { ForwardMessageRequest -> SomeChatId
forwardMessageChatId              :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @\@channelusername).
  , ForwardMessageRequest -> SomeChatId
forwardMessageFromChatId          :: SomeChatId -- ^ Unique identifier for the chat where the original message was sent (or channel username in the format @\@channelusername).
  , ForwardMessageRequest -> Maybe Bool
forwardMessageDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , ForwardMessageRequest -> Maybe Bool
forwardMessageProtectContent      :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving.
  , ForwardMessageRequest -> MessageId
forwardMessageMessageId           :: MessageId  -- ^ Message identifier in the chat specified in from_chat_id.
  } deriving (forall x. Rep ForwardMessageRequest x -> ForwardMessageRequest
forall x. ForwardMessageRequest -> Rep ForwardMessageRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ForwardMessageRequest x -> ForwardMessageRequest
$cfrom :: forall x. ForwardMessageRequest -> Rep ForwardMessageRequest x
Generic)

instance ToJSON   ForwardMessageRequest where toJSON :: ForwardMessageRequest -> 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 ForwardMessageRequest where parseJSON :: Value -> Parser ForwardMessageRequest
parseJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON

-- ** 'sendMessage'
type SendDocumentContent
  = "sendDocument"
  :> MultipartForm Tmp SendDocumentRequest
  :> Post '[JSON] (Response Message)

type SendDocumentLink
  = "sendDocument"
  :> ReqBody '[JSON] SendDocumentRequest
  :> Post '[JSON] (Response Message)

-- | Use this method to send text messages.
-- On success, the sent 'Message' is returned.
--
-- <https:\/\/core.telegram.org\/bots\/api#senddocument>
sendDocument :: SendDocumentRequest -> ClientM (Response Message)
sendDocument :: SendDocumentRequest -> ClientM (Response Message)
sendDocument SendDocumentRequest
r = do
  case SendDocumentRequest -> DocumentFile
sendDocumentDocument SendDocumentRequest
r of
    DocumentFile{} -> do
      ByteString
boundary <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
      forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendDocumentContent) (ByteString
boundary, SendDocumentRequest
r)
    DocumentFile
_ -> forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendDocumentLink) SendDocumentRequest
r

-- | Request parameters for 'sendDocument'
data SendDocumentRequest = SendDocumentRequest
  { SendDocumentRequest -> SomeChatId
sendDocumentChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @\@channelusername@).
  , SendDocumentRequest -> DocumentFile
sendDocumentDocument :: DocumentFile -- ^ Pass a file_id as String to send a file that exists on the Telegram servers (recommended), pass an HTTP URL as a String for Telegram to get a file from the Internet, or upload a new one using multipart/form-data
  , SendDocumentRequest -> Maybe FilePath
sendDocumentThumb :: Maybe FilePath -- ^ Thumbnail of the file sent; can be ignored if thumbnail generation for the file is supported server-side. The thumbnail should be in JPEG format and less than 200 kB in size. A thumbnail's width and height should not exceed 320. Ignored if the file is not uploaded using multipart/form-data. Thumbnails can't be reused and can be only uploaded as a new file, so you can pass “attach://<file_attach_name>” if the thumbnail was uploaded using multipart/form-data under <file_attach_name>
  , SendDocumentRequest -> Maybe Text
sendDocumentCaption :: Maybe Text -- ^ Document caption (may also be used when resending documents by file_id), 0-1024 characters after entities parsing
  , SendDocumentRequest -> Maybe ParseMode
sendDocumentParseMode :: Maybe ParseMode  -- ^ Send 'MarkdownV2', 'HTML' or 'Markdown' (legacy), if you want Telegram apps to show bold, italic, fixed-width text or inline URLs in your bot's message.
  , SendDocumentRequest -> Maybe [MessageEntity]
sendDocumentCaptionEntities :: Maybe [MessageEntity] -- ^ A JSON-serialized list of special entities that appear in the caption, which can be specified instead of /parse_mode/.
  , SendDocumentRequest -> Maybe Bool
sendDocumentDisableContentTypeDetection :: Maybe Bool -- ^ Disables automatic server-side content type detection for files uploaded using @multipart/form-data@.
  , SendDocumentRequest -> Maybe Bool
sendDocumentDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , SendDocumentRequest -> Maybe Bool
sendDocumentProtectContent      :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving.  
  , SendDocumentRequest -> Maybe MessageId
sendDocumentReplyToMessageId :: Maybe MessageId -- ^ If the message is a reply, ID of the original message.
  , SendDocumentRequest -> Maybe Bool
sendDocumentAllowSendingWithoutReply :: Maybe Bool -- ^ Pass 'True', if the message should be sent even if the specified replied-to message is not found.
  , SendDocumentRequest -> Maybe SomeReplyMarkup
sendDocumentReplyMarkup :: Maybe SomeReplyMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x. Rep SendDocumentRequest x -> SendDocumentRequest
forall x. SendDocumentRequest -> Rep SendDocumentRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendDocumentRequest x -> SendDocumentRequest
$cfrom :: forall x. SendDocumentRequest -> Rep SendDocumentRequest x
Generic


newtype DocumentFile = MakeDocumentFile InputFile
  deriving newtype [DocumentFile] -> Encoding
[DocumentFile] -> Value
DocumentFile -> Encoding
DocumentFile -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DocumentFile] -> Encoding
$ctoEncodingList :: [DocumentFile] -> Encoding
toJSONList :: [DocumentFile] -> Value
$ctoJSONList :: [DocumentFile] -> Value
toEncoding :: DocumentFile -> Encoding
$ctoEncoding :: DocumentFile -> Encoding
toJSON :: DocumentFile -> Value
$ctoJSON :: DocumentFile -> Value
ToJSON

pattern DocumentFileId :: FileId -> DocumentFile
pattern $bDocumentFileId :: FileId -> DocumentFile
$mDocumentFileId :: forall {r}. DocumentFile -> (FileId -> r) -> ((# #) -> r) -> r
DocumentFileId x = MakeDocumentFile (InputFileId x)

pattern DocumentUrl :: Text -> DocumentFile
pattern $bDocumentUrl :: Text -> DocumentFile
$mDocumentUrl :: forall {r}. DocumentFile -> (Text -> r) -> ((# #) -> r) -> r
DocumentUrl x = MakeDocumentFile (FileUrl x)

pattern DocumentFile :: FilePath -> ContentType -> DocumentFile
pattern $bDocumentFile :: FilePath -> Text -> DocumentFile
$mDocumentFile :: forall {r}.
DocumentFile -> (FilePath -> Text -> r) -> ((# #) -> r) -> r
DocumentFile x y = MakeDocumentFile (InputFile x y)


instance ToMultipart Tmp SendDocumentRequest where
  toMultipart :: SendDocumentRequest -> MultipartData Tmp
toMultipart SendDocumentRequest{Maybe Bool
Maybe FilePath
Maybe [MessageEntity]
Maybe Text
Maybe MessageId
Maybe ParseMode
Maybe SomeReplyMarkup
SomeChatId
DocumentFile
sendDocumentReplyMarkup :: Maybe SomeReplyMarkup
sendDocumentAllowSendingWithoutReply :: Maybe Bool
sendDocumentReplyToMessageId :: Maybe MessageId
sendDocumentProtectContent :: Maybe Bool
sendDocumentDisableNotification :: Maybe Bool
sendDocumentDisableContentTypeDetection :: Maybe Bool
sendDocumentCaptionEntities :: Maybe [MessageEntity]
sendDocumentParseMode :: Maybe ParseMode
sendDocumentCaption :: Maybe Text
sendDocumentThumb :: Maybe FilePath
sendDocumentDocument :: DocumentFile
sendDocumentChatId :: SomeChatId
sendDocumentReplyMarkup :: SendDocumentRequest -> Maybe SomeReplyMarkup
sendDocumentAllowSendingWithoutReply :: SendDocumentRequest -> Maybe Bool
sendDocumentReplyToMessageId :: SendDocumentRequest -> Maybe MessageId
sendDocumentProtectContent :: SendDocumentRequest -> Maybe Bool
sendDocumentDisableNotification :: SendDocumentRequest -> Maybe Bool
sendDocumentDisableContentTypeDetection :: SendDocumentRequest -> Maybe Bool
sendDocumentCaptionEntities :: SendDocumentRequest -> Maybe [MessageEntity]
sendDocumentParseMode :: SendDocumentRequest -> Maybe ParseMode
sendDocumentCaption :: SendDocumentRequest -> Maybe Text
sendDocumentThumb :: SendDocumentRequest -> Maybe FilePath
sendDocumentChatId :: SendDocumentRequest -> SomeChatId
sendDocumentDocument :: SendDocumentRequest -> DocumentFile
..} = forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [FileData Tmp]
files where
    fields :: [Input]
fields =
      [ Text -> Text -> Input
Input Text
"document" forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ FilePath
"attach://file"
      , Text -> Text -> Input
Input Text
"chat_id" forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendDocumentChatId of
          SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> FilePath
show Integer
chat_id
          SomeChatUsername Text
txt -> Text
txt
      ] forall a. Semigroup a => a -> a -> a
<>
      (   (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\FilePath
_ -> ((Text -> Text -> Input
Input Text
"thumb" Text
"attach://thumb")forall a. a -> [a] -> [a]
:)) Maybe FilePath
sendDocumentThumb)
        forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Text
t -> ((Text -> Text -> Input
Input Text
"caption" Text
t)forall a. a -> [a] -> [a]
:)) Maybe Text
sendDocumentCaption)
        forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\ParseMode
t -> ((Text -> Text -> Input
Input Text
"parse_mode" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText ParseMode
t))forall a. a -> [a] -> [a]
:)) Maybe ParseMode
sendDocumentParseMode)
        forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\[MessageEntity]
t -> ((Text -> Text -> Input
Input Text
"caption_entities" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText [MessageEntity]
t))forall a. a -> [a] -> [a]
:)) Maybe [MessageEntity]
sendDocumentCaptionEntities)
        forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Bool
t -> ((Text -> Text -> Input
Input Text
"disable_notification" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t))forall a. a -> [a] -> [a]
:)) Maybe Bool
sendDocumentDisableNotification)
        forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Bool
t -> ((Text -> Text -> Input
Input Text
"disable_content_type_detection" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t))forall a. a -> [a] -> [a]
:)) Maybe Bool
sendDocumentDisableContentTypeDetection)
        forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\MessageId
t -> ((Text -> Text -> Input
Input Text
"reply_to_message_id" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t))forall a. a -> [a] -> [a]
:)) Maybe MessageId
sendDocumentReplyToMessageId)
        forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Bool
t -> ((Text -> Text -> Input
Input Text
"allow_sending_without_reply" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t))forall a. a -> [a] -> [a]
:)) Maybe Bool
sendDocumentAllowSendingWithoutReply)
        forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\SomeReplyMarkup
t -> ((Text -> Text -> Input
Input Text
"reply_markup" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText SomeReplyMarkup
t))forall a. a -> [a] -> [a]
:)) Maybe SomeReplyMarkup
sendDocumentReplyMarkup)
        [])
    files :: [FileData Tmp]
files
      = (forall tag.
Text -> Text -> Text -> MultipartResult tag -> FileData tag
FileData Text
"file" (FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeFileName FilePath
path) Text
ct FilePath
path)
      forall a. a -> [a] -> [a]
: forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\FilePath
t -> [forall tag.
Text -> Text -> Text -> MultipartResult tag -> FileData tag
FileData Text
"thumb" (FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeFileName FilePath
t) Text
"image/jpeg" FilePath
t]) Maybe FilePath
sendDocumentThumb

    DocumentFile FilePath
path Text
ct = DocumentFile
sendDocumentDocument


instance ToJSON   SendDocumentRequest where toJSON :: SendDocumentRequest -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON

-- | Generate send document structure.
toSendDocument :: SomeChatId -> DocumentFile -> SendDocumentRequest
toSendDocument :: SomeChatId -> DocumentFile -> SendDocumentRequest
toSendDocument SomeChatId
ch DocumentFile
df = SendDocumentRequest
  { sendDocumentChatId :: SomeChatId
sendDocumentChatId = SomeChatId
ch
  , sendDocumentDocument :: DocumentFile
sendDocumentDocument = DocumentFile
df
  , sendDocumentThumb :: Maybe FilePath
sendDocumentThumb = forall a. Maybe a
Nothing
  , sendDocumentCaption :: Maybe Text
sendDocumentCaption = forall a. Maybe a
Nothing
  , sendDocumentParseMode :: Maybe ParseMode
sendDocumentParseMode = forall a. Maybe a
Nothing
  , sendDocumentCaptionEntities :: Maybe [MessageEntity]
sendDocumentCaptionEntities =  forall a. Maybe a
Nothing
  , sendDocumentDisableContentTypeDetection :: Maybe Bool
sendDocumentDisableContentTypeDetection = forall a. Maybe a
Nothing
  , sendDocumentDisableNotification :: Maybe Bool
sendDocumentDisableNotification = forall a. Maybe a
Nothing
  , sendDocumentProtectContent :: Maybe Bool
sendDocumentProtectContent = forall a. Maybe a
Nothing
  , sendDocumentReplyToMessageId :: Maybe MessageId
sendDocumentReplyToMessageId = forall a. Maybe a
Nothing
  , sendDocumentAllowSendingWithoutReply :: Maybe Bool
sendDocumentAllowSendingWithoutReply = forall a. Maybe a
Nothing
  , sendDocumentReplyMarkup :: Maybe SomeReplyMarkup
sendDocumentReplyMarkup = forall a. Maybe a
Nothing
  }

-- ** 'getFile'
type GetFile
  = "getFile"
  :> RequiredQueryParam "file_id" FileId
  :> Get '[JSON] (Response File)

getFile :: FileId -> ClientM (Response File)
getFile :: FileId -> ClientM (Response File)
getFile = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @GetFile)

-- ** 'sendPhoto'
type SendPhotoContent
  = "sendPhoto"
  :> MultipartForm Tmp SendPhotoRequest
  :> Post '[JSON] (Response Message)

type SendPhotoLink
  = "sendPhoto"
  :> ReqBody '[JSON] SendPhotoRequest
  :> Post '[JSON] (Response Message)



newtype PhotoFile = MakePhotoFile InputFile
  deriving newtype [PhotoFile] -> Encoding
[PhotoFile] -> Value
PhotoFile -> Encoding
PhotoFile -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PhotoFile] -> Encoding
$ctoEncodingList :: [PhotoFile] -> Encoding
toJSONList :: [PhotoFile] -> Value
$ctoJSONList :: [PhotoFile] -> Value
toEncoding :: PhotoFile -> Encoding
$ctoEncoding :: PhotoFile -> Encoding
toJSON :: PhotoFile -> Value
$ctoJSON :: PhotoFile -> Value
ToJSON

pattern PhotoFileId :: FileId -> PhotoFile
pattern $bPhotoFileId :: FileId -> PhotoFile
$mPhotoFileId :: forall {r}. PhotoFile -> (FileId -> r) -> ((# #) -> r) -> r
PhotoFileId x = MakePhotoFile (InputFileId x)

pattern PhotoUrl :: Text -> PhotoFile
pattern $bPhotoUrl :: Text -> PhotoFile
$mPhotoUrl :: forall {r}. PhotoFile -> (Text -> r) -> ((# #) -> r) -> r
PhotoUrl x = MakePhotoFile (FileUrl x)

pattern PhotoFile :: FilePath -> ContentType -> PhotoFile
pattern $bPhotoFile :: FilePath -> Text -> PhotoFile
$mPhotoFile :: forall {r}.
PhotoFile -> (FilePath -> Text -> r) -> ((# #) -> r) -> r
PhotoFile x y = MakePhotoFile (InputFile x y)


-- | Request parameters for 'sendPhoto'
data SendPhotoRequest = SendPhotoRequest
  { SendPhotoRequest -> SomeChatId
sendPhotoChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @\@channelusername@).
  , SendPhotoRequest -> PhotoFile
sendPhotoPhoto :: PhotoFile -- ^ Pass a file_id as String to send a file that exists on the Telegram servers (recommended), pass an HTTP URL as a String for Telegram to get a file from the Internet, or upload a new one using multipart/form-data
  , SendPhotoRequest -> Maybe FilePath
sendPhotoThumb :: Maybe FilePath -- ^ Thumbnail of the file sent; can be ignored if thumbnail generation for the file is supported server-side. The thumbnail should be in JPEG format and less than 200 kB in size. A thumbnail's width and height should not exceed 320. Ignored if the file is not uploaded using multipart/form-data. Thumbnails can't be reused and can be only uploaded as a new file, so you can pass “attach://<file_attach_name>” if the thumbnail was uploaded using multipart/form-data under <file_attach_name>
  , SendPhotoRequest -> Maybe Text
sendPhotoCaption :: Maybe Text -- ^ Photo caption (may also be used when resending Photos by file_id), 0-1024 characters after entities parsing
  , SendPhotoRequest -> Maybe ParseMode
sendPhotoParseMode :: Maybe ParseMode  -- ^ Send 'MarkdownV2', 'HTML' or 'Markdown' (legacy), if you want Telegram apps to show bold, italic, fixed-width text or inline URLs in your bot's message.
  , SendPhotoRequest -> Maybe [MessageEntity]
sendPhotoCaptionEntities :: Maybe [MessageEntity] -- ^ A JSON-serialized list of special entities that appear in the caption, which can be specified instead of /parse_mode/.
  , SendPhotoRequest -> Maybe Bool
sendPhotoDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , SendPhotoRequest -> Maybe Bool
sendPhotoProtectContent      :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving.  
  , SendPhotoRequest -> Maybe MessageId
sendPhotoReplyToMessageId :: Maybe MessageId -- ^ If the message is a reply, ID of the original message.
  , SendPhotoRequest -> Maybe Bool
sendPhotoAllowSendingWithoutReply :: Maybe Bool -- ^ Pass 'True', if the message should be sent even if the specified replied-to message is not found.
  , SendPhotoRequest -> Maybe SomeReplyMarkup
sendPhotoReplyMarkup :: Maybe SomeReplyMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x. Rep SendPhotoRequest x -> SendPhotoRequest
forall x. SendPhotoRequest -> Rep SendPhotoRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendPhotoRequest x -> SendPhotoRequest
$cfrom :: forall x. SendPhotoRequest -> Rep SendPhotoRequest x
Generic

instance ToMultipart Tmp SendPhotoRequest where
  toMultipart :: SendPhotoRequest -> MultipartData Tmp
toMultipart SendPhotoRequest{Maybe Bool
Maybe FilePath
Maybe [MessageEntity]
Maybe Text
Maybe MessageId
Maybe ParseMode
Maybe SomeReplyMarkup
SomeChatId
PhotoFile
sendPhotoReplyMarkup :: Maybe SomeReplyMarkup
sendPhotoAllowSendingWithoutReply :: Maybe Bool
sendPhotoReplyToMessageId :: Maybe MessageId
sendPhotoProtectContent :: Maybe Bool
sendPhotoDisableNotification :: Maybe Bool
sendPhotoCaptionEntities :: Maybe [MessageEntity]
sendPhotoParseMode :: Maybe ParseMode
sendPhotoCaption :: Maybe Text
sendPhotoThumb :: Maybe FilePath
sendPhotoPhoto :: PhotoFile
sendPhotoChatId :: SomeChatId
sendPhotoReplyMarkup :: SendPhotoRequest -> Maybe SomeReplyMarkup
sendPhotoAllowSendingWithoutReply :: SendPhotoRequest -> Maybe Bool
sendPhotoReplyToMessageId :: SendPhotoRequest -> Maybe MessageId
sendPhotoProtectContent :: SendPhotoRequest -> Maybe Bool
sendPhotoDisableNotification :: SendPhotoRequest -> Maybe Bool
sendPhotoCaptionEntities :: SendPhotoRequest -> Maybe [MessageEntity]
sendPhotoParseMode :: SendPhotoRequest -> Maybe ParseMode
sendPhotoCaption :: SendPhotoRequest -> Maybe Text
sendPhotoThumb :: SendPhotoRequest -> Maybe FilePath
sendPhotoPhoto :: SendPhotoRequest -> PhotoFile
sendPhotoChatId :: SendPhotoRequest -> SomeChatId
..} = forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [FileData Tmp]
files where
    fields :: [Input]
fields =
      [ Text -> Text -> Input
Input Text
"photo" forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ FilePath
"attach://file"
      , Text -> Text -> Input
Input Text
"chat_id" forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendPhotoChatId of
          SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> FilePath
show Integer
chat_id
          SomeChatUsername Text
txt -> Text
txt
      ] forall a. Semigroup a => a -> a -> a
<>
      (   (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\FilePath
_ -> ((Text -> Text -> Input
Input Text
"thumb" Text
"attach://thumb")forall a. a -> [a] -> [a]
:)) Maybe FilePath
sendPhotoThumb)
        forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Text
t -> ((Text -> Text -> Input
Input Text
"caption" Text
t)forall a. a -> [a] -> [a]
:)) Maybe Text
sendPhotoCaption)
        forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\ParseMode
t -> ((Text -> Text -> Input
Input Text
"parse_mode" (Text -> Text
TL.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text -> Text
TL.replace Text
"\"" Text
"" forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText ParseMode
t))forall a. a -> [a] -> [a]
:)) Maybe ParseMode
sendPhotoParseMode)
        forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\[MessageEntity]
t -> ((Text -> Text -> Input
Input Text
"caption_entities" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText [MessageEntity]
t))forall a. a -> [a] -> [a]
:)) Maybe [MessageEntity]
sendPhotoCaptionEntities)
        forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Bool
t -> ((Text -> Text -> Input
Input Text
"disable_notification" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t))forall a. a -> [a] -> [a]
:)) Maybe Bool
sendPhotoDisableNotification)
        forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\MessageId
t -> ((Text -> Text -> Input
Input Text
"reply_to_message_id" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t))forall a. a -> [a] -> [a]
:)) Maybe MessageId
sendPhotoReplyToMessageId)
        forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\Bool
t -> ((Text -> Text -> Input
Input Text
"allow_sending_without_reply" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t))forall a. a -> [a] -> [a]
:)) Maybe Bool
sendPhotoAllowSendingWithoutReply)
        forall a b. (a -> b) -> a -> b
$ (forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (\SomeReplyMarkup
t -> ((Text -> Text -> Input
Input Text
"reply_markup" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText SomeReplyMarkup
t))forall a. a -> [a] -> [a]
:)) Maybe SomeReplyMarkup
sendPhotoReplyMarkup)
        [])
    files :: [FileData Tmp]
files
      = (forall tag.
Text -> Text -> Text -> MultipartResult tag -> FileData tag
FileData Text
"file" (FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeFileName FilePath
path) Text
ct FilePath
path)
      forall a. a -> [a] -> [a]
: forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\FilePath
t -> [forall tag.
Text -> Text -> Text -> MultipartResult tag -> FileData tag
FileData Text
"thumb" (FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeFileName FilePath
t) Text
"image/jpeg" FilePath
t]) Maybe FilePath
sendPhotoThumb

    PhotoFile FilePath
path Text
ct = PhotoFile
sendPhotoPhoto

instance ToJSON SendPhotoRequest where toJSON :: SendPhotoRequest -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON

-- | Use this method to send photos.
-- On success, the sent 'Message' is returned.
--
-- <https:\/\/core.telegram.org\/bots\/api#sendphoto>
sendPhoto :: SendPhotoRequest -> ClientM (Response Message)
sendPhoto :: SendPhotoRequest -> ClientM (Response Message)
sendPhoto SendPhotoRequest
r = do
  case SendPhotoRequest -> PhotoFile
sendPhotoPhoto SendPhotoRequest
r of
    PhotoFile{} -> do
      ByteString
boundary <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
      forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendPhotoContent) (ByteString
boundary, SendPhotoRequest
r)
    PhotoFile
_ -> forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendPhotoLink) SendPhotoRequest
r

-- | Request parameters for 'copyMessage'.
data CopyMessageRequest = CopyMessageRequest
  { CopyMessageRequest -> SomeChatId
copyMessageChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , CopyMessageRequest -> SomeChatId
copyMessageFromChatId :: SomeChatId -- ^ Unique identifier for the chat where the original message was sent (or channel username in the format @channelusername)
  , CopyMessageRequest -> MessageId
copyMessageMessageId :: MessageId -- ^ Message identifier in the chat specified in from_chat_id
  , CopyMessageRequest -> Maybe Text
copyMessageCaption :: Maybe Text -- ^ New caption for media, 0-1024 characters after entities parsing. If not specified, the original caption is kept
  , CopyMessageRequest -> Maybe ParseMode
copyMessageParseMode :: Maybe ParseMode  -- ^ Send 'MarkdownV2', 'HTML' or 'Markdown' (legacy), if you want Telegram apps to show bold, italic, fixed-width text or inline URLs in your bot's message.
  , CopyMessageRequest -> Maybe [MessageEntity]
copyMessageCaptionEntities :: Maybe [MessageEntity] -- ^ A JSON-serialized list of special entities that appear in the caption, which can be specified instead of parse_mode
  , CopyMessageRequest -> Maybe Bool
copyMessageDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , CopyMessageRequest -> Maybe Bool
copyMessageProtectContent :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving
  , CopyMessageRequest -> Maybe MessageId
copyMessageReplyToMessageId :: Maybe MessageId -- ^ If the message is a reply, ID of the original message
  , CopyMessageRequest -> Maybe Bool
copyMessageAllowSendingWithoutReply :: Maybe Bool -- ^ Pass True, if the message should be sent even if the specified replied-to message is not found
  , CopyMessageRequest -> Maybe InlineKeyboardMarkup
copyMessageReplyMarkup :: Maybe InlineKeyboardMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x. Rep CopyMessageRequest x -> CopyMessageRequest
forall x. CopyMessageRequest -> Rep CopyMessageRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CopyMessageRequest x -> CopyMessageRequest
$cfrom :: forall x. CopyMessageRequest -> Rep CopyMessageRequest x
Generic

-- | Request parameters for 'sendAudio'.
data SendAudioRequest = SendAudioRequest
  { SendAudioRequest -> SomeChatId
sendAudioChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , SendAudioRequest -> InputFile
sendAudioAudio :: InputFile -- ^ Audio to send. Pass a file_id as String to send an audio that exists on the Telegram servers (recommended), pass an HTTP URL as a String for Telegram to get a audio from the Internet, or upload a new audio using multipart/form-data. More info on Sending Files »
  , SendAudioRequest -> Maybe Int
sendAudioDuration :: Maybe Int -- ^ Duration of sent audio in seconds
  , SendAudioRequest -> Maybe Text
sendAudioPerformer :: Maybe Text -- ^ Performer
  , SendAudioRequest -> Maybe Text
sendAudioTitle :: Maybe Text -- ^ Track name
  , SendAudioRequest -> Maybe InputFile
sendAudioThumb :: Maybe InputFile -- ^ Thumbnail of the file sent; can be ignored if thumbnail generation for the file is supported server-side. The thumbnail should be in JPEG format and less than 200 kB in size. A thumbnail's width and height should not exceed 320. Ignored if the file is not uploaded using multipart/form-data. Thumbnails can't be reused and can be only uploaded as a new file, so you can pass “attach://<file_attach_name>” if the thumbnail was uploaded using multipart/form-data under <file_attach_name>. More info on Sending Files »
  , SendAudioRequest -> Maybe Text
sendAudioCaption :: Maybe Text -- ^ Audio caption (may also be used when resending audios by file_id), 0-1024 characters after entities parsing
  , SendAudioRequest -> Maybe ParseMode
sendAudioParseMode :: Maybe ParseMode  -- ^ Send 'MarkdownV2', 'HTML' or 'Markdown' (legacy), if you want Telegram apps to show bold, italic, fixed-width text or inline URLs in your bot's message.
  , SendAudioRequest -> Maybe [MessageEntity]
sendAudioCaptionEntities :: Maybe [MessageEntity] -- ^ A JSON-serialized list of special entities that appear in the caption, which can be specified instead of parse_mode
  , SendAudioRequest -> Maybe Bool
sendAudioDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , SendAudioRequest -> Maybe Bool
sendAudioProtectContent :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving
  , SendAudioRequest -> Maybe MessageId
sendAudioReplyToMessageId :: Maybe MessageId -- ^ If the message is a reply, ID of the original message
  , SendAudioRequest -> Maybe Bool
sendAudioAllowSendingWithoutReply :: Maybe Bool -- ^ Pass True, if the message should be sent even if the specified replied-to message is not found
  , SendAudioRequest -> Maybe InlineKeyboardMarkup
sendAudioReplyMarkup :: Maybe InlineKeyboardMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x. Rep SendAudioRequest x -> SendAudioRequest
forall x. SendAudioRequest -> Rep SendAudioRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendAudioRequest x -> SendAudioRequest
$cfrom :: forall x. SendAudioRequest -> Rep SendAudioRequest x
Generic

instance ToJSON SendAudioRequest where toJSON :: SendAudioRequest -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON

instance ToMultipart Tmp SendAudioRequest where
  toMultipart :: SendAudioRequest -> MultipartData Tmp
toMultipart SendAudioRequest{Maybe Bool
Maybe Int
Maybe [MessageEntity]
Maybe Text
Maybe InlineKeyboardMarkup
Maybe InputFile
Maybe MessageId
Maybe ParseMode
SomeChatId
InputFile
sendAudioReplyMarkup :: Maybe InlineKeyboardMarkup
sendAudioAllowSendingWithoutReply :: Maybe Bool
sendAudioReplyToMessageId :: Maybe MessageId
sendAudioProtectContent :: Maybe Bool
sendAudioDisableNotification :: Maybe Bool
sendAudioCaptionEntities :: Maybe [MessageEntity]
sendAudioParseMode :: Maybe ParseMode
sendAudioCaption :: Maybe Text
sendAudioThumb :: Maybe InputFile
sendAudioTitle :: Maybe Text
sendAudioPerformer :: Maybe Text
sendAudioDuration :: Maybe Int
sendAudioAudio :: InputFile
sendAudioChatId :: SomeChatId
sendAudioReplyMarkup :: SendAudioRequest -> Maybe InlineKeyboardMarkup
sendAudioAllowSendingWithoutReply :: SendAudioRequest -> Maybe Bool
sendAudioReplyToMessageId :: SendAudioRequest -> Maybe MessageId
sendAudioProtectContent :: SendAudioRequest -> Maybe Bool
sendAudioDisableNotification :: SendAudioRequest -> Maybe Bool
sendAudioCaptionEntities :: SendAudioRequest -> Maybe [MessageEntity]
sendAudioParseMode :: SendAudioRequest -> Maybe ParseMode
sendAudioCaption :: SendAudioRequest -> Maybe Text
sendAudioThumb :: SendAudioRequest -> Maybe InputFile
sendAudioTitle :: SendAudioRequest -> Maybe Text
sendAudioPerformer :: SendAudioRequest -> Maybe Text
sendAudioDuration :: SendAudioRequest -> Maybe Int
sendAudioAudio :: SendAudioRequest -> InputFile
sendAudioChatId :: SendAudioRequest -> SomeChatId
..} =
    forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"thumb") Maybe InputFile
sendAudioThumb forall a b. (a -> b) -> a -> b
$
    Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"audio" InputFile
sendAudioAudio forall a b. (a -> b) -> a -> b
$
    forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [] where
    fields :: [Input]
fields =
      [ Text -> Text -> Input
Input Text
"chat_id" forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendAudioChatId of
          SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> FilePath
show Integer
chat_id
          SomeChatUsername Text
txt -> Text
txt
      ] forall a. Semigroup a => a -> a -> a
<> forall a. [Maybe a] -> [a]
catMaybes
      [ Maybe Text
sendAudioCaption forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Text
t -> Text -> Text -> Input
Input Text
"caption" Text
t
      , Maybe ParseMode
sendAudioParseMode forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \ParseMode
t -> Text -> Text -> Input
Input Text
"parse_mode" (Text -> Text
TL.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text -> Text
TL.replace Text
"\"" Text
"" forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText ParseMode
t)
      , Maybe [MessageEntity]
sendAudioCaptionEntities forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \[MessageEntity]
t -> Text -> Text -> Input
Input Text
"caption_entities" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText [MessageEntity]
t)
      , Maybe Int
sendAudioDuration forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Int
t -> Text -> Text -> Input
Input Text
"duration" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
      , Maybe Text
sendAudioPerformer forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Text
t -> Text -> Text -> Input
Input Text
"performer" Text
t
      , Maybe Text
sendAudioTitle forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Text
t -> Text -> Text -> Input
Input Text
"title" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText Text
t)
      , Maybe Bool
sendAudioDisableNotification forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"disable_notification" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe Bool
sendAudioProtectContent forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"protected_content" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe MessageId
sendAudioReplyToMessageId forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \MessageId
t -> Text -> Text -> Input
Input Text
"reply_to_message_id" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t)
      , Maybe Bool
sendAudioAllowSendingWithoutReply forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"allow_sending_without_reply" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe InlineKeyboardMarkup
sendAudioReplyMarkup forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \InlineKeyboardMarkup
t -> Text -> Text -> Input
Input Text
"reply_markup" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText InlineKeyboardMarkup
t)
      ]

type SendAudioContent
  = "sendAudio"
  :> MultipartForm Tmp SendAudioRequest
  :> Post '[JSON] (Response Message)

type SendAudioLink
  = "sendAudio"
  :> ReqBody '[JSON] SendAudioRequest
  :> Post '[JSON] (Response Message)

-- | Use this method to send audio files, if
--   you want Telegram clients to display them
--   in the music player. Your audio must be in
--   the .MP3 or .M4A format. On success, the sent
--   Message is returned. Bots can currently send
--   audio files of up to 50 MB in size, this limit
--   may be changed in the future.
--
--   For sending voice messages, use the sendVoice method instead.
sendAudio :: SendAudioRequest ->  ClientM (Response Message)
sendAudio :: SendAudioRequest -> ClientM (Response Message)
sendAudio SendAudioRequest
r = case (SendAudioRequest -> InputFile
sendAudioAudio SendAudioRequest
r, SendAudioRequest -> Maybe InputFile
sendAudioThumb SendAudioRequest
r) of
  (InputFile{}, Maybe InputFile
_) -> do
    ByteString
boundary <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
    forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendAudioContent) (ByteString
boundary, SendAudioRequest
r)
  (InputFile
_, Just InputFile{}) -> do
    ByteString
boundary <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
    forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendAudioContent) (ByteString
boundary, SendAudioRequest
r)
  (InputFile, Maybe InputFile)
_ ->  forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendAudioLink) SendAudioRequest
r

-- | Request parameters for 'sendVideo'.
data SendVideoRequest = SendVideoRequest
  { SendVideoRequest -> SomeChatId
sendVideoChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , SendVideoRequest -> InputFile
sendVideoVideo :: InputFile -- ^ Video to send. Pass a file_id as String to send an video that exists on the Telegram servers (recommended), pass an HTTP URL as a String for Telegram to get a video from the Internet, or upload a new video using multipart/form-data. More info on Sending Files »
  , SendVideoRequest -> Maybe Int
sendVideoDuration :: Maybe Int -- ^ Duration of sent video in seconds
  , SendVideoRequest -> Maybe Int
sendVideoWidth :: Maybe Int -- ^ Video width
  , SendVideoRequest -> Maybe Int
sendVideoHeight :: Maybe Int -- ^ Video height
  , SendVideoRequest -> Maybe InputFile
sendVideoThumb :: Maybe InputFile -- ^ Thumbnail of the file sent; can be ignored if thumbnail generation for the file is supported server-side. The thumbnail should be in JPEG format and less than 200 kB in size. A thumbnail's width and height should not exceed 320. Ignored if the file is not uploaded using multipart/form-data. Thumbnails can't be reused and can be only uploaded as a new file, so you can pass “attach://<file_attach_name>” if the thumbnail was uploaded using multipart/form-data under <file_attach_name>. More info on Sending Files »
  , SendVideoRequest -> Maybe Text
sendVideoCaption :: Maybe Text -- ^ Video caption (may also be used when resending videos by file_id), 0-1024 characters after entities parsing
  , SendVideoRequest -> Maybe ParseMode
sendVideoParseMode :: Maybe ParseMode  -- ^ Send 'MarkdownV2', 'HTML' or 'Markdown' (legacy), if you want Telegram apps to show bold, italic, fixed-width text or inline URLs in your bot's message.
  , SendVideoRequest -> Maybe [MessageEntity]
sendVideoCaptionEntities :: Maybe [MessageEntity] -- ^ A JSON-serialized list of special entities that appear in the caption, which can be specified instead of parse_mode
  , SendVideoRequest -> Maybe Bool
sendVideoSupportsStreaming :: Maybe Bool -- ^ Pass True, if the uploaded video is suitable for streaming
  , SendVideoRequest -> Maybe Bool
sendVideoDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , SendVideoRequest -> Maybe Bool
sendVideoProtectContent :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving.
  , SendVideoRequest -> Maybe MessageId
sendVideoReplyToMessageId :: Maybe MessageId -- ^ If the message is a reply, ID of the original message
  , SendVideoRequest -> Maybe Bool
sendVideoAllowSendingWithoutReply :: Maybe Bool -- ^ Pass True, if the message should be sent even if the specified replied-to message is not found
  , SendVideoRequest -> Maybe InlineKeyboardMarkup
sendVideoReplyMarkup :: Maybe InlineKeyboardMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x. Rep SendVideoRequest x -> SendVideoRequest
forall x. SendVideoRequest -> Rep SendVideoRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendVideoRequest x -> SendVideoRequest
$cfrom :: forall x. SendVideoRequest -> Rep SendVideoRequest x
Generic

instance ToJSON SendVideoRequest where toJSON :: SendVideoRequest -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON

instance ToMultipart Tmp SendVideoRequest where
  toMultipart :: SendVideoRequest -> MultipartData Tmp
toMultipart SendVideoRequest{Maybe Bool
Maybe Int
Maybe [MessageEntity]
Maybe Text
Maybe InlineKeyboardMarkup
Maybe InputFile
Maybe MessageId
Maybe ParseMode
SomeChatId
InputFile
sendVideoReplyMarkup :: Maybe InlineKeyboardMarkup
sendVideoAllowSendingWithoutReply :: Maybe Bool
sendVideoReplyToMessageId :: Maybe MessageId
sendVideoProtectContent :: Maybe Bool
sendVideoDisableNotification :: Maybe Bool
sendVideoSupportsStreaming :: Maybe Bool
sendVideoCaptionEntities :: Maybe [MessageEntity]
sendVideoParseMode :: Maybe ParseMode
sendVideoCaption :: Maybe Text
sendVideoThumb :: Maybe InputFile
sendVideoHeight :: Maybe Int
sendVideoWidth :: Maybe Int
sendVideoDuration :: Maybe Int
sendVideoVideo :: InputFile
sendVideoChatId :: SomeChatId
sendVideoReplyMarkup :: SendVideoRequest -> Maybe InlineKeyboardMarkup
sendVideoAllowSendingWithoutReply :: SendVideoRequest -> Maybe Bool
sendVideoReplyToMessageId :: SendVideoRequest -> Maybe MessageId
sendVideoProtectContent :: SendVideoRequest -> Maybe Bool
sendVideoDisableNotification :: SendVideoRequest -> Maybe Bool
sendVideoSupportsStreaming :: SendVideoRequest -> Maybe Bool
sendVideoCaptionEntities :: SendVideoRequest -> Maybe [MessageEntity]
sendVideoParseMode :: SendVideoRequest -> Maybe ParseMode
sendVideoCaption :: SendVideoRequest -> Maybe Text
sendVideoThumb :: SendVideoRequest -> Maybe InputFile
sendVideoHeight :: SendVideoRequest -> Maybe Int
sendVideoWidth :: SendVideoRequest -> Maybe Int
sendVideoDuration :: SendVideoRequest -> Maybe Int
sendVideoVideo :: SendVideoRequest -> InputFile
sendVideoChatId :: SendVideoRequest -> SomeChatId
..} =
    forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"thumb") Maybe InputFile
sendVideoThumb forall a b. (a -> b) -> a -> b
$
    Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"video" InputFile
sendVideoVideo forall a b. (a -> b) -> a -> b
$
    forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [] where
    fields :: [Input]
fields =
      [ Text -> Text -> Input
Input Text
"chat_id" forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendVideoChatId of
          SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> FilePath
show Integer
chat_id
          SomeChatUsername Text
txt -> Text
txt
      ] forall a. Semigroup a => a -> a -> a
<> forall a. [Maybe a] -> [a]
catMaybes
      [ Maybe Text
sendVideoCaption forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Text
t -> Text -> Text -> Input
Input Text
"caption" Text
t
      , Maybe ParseMode
sendVideoParseMode forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \ParseMode
t -> Text -> Text -> Input
Input Text
"parse_mode" (Text -> Text
TL.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text -> Text
TL.replace Text
"\"" Text
"" forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText ParseMode
t)
      , Maybe [MessageEntity]
sendVideoCaptionEntities forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \[MessageEntity]
t -> Text -> Text -> Input
Input Text
"caption_entities" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText [MessageEntity]
t)
      , Maybe Int
sendVideoDuration forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Int
t -> Text -> Text -> Input
Input Text
"duration" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
      , Maybe Int
sendVideoWidth forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Int
t -> Text -> Text -> Input
Input Text
"width" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
      , Maybe Int
sendVideoHeight forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Int
t -> Text -> Text -> Input
Input Text
"height" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
      , Maybe Bool
sendVideoDisableNotification forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"disable_notification" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe Bool
sendVideoSupportsStreaming forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"supports_streaming" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe Bool
sendVideoProtectContent forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"protected_content" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe MessageId
sendVideoReplyToMessageId forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \MessageId
t -> Text -> Text -> Input
Input Text
"reply_to_message_id" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t)
      , Maybe Bool
sendVideoAllowSendingWithoutReply forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"allow_sending_without_reply" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe InlineKeyboardMarkup
sendVideoReplyMarkup forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \InlineKeyboardMarkup
t -> Text -> Text -> Input
Input Text
"reply_markup" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText InlineKeyboardMarkup
t)
      ]

type SendVideoContent
  = "sendVideo"
  :> MultipartForm Tmp SendVideoRequest
  :> Post '[JSON] (Response Message)

type SendVideoLink
  = "sendVideo"
  :> ReqBody '[JSON] SendVideoRequest
  :> Post '[JSON] (Response Message)

-- | Use this method to send video files,
--   Telegram clients support mp4 videos
--   (other formats may be sent as Document).
--   On success, the sent Message is returned.
--   Bots can currently send video files of up
--   to 50 MB in size, this limit may be changed in the future.
sendVideo :: SendVideoRequest ->  ClientM (Response Message)
sendVideo :: SendVideoRequest -> ClientM (Response Message)
sendVideo SendVideoRequest
r = case (SendVideoRequest -> InputFile
sendVideoVideo SendVideoRequest
r, SendVideoRequest -> Maybe InputFile
sendVideoThumb SendVideoRequest
r) of
  (InputFile{}, Maybe InputFile
_) -> do
    ByteString
boundary <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
    forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendVideoContent) (ByteString
boundary, SendVideoRequest
r)
  (InputFile
_, Just InputFile{}) -> do
    ByteString
boundary <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
    forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendVideoContent) (ByteString
boundary, SendVideoRequest
r)
  (InputFile, Maybe InputFile)
_ ->  forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendVideoLink) SendVideoRequest
r

-- | Request parameters for 'sendAnimation'.
data SendAnimationRequest = SendAnimationRequest
  { SendAnimationRequest -> SomeChatId
sendAnimationChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , SendAnimationRequest -> InputFile
sendAnimationAnimation :: InputFile -- ^ Animation to send. Pass a file_id as String to send an animation that exists on the Telegram servers (recommended), pass an HTTP URL as a String for Telegram to get an animation from the Internet, or upload a new animation using multipart/form-data. More info on Sending Files »
  , SendAnimationRequest -> Maybe Int
sendAnimationDuration :: Maybe Int -- ^ Duration of sent animation in seconds
  , SendAnimationRequest -> Maybe Int
sendAnimationWidth :: Maybe Int -- ^ Animation width
  , SendAnimationRequest -> Maybe Int
sendAnimationHeight :: Maybe Int -- ^ Animation height
  , SendAnimationRequest -> Maybe InputFile
sendAnimationThumb :: Maybe InputFile -- ^ Thumbnail of the file sent; can be ignored if thumbnail generation for the file is supported server-side. The thumbnail should be in JPEG format and less than 200 kB in size. A thumbnail's width and height should not exceed 320. Ignored if the file is not uploaded using multipart/form-data. Thumbnails can't be reused and can be only uploaded as a new file, so you can pass “attach://<file_attach_name>” if the thumbnail was uploaded using multipart/form-data under <file_attach_name>. More info on Sending Files »
  , SendAnimationRequest -> Maybe Text
sendAnimationCaption :: Maybe Text -- ^ Animation caption (may also be used when resending animation by file_id), 0-1024 characters after entities parsing
  , SendAnimationRequest -> Maybe ParseMode
sendAnimationParseMode :: Maybe ParseMode  -- ^ Send 'MarkdownV2', 'HTML' or 'Markdown' (legacy), if you want Telegram apps to show bold, italic, fixed-width text or inline URLs in your bot's message.
  , SendAnimationRequest -> Maybe [MessageEntity]
sendAnimationCaptionEntities :: Maybe [MessageEntity] -- ^ A JSON-serialized list of special entities that appear in the caption, which can be specified instead of parse_mode
  , SendAnimationRequest -> Maybe Bool
sendAnimationDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , SendAnimationRequest -> Maybe Bool
sendAnimationProtectContent :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving.
  , SendAnimationRequest -> Maybe MessageId
sendAnimationReplyToMessageId :: Maybe MessageId -- ^ If the message is a reply, ID of the original message.
  , SendAnimationRequest -> Maybe Bool
sendAnimationAllowSendingWithoutReply :: Maybe Bool -- ^ Pass True, if the message should be sent even if the specified replied-to message is not found.
  , SendAnimationRequest -> Maybe InlineKeyboardMarkup
sendAnimationReplyMarkup :: Maybe InlineKeyboardMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x. Rep SendAnimationRequest x -> SendAnimationRequest
forall x. SendAnimationRequest -> Rep SendAnimationRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendAnimationRequest x -> SendAnimationRequest
$cfrom :: forall x. SendAnimationRequest -> Rep SendAnimationRequest x
Generic

instance ToJSON SendAnimationRequest where toJSON :: SendAnimationRequest -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON

instance ToMultipart Tmp SendAnimationRequest where
  toMultipart :: SendAnimationRequest -> MultipartData Tmp
toMultipart SendAnimationRequest{Maybe Bool
Maybe Int
Maybe [MessageEntity]
Maybe Text
Maybe InlineKeyboardMarkup
Maybe InputFile
Maybe MessageId
Maybe ParseMode
SomeChatId
InputFile
sendAnimationReplyMarkup :: Maybe InlineKeyboardMarkup
sendAnimationAllowSendingWithoutReply :: Maybe Bool
sendAnimationReplyToMessageId :: Maybe MessageId
sendAnimationProtectContent :: Maybe Bool
sendAnimationDisableNotification :: Maybe Bool
sendAnimationCaptionEntities :: Maybe [MessageEntity]
sendAnimationParseMode :: Maybe ParseMode
sendAnimationCaption :: Maybe Text
sendAnimationThumb :: Maybe InputFile
sendAnimationHeight :: Maybe Int
sendAnimationWidth :: Maybe Int
sendAnimationDuration :: Maybe Int
sendAnimationAnimation :: InputFile
sendAnimationChatId :: SomeChatId
sendAnimationReplyMarkup :: SendAnimationRequest -> Maybe InlineKeyboardMarkup
sendAnimationAllowSendingWithoutReply :: SendAnimationRequest -> Maybe Bool
sendAnimationReplyToMessageId :: SendAnimationRequest -> Maybe MessageId
sendAnimationProtectContent :: SendAnimationRequest -> Maybe Bool
sendAnimationDisableNotification :: SendAnimationRequest -> Maybe Bool
sendAnimationCaptionEntities :: SendAnimationRequest -> Maybe [MessageEntity]
sendAnimationParseMode :: SendAnimationRequest -> Maybe ParseMode
sendAnimationCaption :: SendAnimationRequest -> Maybe Text
sendAnimationThumb :: SendAnimationRequest -> Maybe InputFile
sendAnimationHeight :: SendAnimationRequest -> Maybe Int
sendAnimationWidth :: SendAnimationRequest -> Maybe Int
sendAnimationDuration :: SendAnimationRequest -> Maybe Int
sendAnimationAnimation :: SendAnimationRequest -> InputFile
sendAnimationChatId :: SendAnimationRequest -> SomeChatId
..} =
    forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"thumb") Maybe InputFile
sendAnimationThumb forall a b. (a -> b) -> a -> b
$
    Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"animation" InputFile
sendAnimationAnimation forall a b. (a -> b) -> a -> b
$
    forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [] where
    fields :: [Input]
fields =
      [ Text -> Text -> Input
Input Text
"chat_id" forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendAnimationChatId of
          SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> FilePath
show Integer
chat_id
          SomeChatUsername Text
txt -> Text
txt
      ] forall a. Semigroup a => a -> a -> a
<> forall a. [Maybe a] -> [a]
catMaybes
      [ Maybe Text
sendAnimationCaption forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Text
t -> Text -> Text -> Input
Input Text
"caption" Text
t
      , Maybe ParseMode
sendAnimationParseMode forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \ParseMode
t -> Text -> Text -> Input
Input Text
"parse_mode" (Text -> Text
TL.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text -> Text
TL.replace Text
"\"" Text
"" forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText ParseMode
t)
      , Maybe [MessageEntity]
sendAnimationCaptionEntities forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \[MessageEntity]
t -> Text -> Text -> Input
Input Text
"caption_entities" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText [MessageEntity]
t)
      , Maybe Int
sendAnimationDuration forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Int
t -> Text -> Text -> Input
Input Text
"duration" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
      , Maybe Int
sendAnimationWidth forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Int
t -> Text -> Text -> Input
Input Text
"width" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
      , Maybe Int
sendAnimationHeight forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Int
t -> Text -> Text -> Input
Input Text
"height" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
      , Maybe Bool
sendAnimationDisableNotification forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"disable_notification" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe Bool
sendAnimationProtectContent forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"protected_content" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe MessageId
sendAnimationReplyToMessageId forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \MessageId
t -> Text -> Text -> Input
Input Text
"reply_to_message_id" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t)
      , Maybe Bool
sendAnimationAllowSendingWithoutReply forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"allow_sending_without_reply" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe InlineKeyboardMarkup
sendAnimationReplyMarkup forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \InlineKeyboardMarkup
t -> Text -> Text -> Input
Input Text
"reply_markup" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText InlineKeyboardMarkup
t)
      ]

type SendAnimationContent
  = "sendAnimation"
  :> MultipartForm Tmp SendAnimationRequest
  :> Post '[JSON] (Response Message)

type SendAnimationLink
  = "sendAnimation"
  :> ReqBody '[JSON] SendAnimationRequest
  :> Post '[JSON] (Response Message)

-- | Use this method to send animation files
--   (GIF or H.264/MPEG-4 AVC video without sound).
--   On success, the sent Message is returned. Bots
--   can currently send animation files of up to 50
--   MB in size, this limit may be changed in the future.
sendAnimation :: SendAnimationRequest ->  ClientM (Response Message)
sendAnimation :: SendAnimationRequest -> ClientM (Response Message)
sendAnimation SendAnimationRequest
r = case (SendAnimationRequest -> InputFile
sendAnimationAnimation SendAnimationRequest
r, SendAnimationRequest -> Maybe InputFile
sendAnimationThumb SendAnimationRequest
r) of
  (InputFile{}, Maybe InputFile
_) -> do
    ByteString
boundary <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
    forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendAnimationContent) (ByteString
boundary, SendAnimationRequest
r)
  (InputFile
_, Just InputFile{}) -> do
    ByteString
boundary <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
    forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendAnimationContent) (ByteString
boundary, SendAnimationRequest
r)
  (InputFile, Maybe InputFile)
_ ->  forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendAnimationLink) SendAnimationRequest
r

-- | Request parameters for 'sendVoice'.
data SendVoiceRequest = SendVoiceRequest
  { SendVoiceRequest -> SomeChatId
sendVoiceChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , SendVoiceRequest -> InputFile
sendVoiceVoice :: InputFile -- ^ Audio file to send. Pass a file_id as String to send a file that exists on the Telegram servers (recommended), pass an HTTP URL as a String for Telegram to get a file from the Internet, or upload a new one using multipart/form-data. More info on Sending Files »
  , SendVoiceRequest -> Maybe Text
sendVoiceCaption :: Maybe Text -- ^ Voice message caption, 0-1024 characters after entities parsing
  , SendVoiceRequest -> Maybe ParseMode
sendVoiceParseMode :: Maybe ParseMode  -- ^ Send 'MarkdownV2', 'HTML' or 'Markdown' (legacy), if you want Telegram apps to show bold, italic, fixed-width text or inline URLs in your bot's message.
  , SendVoiceRequest -> Maybe [MessageEntity]
sendVoiceCaptionEntities :: Maybe [MessageEntity] -- ^ A JSON-serialized list of special entities that appear in the caption, which can be specified instead of parse_mode
  , SendVoiceRequest -> Maybe Int
sendVoiceDuration :: Maybe Int -- ^ Duration of the voice message in seconds
  , SendVoiceRequest -> Maybe Bool
sendVoiceDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , SendVoiceRequest -> Maybe Bool
sendVoiceProtectContent :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving
  , SendVoiceRequest -> Maybe MessageId
sendVoiceReplyToMessageId :: Maybe MessageId -- ^ If the message is a reply, ID of the original message
  , SendVoiceRequest -> Maybe Bool
sendVoiceAllowSendingWithoutReply :: Maybe Bool -- ^ Pass True, if the message should be sent even if the specified replied-to message is not found
  , SendVoiceRequest -> Maybe InlineKeyboardMarkup
sendVoiceReplyMarkup :: Maybe InlineKeyboardMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x. Rep SendVoiceRequest x -> SendVoiceRequest
forall x. SendVoiceRequest -> Rep SendVoiceRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendVoiceRequest x -> SendVoiceRequest
$cfrom :: forall x. SendVoiceRequest -> Rep SendVoiceRequest x
Generic

instance ToJSON SendVoiceRequest where toJSON :: SendVoiceRequest -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON

instance ToMultipart Tmp SendVoiceRequest where
  toMultipart :: SendVoiceRequest -> MultipartData Tmp
toMultipart SendVoiceRequest{Maybe Bool
Maybe Int
Maybe [MessageEntity]
Maybe Text
Maybe InlineKeyboardMarkup
Maybe MessageId
Maybe ParseMode
SomeChatId
InputFile
sendVoiceReplyMarkup :: Maybe InlineKeyboardMarkup
sendVoiceAllowSendingWithoutReply :: Maybe Bool
sendVoiceReplyToMessageId :: Maybe MessageId
sendVoiceProtectContent :: Maybe Bool
sendVoiceDisableNotification :: Maybe Bool
sendVoiceDuration :: Maybe Int
sendVoiceCaptionEntities :: Maybe [MessageEntity]
sendVoiceParseMode :: Maybe ParseMode
sendVoiceCaption :: Maybe Text
sendVoiceVoice :: InputFile
sendVoiceChatId :: SomeChatId
sendVoiceReplyMarkup :: SendVoiceRequest -> Maybe InlineKeyboardMarkup
sendVoiceAllowSendingWithoutReply :: SendVoiceRequest -> Maybe Bool
sendVoiceReplyToMessageId :: SendVoiceRequest -> Maybe MessageId
sendVoiceProtectContent :: SendVoiceRequest -> Maybe Bool
sendVoiceDisableNotification :: SendVoiceRequest -> Maybe Bool
sendVoiceDuration :: SendVoiceRequest -> Maybe Int
sendVoiceCaptionEntities :: SendVoiceRequest -> Maybe [MessageEntity]
sendVoiceParseMode :: SendVoiceRequest -> Maybe ParseMode
sendVoiceCaption :: SendVoiceRequest -> Maybe Text
sendVoiceVoice :: SendVoiceRequest -> InputFile
sendVoiceChatId :: SendVoiceRequest -> SomeChatId
..} =
    Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"voice" InputFile
sendVoiceVoice forall a b. (a -> b) -> a -> b
$
    forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [] where
    fields :: [Input]
fields =
      [ Text -> Text -> Input
Input Text
"chat_id" forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendVoiceChatId of
          SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> FilePath
show Integer
chat_id
          SomeChatUsername Text
txt -> Text
txt
      ] forall a. Semigroup a => a -> a -> a
<> forall a. [Maybe a] -> [a]
catMaybes
      [ Maybe Text
sendVoiceCaption forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Text
t -> Text -> Text -> Input
Input Text
"caption" Text
t
      , Maybe ParseMode
sendVoiceParseMode forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \ParseMode
t -> Text -> Text -> Input
Input Text
"parse_mode" (Text -> Text
TL.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text -> Text
TL.replace Text
"\"" Text
"" forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText ParseMode
t)
      , Maybe [MessageEntity]
sendVoiceCaptionEntities forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \[MessageEntity]
t -> Text -> Text -> Input
Input Text
"caption_entities" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText [MessageEntity]
t)
      , Maybe Int
sendVoiceDuration forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Int
t -> Text -> Text -> Input
Input Text
"duration" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
      , Maybe Bool
sendVoiceProtectContent forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"protected_content" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe Bool
sendVoiceDisableNotification forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"disable_notification" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe MessageId
sendVoiceReplyToMessageId forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \MessageId
t -> Text -> Text -> Input
Input Text
"reply_to_message_id" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t)
      , Maybe Bool
sendVoiceAllowSendingWithoutReply forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"allow_sending_without_reply" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe InlineKeyboardMarkup
sendVoiceReplyMarkup forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \InlineKeyboardMarkup
t -> Text -> Text -> Input
Input Text
"reply_markup" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText InlineKeyboardMarkup
t)
      ]

type SendVoiceContent
  = "sendVoice"
  :> MultipartForm Tmp SendVoiceRequest
  :> Post '[JSON] (Response Message)

type SendVoiceLink
  = "sendVoice"
  :> ReqBody '[JSON] SendVoiceRequest
  :> Post '[JSON] (Response Message)

-- | Use this method to send audio files,
--   if you want Telegram clients to display
--   the file as a playable voice message. For
--   this to work, your audio must be in an .OGG
--   file encoded with OPUS (other formats may be
--   sent as Audio or Document).
--   On success, the sent Message is returned.
--   Bots can currently send voice messages of up
--   to 50 MB in size, this limit may be changed in the future.
sendVoice :: SendVoiceRequest ->  ClientM (Response Message)
sendVoice :: SendVoiceRequest -> ClientM (Response Message)
sendVoice SendVoiceRequest
r = case SendVoiceRequest -> InputFile
sendVoiceVoice SendVoiceRequest
r of
  InputFile{} -> do
    ByteString
boundary <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
    forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendVoiceContent) (ByteString
boundary, SendVoiceRequest
r)
  InputFile
_ ->  forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendVoiceLink) SendVoiceRequest
r

-- | Request parameters for 'sendVideoNote'.
data SendVideoNoteRequest = SendVideoNoteRequest
  { SendVideoNoteRequest -> SomeChatId
sendVideoNoteChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , SendVideoNoteRequest -> InputFile
sendVideoNoteVideoNote :: InputFile -- ^ Video note to send. Pass a file_id as String to send a video note that exists on the Telegram servers (recommended) or upload a new video using multipart/form-data. More info on Sending Files ». Sending video notes by a URL is currently unsupported
  , SendVideoNoteRequest -> Maybe Int
sendVideoNoteDuration :: Maybe Int -- ^ Duration of sent video in seconds
  , SendVideoNoteRequest -> Maybe Int
sendVideoNoteLength :: Maybe Int -- ^ Video width and height, i.e. diameter of the video message
  , SendVideoNoteRequest -> Maybe InputFile
sendVideoNoteThumb :: Maybe InputFile -- ^ Thumbnail of the file sent; can be ignored if thumbnail generation for the file is supported server-side. The thumbnail should be in JPEG format and less than 200 kB in size. A thumbnail's width and height should not exceed 320. Ignored if the file is not uploaded using multipart/form-data. Thumbnails can't be reused and can be only uploaded as a new file, so you can pass “attach://<file_attach_name>” if the thumbnail was uploaded using multipart/form-data under <file_attach_name>. More info on Sending Files »
  , SendVideoNoteRequest -> Maybe Bool
sendVideoNoteDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , SendVideoNoteRequest -> Maybe Bool
sendVideoNoteProtectContent :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving
  , SendVideoNoteRequest -> Maybe MessageId
sendVideoNoteReplyToMessageId :: Maybe MessageId -- ^ If the message is a reply, ID of the original message
  , SendVideoNoteRequest -> Maybe Bool
sendVideoNoteAllowSendingWithoutReply :: Maybe Bool -- ^ Pass True, if the message should be sent even if the specified replied-to message is not found
  , SendVideoNoteRequest -> Maybe InlineKeyboardMarkup
sendVideoNoteReplyMarkup :: Maybe InlineKeyboardMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x. Rep SendVideoNoteRequest x -> SendVideoNoteRequest
forall x. SendVideoNoteRequest -> Rep SendVideoNoteRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendVideoNoteRequest x -> SendVideoNoteRequest
$cfrom :: forall x. SendVideoNoteRequest -> Rep SendVideoNoteRequest x
Generic

instance ToJSON SendVideoNoteRequest where toJSON :: SendVideoNoteRequest -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON

instance ToMultipart Tmp SendVideoNoteRequest where
  toMultipart :: SendVideoNoteRequest -> MultipartData Tmp
toMultipart SendVideoNoteRequest{Maybe Bool
Maybe Int
Maybe InlineKeyboardMarkup
Maybe InputFile
Maybe MessageId
SomeChatId
InputFile
sendVideoNoteReplyMarkup :: Maybe InlineKeyboardMarkup
sendVideoNoteAllowSendingWithoutReply :: Maybe Bool
sendVideoNoteReplyToMessageId :: Maybe MessageId
sendVideoNoteProtectContent :: Maybe Bool
sendVideoNoteDisableNotification :: Maybe Bool
sendVideoNoteThumb :: Maybe InputFile
sendVideoNoteLength :: Maybe Int
sendVideoNoteDuration :: Maybe Int
sendVideoNoteVideoNote :: InputFile
sendVideoNoteChatId :: SomeChatId
sendVideoNoteReplyMarkup :: SendVideoNoteRequest -> Maybe InlineKeyboardMarkup
sendVideoNoteAllowSendingWithoutReply :: SendVideoNoteRequest -> Maybe Bool
sendVideoNoteReplyToMessageId :: SendVideoNoteRequest -> Maybe MessageId
sendVideoNoteProtectContent :: SendVideoNoteRequest -> Maybe Bool
sendVideoNoteDisableNotification :: SendVideoNoteRequest -> Maybe Bool
sendVideoNoteThumb :: SendVideoNoteRequest -> Maybe InputFile
sendVideoNoteLength :: SendVideoNoteRequest -> Maybe Int
sendVideoNoteDuration :: SendVideoNoteRequest -> Maybe Int
sendVideoNoteVideoNote :: SendVideoNoteRequest -> InputFile
sendVideoNoteChatId :: SendVideoNoteRequest -> SomeChatId
..} =
    forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id (Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"thumb") Maybe InputFile
sendVideoNoteThumb forall a b. (a -> b) -> a -> b
$
    Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"video_note" InputFile
sendVideoNoteVideoNote forall a b. (a -> b) -> a -> b
$
    forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [] where
    fields :: [Input]
fields =
      [ Text -> Text -> Input
Input Text
"chat_id" forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendVideoNoteChatId of
          SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> FilePath
show Integer
chat_id
          SomeChatUsername Text
txt -> Text
txt
      ] forall a. Semigroup a => a -> a -> a
<> forall a. [Maybe a] -> [a]
catMaybes
      [ Maybe Bool
sendVideoNoteDisableNotification forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"disable_notification" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe Bool
sendVideoNoteProtectContent forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"protected_content" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe MessageId
sendVideoNoteReplyToMessageId forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \MessageId
t -> Text -> Text -> Input
Input Text
"reply_to_message_id" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t)
      , Maybe Bool
sendVideoNoteAllowSendingWithoutReply forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \Bool
t -> Text -> Text -> Input
Input Text
"allow_sending_without_reply" (forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
      , Maybe InlineKeyboardMarkup
sendVideoNoteReplyMarkup forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
        \InlineKeyboardMarkup
t -> Text -> Text -> Input
Input Text
"reply_markup" (Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ forall a. ToJSON a => a -> Text
encodeToLazyText InlineKeyboardMarkup
t)
      ]

type SendVideoNoteContent
  = "sendVideoNote"
  :> MultipartForm Tmp SendVideoNoteRequest
  :> Post '[JSON] (Response Message)

type SendVideoNoteLink
  = "sendVideoNote"
  :> ReqBody '[JSON] SendVideoNoteRequest
  :> Post '[JSON] (Response Message)

-- | As of v.4.0, Telegram clients support rounded
--   square mp4 videos of up to 1 minute long. Use
--   this method to send video messages.
--   On success, the sent Message is returned.
sendVideoNote :: SendVideoNoteRequest ->  ClientM (Response Message)
sendVideoNote :: SendVideoNoteRequest -> ClientM (Response Message)
sendVideoNote SendVideoNoteRequest
r = case (SendVideoNoteRequest -> InputFile
sendVideoNoteVideoNote SendVideoNoteRequest
r, SendVideoNoteRequest -> Maybe InputFile
sendVideoNoteThumb SendVideoNoteRequest
r) of
  (InputFile{}, Maybe InputFile
_) -> do
    ByteString
boundary <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
    forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendVideoNoteContent) (ByteString
boundary, SendVideoNoteRequest
r)
  (InputFile
_, Just InputFile{}) -> do
    ByteString
boundary <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
    forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendVideoNoteContent) (ByteString
boundary, SendVideoNoteRequest
r)
  (InputFile, Maybe InputFile)
_ ->  forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendVideoNoteLink) SendVideoNoteRequest
r

-- | Request parameters for 'sendMediaGroup'.
data SendMediaGroupRequest = SendMediaGroupRequest
  { SendMediaGroupRequest -> SomeChatId
sendMediaGroupChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , SendMediaGroupRequest -> [InputMedia]
sendMediaGroupMedia :: [InputMedia] -- ^ A JSON-serialized array describing messages to be sent, must include 2-10 items. InputMediaAudio, InputMediaDocument, InputMediaPhoto or InputMediaVideo.
  , SendMediaGroupRequest -> Maybe Bool
sendMediaGroupDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , SendMediaGroupRequest -> Maybe Bool
sendMediaGroupProtectContent :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving
  , SendMediaGroupRequest -> Maybe MessageId
sendMediaGroupReplyToMessageId :: Maybe MessageId -- ^ If the message is a reply, ID of the original message
  , SendMediaGroupRequest -> Maybe Bool
sendMediaGroupAllowSendingWithoutReply :: Maybe Bool -- ^ Pass True, if the message should be sent even if the specified replied-to message is not found
  , SendMediaGroupRequest -> Maybe InlineKeyboardMarkup
sendMediaGroupReplyMarkup :: Maybe InlineKeyboardMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x. Rep SendMediaGroupRequest x -> SendMediaGroupRequest
forall x. SendMediaGroupRequest -> Rep SendMediaGroupRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendMediaGroupRequest x -> SendMediaGroupRequest
$cfrom :: forall x. SendMediaGroupRequest -> Rep SendMediaGroupRequest x
Generic

instance ToJSON SendMediaGroupRequest where toJSON :: SendMediaGroupRequest -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON

type SendMediaGroup = "sendMediaGroup"
  :> ReqBody '[JSON] SendMediaGroupRequest
  :> Post '[JSON] (Response [Message])

-- | Use this method to send a group of photos, videos,
--   documents or audios as an album. Documents
--   and audio files can be only grouped in an album
--   with messages of the same type.
--   On success, an array of Messages that were sent is returned.
sendMediaGroup :: SendMediaGroupRequest ->  ClientM (Response [Message])
sendMediaGroup :: SendMediaGroupRequest -> ClientM (Response [Message])
sendMediaGroup = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendMediaGroup)

-- | Request parameters for 'sendLocation'.
data SendLocationRequest = SendLocationRequest
  { SendLocationRequest -> SomeChatId
sendLocationChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , SendLocationRequest -> Float
sendLocationLatitude :: Float -- ^ Latitude of new location
  , SendLocationRequest -> Float
sendLocationLongitude :: Float -- ^ Longitude of new location
  , SendLocationRequest -> Maybe Float
sendLocationHorizontalAccuracy :: Maybe Float -- ^ The radius of uncertainty for the location, measured in meters; 0-1500
  , SendLocationRequest -> Int
sendLocationLivePeriod :: Int -- ^ Period in seconds for which the location will be updated (see Live Locations, should be between 60 and 86400.)
  , SendLocationRequest -> Maybe Int
sendLocationHeading :: Maybe Int -- ^ Direction in which the user is moving, in degrees. Must be between 1 and 360 if specified.
  , SendLocationRequest -> Maybe Int
sendLocationProximityAlertRadius :: Maybe Int  -- ^ Maximum distance for proximity alerts about approaching another chat member, in meters. Must be between 1 and 100000 if specified.
  , SendLocationRequest -> Maybe Bool
sendLocationDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , SendLocationRequest -> Maybe Bool
sendLocationProtectContent :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving
  , SendLocationRequest -> Maybe MessageId
sendLocationReplyToMessageId :: Maybe MessageId -- ^ If the message is a reply, ID of the original message
  , SendLocationRequest -> Maybe Bool
sendLocationAllowSendingWithoutReply :: Maybe Bool -- ^ Pass True, if the message should be sent even if the specified replied-to message is not found
  , SendLocationRequest -> Maybe InlineKeyboardMarkup
sendLocationReplyMarkup :: Maybe InlineKeyboardMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x. Rep SendLocationRequest x -> SendLocationRequest
forall x. SendLocationRequest -> Rep SendLocationRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendLocationRequest x -> SendLocationRequest
$cfrom :: forall x. SendLocationRequest -> Rep SendLocationRequest x
Generic

-- | Request parameters for 'editMessageLiveLocation'.
data EditMessageLiveLocationRequest = EditMessageLiveLocationRequest
  { EditMessageLiveLocationRequest -> Maybe SomeChatId
editMessageLiveLocationChatId :: Maybe SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , EditMessageLiveLocationRequest -> Maybe MessageId
editMessageLiveLocationMessageId :: Maybe MessageId -- ^ Required if inline_message_id is not specified. Identifier of the message with live location to stop
  , EditMessageLiveLocationRequest -> Maybe Text
editMessageLiveLocationInlineMessageId :: Maybe Text -- ^  	Required if chat_id and message_id are not specified. Identifier of the inline message
  , EditMessageLiveLocationRequest -> Float
editMessageLiveLocationLatitude :: Float -- ^ Latitude of new location
  , EditMessageLiveLocationRequest -> Float
editMessageLiveLocationLongitude :: Float -- ^ Longitude of new location
  , EditMessageLiveLocationRequest -> Maybe Float
editMessageLiveLocationHorizontalAccuracy :: Maybe Float -- ^ The radius of uncertainty for the location, measured in meters; 0-1500
  , EditMessageLiveLocationRequest -> Maybe Int
editMessageLiveLocationHeading :: Maybe Int -- ^ Direction in which the user is moving, in degrees. Must be between 1 and 360 if specified.
  , EditMessageLiveLocationRequest -> Maybe Int
editMessageLiveLocationProximityAlertRadius :: Maybe Int  -- ^ Maximum distance for proximity alerts about approaching another chat member, in meters. Must be between 1 and 100000 if specified.
  , EditMessageLiveLocationRequest -> Maybe InlineKeyboardMarkup
editMessageLiveLocationReplyMarkup :: Maybe InlineKeyboardMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x.
Rep EditMessageLiveLocationRequest x
-> EditMessageLiveLocationRequest
forall x.
EditMessageLiveLocationRequest
-> Rep EditMessageLiveLocationRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EditMessageLiveLocationRequest x
-> EditMessageLiveLocationRequest
$cfrom :: forall x.
EditMessageLiveLocationRequest
-> Rep EditMessageLiveLocationRequest x
Generic

-- | Request parameters for 'stopMessageLiveLocation'.
data StopMessageLiveLocationRequest = StopMessageLiveLocationRequest
  { StopMessageLiveLocationRequest -> Maybe SomeChatId
stopMessageLiveLocationChatId :: Maybe SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , StopMessageLiveLocationRequest -> Maybe MessageId
stopMessageLiveLocationMessageId :: Maybe MessageId -- ^ Required if inline_message_id is not specified. Identifier of the message with live location to stop
  , StopMessageLiveLocationRequest -> Maybe Text
stopMessageLiveLocationInlineMessageId :: Maybe Text -- ^  	Required if chat_id and message_id are not specified. Identifier of the inline message
  , StopMessageLiveLocationRequest -> Maybe InlineKeyboardMarkup
stopMessageLiveLocationReplyMarkup :: Maybe InlineKeyboardMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x.
Rep StopMessageLiveLocationRequest x
-> StopMessageLiveLocationRequest
forall x.
StopMessageLiveLocationRequest
-> Rep StopMessageLiveLocationRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StopMessageLiveLocationRequest x
-> StopMessageLiveLocationRequest
$cfrom :: forall x.
StopMessageLiveLocationRequest
-> Rep StopMessageLiveLocationRequest x
Generic

-- | Request parameters for 'sendVenue'.
data SendVenueRequest = SendVenueRequest
  { SendVenueRequest -> SomeChatId
sendVenueChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , SendVenueRequest -> Float
sendVenueLatitude :: Float -- ^ Latitude of the venue
  , SendVenueRequest -> Float
sendVenueLongitude :: Float -- ^ Longitude of the venue
  , SendVenueRequest -> Text
sendVenueTitle :: Text -- ^ Name of the venue
  , SendVenueRequest -> Text
sendVenueAddress :: Text -- ^ Address of the venue
  , SendVenueRequest -> Maybe Text
sendVenueFoursquareId :: Maybe Text -- ^ Foursquare identifier of the venue
  , SendVenueRequest -> Maybe Text
sendVenueFoursquareType :: Maybe Text -- ^ Foursquare type of the venue, if known. (For example, “arts_entertainment/default”, “arts_entertainment/aquarium” or “food/icecream”.)
  , SendVenueRequest -> Maybe Text
sendVenueGooglePlaceId :: Maybe Text -- ^ Google Places identifier of the venue
  , SendVenueRequest -> Maybe Text
sendVenueGooglePlaceType :: Maybe Text -- ^ Google Places type of the venue. (See supported types <https:\/\/developers.google.com\/maps\/documentation\/places\/web-service\/supported_types>.)
  , SendVenueRequest -> Maybe Bool
sendVenueDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , SendVenueRequest -> Maybe Bool
sendVenueProtectContent :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving
  , SendVenueRequest -> Maybe MessageId
sendVenueReplyToMessageId :: Maybe MessageId -- ^ If the message is a reply, ID of the original message
  , SendVenueRequest -> Maybe Bool
sendVenueAllowSendingWithoutReply :: Maybe Bool -- ^ Pass True, if the message should be sent even if the specified replied-to message is not found
  , SendVenueRequest -> Maybe InlineKeyboardMarkup
sendVenueReplyMarkup :: Maybe InlineKeyboardMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x. Rep SendVenueRequest x -> SendVenueRequest
forall x. SendVenueRequest -> Rep SendVenueRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendVenueRequest x -> SendVenueRequest
$cfrom :: forall x. SendVenueRequest -> Rep SendVenueRequest x
Generic

-- | Request parameters for 'sendContact'.
data SendContactRequest = SendContactRequest
  { SendContactRequest -> SomeChatId
sendContactChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , SendContactRequest -> Text
sendContactPhoneNumber :: Text -- ^ Contact's phone number
  , SendContactRequest -> Text
sendContactFirstName  :: Text -- ^ Contact's first name
  , SendContactRequest -> Text
sendContactLastName  :: Text -- ^ Contact's last name
  , SendContactRequest -> Text
sendContactVcard  :: Text -- ^ Additional data about the contact in the form of a vCard, 0-2048 bytes
  , SendContactRequest -> Maybe Bool
sendContactDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , SendContactRequest -> Maybe Bool
sendContactProtectContent :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving
  , SendContactRequest -> Maybe MessageId
sendContactReplyToMessageId :: Maybe MessageId -- ^ If the message is a reply, ID of the original message
  , SendContactRequest -> Maybe Bool
sendContactAllowSendingWithoutReply :: Maybe Bool -- ^ Pass True, if the message should be sent even if the specified replied-to message is not found
  , SendContactRequest -> Maybe InlineKeyboardMarkup
sendContactReplyMarkup :: Maybe InlineKeyboardMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x. Rep SendContactRequest x -> SendContactRequest
forall x. SendContactRequest -> Rep SendContactRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendContactRequest x -> SendContactRequest
$cfrom :: forall x. SendContactRequest -> Rep SendContactRequest x
Generic

-- | Request parameters for 'sendPoll'.
data SendPollRequest = SendPollRequest
  { SendPollRequest -> SomeChatId
sendPollChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , SendPollRequest -> Text
sendPollQuestion :: Text -- ^ Poll question, 1-300 characters
  , SendPollRequest -> [Text]
sendPollOptions :: [Text] -- ^ A JSON-serialized list of answer options, 2-10 strings 1-100 characters each
  , SendPollRequest -> Maybe Bool
sendPollIsAnonymous :: Maybe Bool -- ^ True, if the poll needs to be anonymous, defaults to True
  , SendPollRequest -> Maybe Text
sendPollType :: Maybe Text -- ^ Poll type, “quiz” or “regular”, defaults to “regular”
  , SendPollRequest -> Maybe Bool
sendPollAllowsMultipleAnswers :: Maybe Bool -- ^ True, if the poll allows multiple answers, ignored for polls in quiz mode, defaults to False
  , SendPollRequest -> Maybe Int
sendPollCorrectOptionId :: Maybe Int -- ^ 0-based identifier of the correct answer option, required for polls in quiz mode
  , SendPollRequest -> Maybe Text
sendPollExplanation :: Maybe Text -- ^ Text that is shown when a user chooses an incorrect answer or taps on the lamp icon in a quiz-style poll, 0-200 characters with at most 2 line feeds after entities parsing
  , SendPollRequest -> Maybe ParseMode
sendPollExplanationParseMode :: Maybe ParseMode  -- ^ Send 'MarkdownV2', 'HTML' or 'Markdown' (legacy), if you want Telegram apps to show bold, italic, fixed-width text or inline URLs in your bot's message.
  , SendPollRequest -> Maybe [MessageEntity]
sendPollExplanationEntities :: Maybe [MessageEntity] -- ^ A JSON-serialized list of special entities that appear in the poll explanation, which can be specified instead of parse_mode
  , SendPollRequest -> Maybe Int
sendPollOpenPeriod :: Maybe Int -- ^ Amount of time in seconds the poll will be active after creation, 5-600. Can't be used together with close_date.
  , SendPollRequest -> Maybe Int
sendPollCloseDate :: Maybe Int -- ^ Point in time (Unix timestamp) when the poll will be automatically closed. Must be at least 5 and no more than 600 seconds in the future. Can't be used together with open_period.
  , SendPollRequest -> Maybe Bool
sendPollIsClosed :: Maybe Bool -- ^ Pass True, if the poll needs to be immediately closed. This can be useful for poll preview.
  , SendPollRequest -> Maybe Bool
sendPollDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , SendPollRequest -> Maybe Bool
sendPollProtectContent :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding and saving
  , SendPollRequest -> Maybe MessageId
sendPollReplyToMessageId :: Maybe MessageId -- ^ If the message is a reply, ID of the original message
  , SendPollRequest -> Maybe Bool
sendPollAllowSendingWithoutReply :: Maybe Bool -- ^ Pass True, if the message should be sent even if the specified replied-to message is not found
  , SendPollRequest -> Maybe InlineKeyboardMarkup
sendPollReplyMarkup :: Maybe InlineKeyboardMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x. Rep SendPollRequest x -> SendPollRequest
forall x. SendPollRequest -> Rep SendPollRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendPollRequest x -> SendPollRequest
$cfrom :: forall x. SendPollRequest -> Rep SendPollRequest x
Generic

-- | Request parameters for 'sendDice'.
data SendDiceRequest = SendDiceRequest
  { SendDiceRequest -> SomeChatId
sendDiceChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , SendDiceRequest -> Maybe Text
sendDiceEmoji :: Maybe Text -- ^ Emoji on which the dice throw animation is based. Currently, must be one of “🎲”, “🎯”, “🏀”, “⚽”, “🎳”, or “🎰”. Dice can have values 1-6 for “🎲”, “🎯” and “🎳”, values 1-5 for “🏀” and “⚽”, and values 1-64 for “🎰”. Defaults to “🎲”
  , SendDiceRequest -> Maybe Bool
sendDiceDisableNotification :: Maybe Bool -- ^ Sends the message silently. Users will receive a notification with no sound.
  , SendDiceRequest -> Maybe Bool
sendDiceProtectContent :: Maybe Bool -- ^ Protects the contents of the sent message from forwarding
  , SendDiceRequest -> Maybe MessageId
sendDiceReplyToMessageId :: Maybe MessageId -- ^ If the message is a reply, ID of the original message
  , SendDiceRequest -> Maybe Bool
sendDiceAllowSendingWithoutReply :: Maybe Bool -- ^ Pass True, if the message should be sent even if the specified replied-to message is not found
  , SendDiceRequest -> Maybe InlineKeyboardMarkup
sendDiceReplyMarkup :: Maybe InlineKeyboardMarkup -- ^ Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.
  }
  deriving forall x. Rep SendDiceRequest x -> SendDiceRequest
forall x. SendDiceRequest -> Rep SendDiceRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendDiceRequest x -> SendDiceRequest
$cfrom :: forall x. SendDiceRequest -> Rep SendDiceRequest x
Generic

type SendChatAction = "sendChatAction"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> RequiredQueryParam "action" Text
  :> Post '[JSON] (Response Bool)

-- | Use this method when you need to tell the
--   user that something is happening on the bot's side.
--   The status is set for 5 seconds or less
--   (when a message arrives from your bot, Telegram
--   clients clear its typing status).
--   Returns True on success.
--
--   Example: The ImageBot needs some time to
--   process a request and upload the image.
--   Instead of sending a text message along
--   the lines of “Retrieving image, please wait…”,
--   the bot may use sendChatAction with action = upload_photo.
--   The user will see a “sending photo” status for the bot.
--
--   We only recommend using this method when a
--   response from the bot will take a noticeable
--   amount of time to arrive.
sendChatAction :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> Text -- ^ Type of action to broadcast. Choose one, depending on what the user is about to receive: typing for text messages, upload_photo for photos, record_video or upload_video for videos, record_voice or upload_voice for voice notes, upload_document for general files, choose_sticker for stickers, find_location for location data, record_video_note or upload_video_note for video notes.
  -> ClientM (Response  Bool)
sendChatAction :: SomeChatId -> Text -> ClientM (Response Bool)
sendChatAction = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendChatAction)

-- | Request parameters for 'getUserProfilePhotos'.
data GetUserProfilePhotosRequest = GetUserProfilePhotosRequest
  { GetUserProfilePhotosRequest -> UserId
getUserProfilePhotosUserId :: UserId -- ^ Unique identifier of the target user
  , GetUserProfilePhotosRequest -> Maybe Int
getUserProfilePhotosOffset :: Maybe Int -- ^ Sequential number of the first photo to be returned. By default, all photos are returned.
  , GetUserProfilePhotosRequest -> Maybe Int
getUserProfilePhotosLimit :: Maybe Int -- ^ Limits the number of photos to be retrieved. Values between 1-100 are accepted. Defaults to 100.
  }
  deriving forall x.
Rep GetUserProfilePhotosRequest x -> GetUserProfilePhotosRequest
forall x.
GetUserProfilePhotosRequest -> Rep GetUserProfilePhotosRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetUserProfilePhotosRequest x -> GetUserProfilePhotosRequest
$cfrom :: forall x.
GetUserProfilePhotosRequest -> Rep GetUserProfilePhotosRequest x
Generic

-- | Request parameters for 'banChatMember'.
data BanChatMemberRequest = BanChatMemberRequest
  { BanChatMemberRequest -> SomeChatId
banChatMemberChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , BanChatMemberRequest -> UserId
banChatMemberUserId :: UserId -- ^ Unique identifier of the target user
  , BanChatMemberRequest -> Maybe Int
banChatMemberUntilDate :: Maybe Int -- ^ Date when the user will be unbanned, unix time. If user is banned for more than 366 days or less than 30 seconds from the current time they are considered to be banned forever. Applied for supergroups and channels only.
  , BanChatMemberRequest -> Maybe Bool
banChatMemberRevokeMessages :: Maybe Bool -- ^ Pass True to delete all messages from the chat for the user that is being removed. If False, the user will be able to see messages in the group that were sent before the user was removed. Always True for supergroups and channels.
  }
  deriving forall x. Rep BanChatMemberRequest x -> BanChatMemberRequest
forall x. BanChatMemberRequest -> Rep BanChatMemberRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BanChatMemberRequest x -> BanChatMemberRequest
$cfrom :: forall x. BanChatMemberRequest -> Rep BanChatMemberRequest x
Generic

-- | Request parameters for 'unbanChatMember'.
data UnbanChatMemberRequest = UnbanChatMemberRequest
  { UnbanChatMemberRequest -> SomeChatId
unbanChatMemberChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , UnbanChatMemberRequest -> UserId
unbanChatMemberUserId :: UserId -- ^ Unique identifier of the target user
  , UnbanChatMemberRequest -> Maybe Bool
unbanChatMemberOnlyIfBanned :: Maybe Bool -- ^ Do nothing if the user is not banned
  }
  deriving forall x. Rep UnbanChatMemberRequest x -> UnbanChatMemberRequest
forall x. UnbanChatMemberRequest -> Rep UnbanChatMemberRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UnbanChatMemberRequest x -> UnbanChatMemberRequest
$cfrom :: forall x. UnbanChatMemberRequest -> Rep UnbanChatMemberRequest x
Generic

-- | Request parameters for 'restrictChatMember'.
data RestrictChatMemberRequest = RestrictChatMemberRequest
  { RestrictChatMemberRequest -> SomeChatId
restrictChatMemberChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , RestrictChatMemberRequest -> UserId
restrictChatMemberUserId :: UserId -- ^ Unique identifier of the target user
  , RestrictChatMemberRequest -> ChatPermissions
restrictChatMemberPermissions :: ChatPermissions -- ^ A JSON-serialized object for new user permissions
  , RestrictChatMemberRequest -> Maybe Int
restrictChatMemberUntilDate :: Maybe Int -- ^ Date when restrictions will be lifted for the user, unix time. If user is restricted for more than 366 days or less than 30 seconds from the current time, they are considered to be restricted forever
  }
  deriving forall x.
Rep RestrictChatMemberRequest x -> RestrictChatMemberRequest
forall x.
RestrictChatMemberRequest -> Rep RestrictChatMemberRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RestrictChatMemberRequest x -> RestrictChatMemberRequest
$cfrom :: forall x.
RestrictChatMemberRequest -> Rep RestrictChatMemberRequest x
Generic

-- | Request parameters for 'promoteChatMember'.
data PromoteChatMemberRequest = PromoteChatMemberRequest
  { PromoteChatMemberRequest -> SomeChatId
promoteChatMemberChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , PromoteChatMemberRequest -> UserId
promoteChatMemberUserId :: UserId -- ^ Unique identifier of the target user
  , PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberIsAnonymous :: Maybe Bool -- ^ Pass True, if the administrator's presence in the chat is hidden
  , PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanManageChat :: Maybe Bool -- ^ Pass True, if the administrator can access the chat event log, chat statistics, message statistics in channels, see channel members, see anonymous administrators in supergroups and ignore slow mode. Implied by any other administrator privilege
  , PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanPostMessages :: Maybe Bool -- ^ Pass True, if the administrator can create channel posts, channels only
  , PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanEditMessages :: Maybe Bool -- ^ Pass True, if the administrator can edit messages of other users and can pin messages, channels only
  , PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanDeleteMessages :: Maybe Bool -- ^ Pass True, if the administrator can delete messages of other users
  , PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanManageVideoChats :: Maybe Bool -- ^ Pass True, if the administrator can manage video chats
  , PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanRestrictMembers :: Maybe Bool -- ^ Pass True, if the administrator can restrict, ban or unban chat members
  , PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanPromoteMembers :: Maybe Bool -- ^ Pass True, if the administrator can add new administrators with a subset of their own privileges or demote administrators that he has promoted, directly or indirectly (promoted by administrators that were appointed by him)
  , PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanChangeInfo :: Maybe Bool -- ^ Pass True, if the administrator can change chat title, photo and other settings
  , PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanInviteUsers :: Maybe Bool -- ^ Pass True, if the administrator can invite new users to the chat
  , PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanPinMessages :: Maybe Bool -- ^ Pass True, if the administrator can pin messages, supergroups only
  }
  deriving forall x.
Rep PromoteChatMemberRequest x -> PromoteChatMemberRequest
forall x.
PromoteChatMemberRequest -> Rep PromoteChatMemberRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PromoteChatMemberRequest x -> PromoteChatMemberRequest
$cfrom :: forall x.
PromoteChatMemberRequest -> Rep PromoteChatMemberRequest x
Generic

-- | Request parameters for 'setChatAdministratorCustomTitle'.
data SetChatAdministratorCustomTitleRequest = SetChatAdministratorCustomTitleRequest
  { SetChatAdministratorCustomTitleRequest -> SomeChatId
setChatAdministratorCustomTitleChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , SetChatAdministratorCustomTitleRequest -> UserId
setChatAdministratorCustomTitleUserId :: UserId -- ^ Unique identifier of the target user
  , SetChatAdministratorCustomTitleRequest -> Text
setChatAdministratorCustomTitleCustomTitle :: Text -- ^ New custom title for the administrator; 0-16 characters, emoji are not allowed
  }
  deriving forall x.
Rep SetChatAdministratorCustomTitleRequest x
-> SetChatAdministratorCustomTitleRequest
forall x.
SetChatAdministratorCustomTitleRequest
-> Rep SetChatAdministratorCustomTitleRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetChatAdministratorCustomTitleRequest x
-> SetChatAdministratorCustomTitleRequest
$cfrom :: forall x.
SetChatAdministratorCustomTitleRequest
-> Rep SetChatAdministratorCustomTitleRequest x
Generic

type BanChatSenderChat = "banChatSenderChat"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> RequiredQueryParam "sender_chat_id" ChatId
  :> Post '[JSON] (Response Bool)

-- | Use this method to ban a channel chat
--   in a supergroup or a channel. Until the
--   chat is unbanned, the owner of the banned
--   chat won't be able to send messages on
--   behalf of any of their channels. The bot
--   must be an administrator in the supergroup
--   or channel for this to work and must have
--   the appropriate administrator rights.
--   Returns True on success.
banChatSenderChat :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> ChatId -- ^ Unique identifier of the target sender chat
  -> ClientM (Response  Bool)
banChatSenderChat :: SomeChatId -> ChatId -> ClientM (Response Bool)
banChatSenderChat = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @BanChatSenderChat)

type UnbanChatSenderChat = "unbanChatSenderChat"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> RequiredQueryParam "sender_chat_id" ChatId
  :> Post '[JSON] (Response Bool)

-- | Use this method to unban a previously
--   banned channel chat in a supergroup
--   or channel. The bot must be an administrator
--   for this to work and must have the appropriate
--   administrator rights.
--   Returns True on success.
unbanChatSenderChat :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> ChatId -- ^ Unique identifier of the target sender chat
  -> ClientM (Response  Bool)
unbanChatSenderChat :: SomeChatId -> ChatId -> ClientM (Response Bool)
unbanChatSenderChat = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @UnbanChatSenderChat)

-- | Request parameters for 'setChatPermissions'.
data SetChatPermissionsRequest = SetChatPermissionsRequest
  { SetChatPermissionsRequest -> SomeChatId
setChatPermissionsChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , SetChatPermissionsRequest -> ChatPermissions
setChatPermissionsPermissions :: ChatPermissions -- ^ A JSON-serialized object for new default chat permissions
  }
  deriving forall x.
Rep SetChatPermissionsRequest x -> SetChatPermissionsRequest
forall x.
SetChatPermissionsRequest -> Rep SetChatPermissionsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetChatPermissionsRequest x -> SetChatPermissionsRequest
$cfrom :: forall x.
SetChatPermissionsRequest -> Rep SetChatPermissionsRequest x
Generic

type ExportChatInviteLink = "exportChatInviteLink"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> Post '[JSON] (Response Text)

-- | Use this method to generate a new
--   primary invite link for a chat; any
--   previously generated primary link is
--   revoked. The bot must be an administrator
--   in the chat for this to work and must have
--   the appropriate administrator rights.
--   Returns the new invite link as String on success.
exportChatInviteLink :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> ClientM (Response  Text)
exportChatInviteLink :: SomeChatId -> ClientM (Response Text)
exportChatInviteLink = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @ExportChatInviteLink)

-- | Request parameters for 'createChatInviteLink'.
data CreateChatInviteLinkRequest = CreateChatInviteLinkRequest
  { CreateChatInviteLinkRequest -> SomeChatId
createChatInviteLinkChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , CreateChatInviteLinkRequest -> Maybe Text
createChatInviteLinkName :: Maybe Text -- ^ Invite link name; 0-32 characters
  , CreateChatInviteLinkRequest -> Maybe Integer
createChatInviteLinkExpireDate :: Maybe Integer -- ^ Point in time (Unix timestamp) when the link will expire
  , CreateChatInviteLinkRequest -> Maybe Int
createChatInviteLinkMemberLimit :: Maybe Int -- ^ Maximum number of users that can be members of the chat simultaneously after joining the chat via this invite link; 1-99999
  , CreateChatInviteLinkRequest -> Maybe Bool
createChatInviteLinkCreatesJoinRequest :: Maybe Bool -- ^ True, if users joining the chat via the link need to be approved by chat administrators. If True, member_limit can't be specified
  }
  deriving forall x.
Rep CreateChatInviteLinkRequest x -> CreateChatInviteLinkRequest
forall x.
CreateChatInviteLinkRequest -> Rep CreateChatInviteLinkRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateChatInviteLinkRequest x -> CreateChatInviteLinkRequest
$cfrom :: forall x.
CreateChatInviteLinkRequest -> Rep CreateChatInviteLinkRequest x
Generic

-- | Request parameters for 'editChatInviteLink'.
data EditChatInviteLinkRequest = EditChatInviteLinkRequest
  { EditChatInviteLinkRequest -> SomeChatId
editChatInviteLinkChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , EditChatInviteLinkRequest -> Text
editChatInviteLinkInviteLink :: Text -- ^	The invite link to edit
  , EditChatInviteLinkRequest -> Maybe Text
editChatInviteLinkName :: Maybe Text -- ^ Invite link name; 0-32 characters
  , EditChatInviteLinkRequest -> Maybe Integer
editChatInviteLinkExpireDate :: Maybe Integer -- ^ Point in time (Unix timestamp) when the link will expire
  , EditChatInviteLinkRequest -> Maybe Int
editChatInviteLinkMemberLimit :: Maybe Int -- ^ Maximum number of users that can be members of the chat simultaneously after joining the chat via this invite link; 1-99999
  , EditChatInviteLinkRequest -> Maybe Bool
editChatInviteLinkCreatesJoinRequest :: Maybe Bool -- ^ True, if users joining the chat via the link need to be approved by chat administrators. If True, member_limit can't be specified
  }
  deriving forall x.
Rep EditChatInviteLinkRequest x -> EditChatInviteLinkRequest
forall x.
EditChatInviteLinkRequest -> Rep EditChatInviteLinkRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EditChatInviteLinkRequest x -> EditChatInviteLinkRequest
$cfrom :: forall x.
EditChatInviteLinkRequest -> Rep EditChatInviteLinkRequest x
Generic

type RevokeChatInviteLink = "revokeChatInviteLink"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> RequiredQueryParam "invite_link" Text
  :> Post '[JSON] (Response ChatInviteLink)

-- | Use this method to revoke an invite
--   link created by the bot. If the primary 
--   link is revoked, a new link is automatically 
--   generated. The bot must be an administrator 
--   in the chat for this to work and must have 
--   the appropriate administrator rights. 
--   Returns the revoked invite link as ChatInviteLink object.
revokeChatInviteLink :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> Text -- ^ The invite link to revoke
  -> ClientM (Response  ChatInviteLink)
revokeChatInviteLink :: SomeChatId -> Text -> ClientM (Response ChatInviteLink)
revokeChatInviteLink = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @RevokeChatInviteLink)

type ApproveChatJoinRequest = "approveChatJoinRequest"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> RequiredQueryParam "user_id" UserId
  :> Post '[JSON] (Response Bool)

-- | Use this method to approve a chat 
--   join request. The bot must be an 
--   administrator in the chat for this 
--   to work and must have the can_invite_users 
--   administrator right. 
--   Returns True on success.
approveChatJoinRequest :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> UserId -- ^ Unique identifier of the target user
  -> ClientM (Response Bool)
approveChatJoinRequest :: SomeChatId -> UserId -> ClientM (Response Bool)
approveChatJoinRequest = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @ApproveChatJoinRequest)

type DeclineChatJoinRequest = "declineChatJoinRequest"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> RequiredQueryParam "user_id" UserId
  :> Post '[JSON] (Response Bool)

-- | Use this method to decline a chat 
--   join request. The bot must be an 
--   administrator in the chat for this 
--   to work and must have the can_invite_users 
--   administrator right. 
--   Returns True on success.
declineChatJoinRequest :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> UserId -- ^ Unique identifier of the target user
  -> ClientM (Response Bool)
declineChatJoinRequest :: SomeChatId -> UserId -> ClientM (Response Bool)
declineChatJoinRequest = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @DeclineChatJoinRequest)

-- | Request parameters for 'setChatPhoto'.
data SetChatPhotoRequest = SetChatPhotoRequest
  { SetChatPhotoRequest -> SomeChatId
setChatPhotoChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , SetChatPhotoRequest -> InputFile
setChatPhotoPhoto :: InputFile -- ^ 	New chat photo, uploaded using multipart/form-data
  }

instance ToMultipart Tmp SetChatPhotoRequest where
  toMultipart :: SetChatPhotoRequest -> MultipartData Tmp
toMultipart SetChatPhotoRequest{SomeChatId
InputFile
setChatPhotoPhoto :: InputFile
setChatPhotoChatId :: SomeChatId
setChatPhotoPhoto :: SetChatPhotoRequest -> InputFile
setChatPhotoChatId :: SetChatPhotoRequest -> SomeChatId
..} =
    Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"photo" InputFile
setChatPhotoPhoto (forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields []) where
    fields :: [Input]
fields =
      [ Text -> Text -> Input
Input Text
"chat_id" forall a b. (a -> b) -> a -> b
$ case SomeChatId
setChatPhotoChatId of
          SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> FilePath
show Integer
chat_id
          SomeChatUsername Text
txt -> Text
txt
      ]

type SetChatPhoto = "setChatPhoto"
  :> MultipartForm Tmp SetChatPhotoRequest
  :> Post '[JSON] (Response Bool)

-- | Use this method to set a new profile 
--   photo for the chat. Photos can't be changed
--   for private chats. The bot must be an 
--   administrator in the chat for this to work 
--   and must have the appropriate administrator rights. 
--   Returns True on success.
--
-- *Note*: Only 'InputFile' case might be used in 'SetChatPhotoRequest'.
-- Rest cases will be rejected by Telegram.
setChatPhoto :: SetChatPhotoRequest ->  ClientM (Response Bool)
setChatPhoto :: SetChatPhotoRequest -> ClientM (Response Bool)
setChatPhoto SetChatPhotoRequest
r =do
      ByteString
boundary <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
      forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SetChatPhoto) (ByteString
boundary, SetChatPhotoRequest
r)

type DeleteChatPhoto = "deleteChatPhoto"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> Post '[JSON] (Response Bool)

-- | Use this method to delete a chat photo.
--   Photos can't be changed for private chats.
--   The bot must be an administrator in the chat 
--   for this to work and must have the appropriate 
--   administrator rights. 
--   Returns True on success.
deleteChatPhoto :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> ClientM (Response Bool)
deleteChatPhoto :: SomeChatId -> ClientM (Response Bool)
deleteChatPhoto = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @DeleteChatPhoto)

type SetChatTitle = "setChatTitle"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> RequiredQueryParam "title" Text
  :> Post '[JSON] (Response Bool)

-- | Use this method to change the title of
--   a chat. Titles can't be changed for private
--   chats. The bot must be an administrator in 
--   the chat for this to work and must have the 
--   appropriate administrator rights. 
--   Returns True on success.
setChatTitle :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> Text -- ^ New chat title, 0-255 characters
  -> ClientM (Response Bool)
setChatTitle :: SomeChatId -> Text -> ClientM (Response Bool)
setChatTitle = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SetChatTitle)

type SetChatDescription = "setChatDescription"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> QueryParam "description" Text
  :> Post '[JSON] (Response Bool)

-- | Use this method to change the description 
--   of a group, a supergroup or a channel. The 
--   bot must be an administrator in the chat 
--   for this to work and must have the appropriate 
--   administrator rights. 
--   Returns True on success.
setChatDescription :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> Maybe Text -- ^ New chat description, 0-255 characters
  -> ClientM (Response Bool)
setChatDescription :: SomeChatId -> Maybe Text -> ClientM (Response Bool)
setChatDescription = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SetChatDescription)

-- | Request parameters for 'pinChatMessage'.
data PinChatMessageRequest = PinChatMessageRequest
  { PinChatMessageRequest -> SomeChatId
pinChatMessageChatId :: SomeChatId -- ^ Unique identifier for the target chat or username of the target channel (in the format @channelusername)
  , PinChatMessageRequest -> MessageId
pinChatMessageMessageId :: MessageId -- ^ Identifier of a message to pin
  , PinChatMessageRequest -> Maybe Bool
pinChatMessageDisableNotification :: Maybe Bool -- ^ Pass True, if it is not necessary to send a notification to all chat members about the new pinned message. Notifications are always disabled in channels and private chats.
  }
  deriving forall x. Rep PinChatMessageRequest x -> PinChatMessageRequest
forall x. PinChatMessageRequest -> Rep PinChatMessageRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PinChatMessageRequest x -> PinChatMessageRequest
$cfrom :: forall x. PinChatMessageRequest -> Rep PinChatMessageRequest x
Generic

type UnpinChatMessage = "unpinChatMessage"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> QueryParam "message_id" MessageId
  :> Post '[JSON] (Response Bool)

-- | Use this method to remove a message from the
--   list of pinned messages in a chat. If the chat 
--   is not a private chat, the bot must be an administrator
--   in the chat for this to work and must have the 
--   'can_pin_messages' administrator right in a supergroup 
--   or 'can_edit_messages' administrator right in a 
--   channel. 
--   Returns True on success.
unpinChatMessage :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> Maybe MessageId -- ^ Identifier of a message to unpin. If not specified, the most recent pinned message (by sending date) will be unpinned.
  -> ClientM (Response Bool)
unpinChatMessage :: SomeChatId -> Maybe MessageId -> ClientM (Response Bool)
unpinChatMessage = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @UnpinChatMessage)

type UnpinAllChatMessages = "unpinAllChatMessages"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> Post '[JSON] (Response Bool)

-- | Use this method to clear the list of pinned 
--   messages in a chat. If the chat is not a private 
--   chat, the bot must be an administrator in the 
--   chat for this to work and must have the 'can_pin_messages' 
--   administrator right in a supergroup or 'can_edit_messages' 
--   administrator right in a channel. 
--   Returns True on success.
unpinAllChatMessages :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> ClientM (Response Bool)
unpinAllChatMessages :: SomeChatId -> ClientM (Response Bool)
unpinAllChatMessages = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @UnpinAllChatMessages)

type LeaveChat = "leaveChat"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> Post '[JSON] (Response Bool)

-- | Use this method for your bot to leave a group, supergroup or channel. 
--   Returns True on success.
leaveChat :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> ClientM (Response Bool)
leaveChat :: SomeChatId -> ClientM (Response Bool)
leaveChat = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @LeaveChat)

type GetChat = "getChat"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> Post '[JSON] (Response Chat)

-- | Use this method to get up to date information 
--   about the chat (current name of the user for 
--   one-on-one conversations, current username of 
--   a user, group or channel, etc.). 
--   Returns a Chat object on success.
getChat :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> ClientM (Response Chat)
getChat :: SomeChatId -> ClientM (Response Chat)
getChat = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @GetChat)

type GetChatAdministrators = "getChatAdministrators"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> Post '[JSON] (Response [ChatMember])

-- | Use this method to get a list of administrators
--   in a chat. On success, returns an Array of 
--   ChatMember objects that contains information 
--   about all chat administrators except other bots. 
--   If the chat is a group or a supergroup and no 
--   administrators were appointed, only the creator 
--   will be returned.
getChatAdministrators :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> ClientM (Response [ChatMember])
getChatAdministrators :: SomeChatId -> ClientM (Response [ChatMember])
getChatAdministrators = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @GetChatAdministrators)

type GetChatMemberCount = "getChatMemberCount"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> Post '[JSON] (Response Integer)

-- | Use this method to get the number of members in a chat. 
--   Returns Int on success.
getChatMemberCount :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> ClientM (Response Integer)
getChatMemberCount :: SomeChatId -> ClientM (Response Integer)
getChatMemberCount = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @GetChatMemberCount)

type GetChatMember = "getChatMember"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> RequiredQueryParam "user_id" UserId
  :> Post '[JSON] (Response ChatMember)

-- | Use this method to get information about a member of a chat. 
--   Returns a ChatMember object on success.
getChatMember :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> UserId -- ^ 	Unique identifier of the target user
  -> ClientM (Response ChatMember)
getChatMember :: SomeChatId -> UserId -> ClientM (Response ChatMember)
getChatMember = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @GetChatMember)

type SetChatStickerSet = "setChatStickerSet"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> RequiredQueryParam "sticker_set_name" Text
  :> Post '[JSON] (Response Bool)

-- | Use this method to set a new group sticker
--   set for a supergroup. The bot must be an 
--   administrator in the chat for this to work 
--   and must have the appropriate administrator 
--   rights. Use the field can_set_sticker_set 
--   optionally returned in getChat requests to 
--   check if the bot can use this method. 
--   Returns True on success.
setChatStickerSet :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> Text -- ^ 	Name of the sticker set to be set as the group sticker set
  -> ClientM (Response Bool)
setChatStickerSet :: SomeChatId -> Text -> ClientM (Response Bool)
setChatStickerSet = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SetChatStickerSet)

type DeleteChatStickerSet = "deleteChatStickerSet"
  :> RequiredQueryParam "chat_id" SomeChatId
  :> Post '[JSON] (Response Bool)

-- | Use this method to delete a group sticker 
--   set from a supergroup. The bot must be an 
--   administrator in the chat for this to work 
--   and must have the appropriate administrator 
--   rights. Use the field can_set_sticker_set 
--   optionally returned in getChat requests 
--   to check if the bot can use this method. 
--   Returns True on success.
deleteChatStickerSet :: SomeChatId -- ^ Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)
  -> ClientM (Response Bool)
deleteChatStickerSet :: SomeChatId -> ClientM (Response Bool)
deleteChatStickerSet = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @DeleteChatStickerSet)

-- | Request parameters for 'answerCallbackQuery'.
data AnswerCallbackQueryRequest = AnswerCallbackQueryRequest
  { AnswerCallbackQueryRequest -> CallbackQueryId
answerCallbackQueryCallbackQueryId :: CallbackQueryId -- ^ Unique identifier for the query to be answered
  , AnswerCallbackQueryRequest -> Maybe Text
answerCallbackQueryText :: Maybe Text -- ^ Text of the notification. If not specified, nothing will be shown to the user, 0-200 characters
  , AnswerCallbackQueryRequest -> Maybe Bool
answerCallbackQueryShowAlert :: Maybe Bool -- ^ If True, an alert will be shown by the client instead of a notification at the top of the chat screen. Defaults to false.
  , AnswerCallbackQueryRequest -> Maybe Text
answerCallbackQueryUrl :: Maybe Text
    -- ^ URL that will be opened by the user's client. If you have created a Game and accepted the conditions via @Botfather, specify the URL that opens your game — note that this will only work if the query comes from a callback_game button.
    --
    --   Otherwise, you may use links like t.me/your_bot?start=XXXX that open your bot with a parameter.
  , AnswerCallbackQueryRequest -> Maybe Integer
answerCallbackQueryCacheTime :: Maybe Integer -- ^ The maximum amount of time in seconds that the result of the callback query may be cached client-side. Telegram apps will support caching starting in version 3.14. Defaults to 0.
  }
  deriving forall x.
Rep AnswerCallbackQueryRequest x -> AnswerCallbackQueryRequest
forall x.
AnswerCallbackQueryRequest -> Rep AnswerCallbackQueryRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AnswerCallbackQueryRequest x -> AnswerCallbackQueryRequest
$cfrom :: forall x.
AnswerCallbackQueryRequest -> Rep AnswerCallbackQueryRequest x
Generic

-- | Request parameters for 'setMyCommands'.
data SetMyCommandsRequest = SetMyCommandsRequest
  { SetMyCommandsRequest -> [BotCommand]
setMyCommandsCommands :: [BotCommand] -- ^ A JSON-serialized list of bot commands to be set as the list of the bot's commands. At most 100 commands can be specified.
  , SetMyCommandsRequest -> Maybe BotCommandScope
setMyCommandsScope :: Maybe BotCommandScope -- ^ A JSON-serialized object, describing scope of users for which the commands are relevant. Defaults to BotCommandScopeDefault.
  , SetMyCommandsRequest -> Maybe Text
setMyCommandsLanguageCode :: Maybe Text -- ^ A two-letter ISO 639-1 language code. If empty, commands will be applied to all users from the given scope, for whose language there are no dedicated commands
  }
  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

-- | Request parameters for 'deleteMyCommands'.
data DeleteMyCommandsRequest = DeleteMyCommandsRequest
  { DeleteMyCommandsRequest -> Maybe BotCommandScope
deleteMyCommandsScope :: Maybe BotCommandScope  -- ^ A JSON-serialized object, describing scope of users. Defaults to BotCommandScopeDefault. 
  , DeleteMyCommandsRequest -> Maybe Text
deleteMyCommandsLanguageCode :: Maybe Text  -- ^ 	A two-letter ISO 639-1 language code. If empty, commands will be applied to all users from the given scope, for whose language there are no dedicated commands
  }
  deriving 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
$cto :: forall x. Rep DeleteMyCommandsRequest x -> DeleteMyCommandsRequest
$cfrom :: forall x. DeleteMyCommandsRequest -> Rep DeleteMyCommandsRequest x
Generic

-- | Request parameters for 'getMyCommands'.
data GetMyCommandsRequest = GetMyCommandsRequest
  { GetMyCommandsRequest -> Maybe BotCommandScope
getMyCommandsScope :: Maybe BotCommandScope  -- ^ A JSON-serialized object, describing scope of users. Defaults to BotCommandScopeDefault. 
  , GetMyCommandsRequest -> Maybe Text
getMyCommandsLanguageCode :: Maybe Text   -- ^ 	A two-letter ISO 639-1 language code or an empty string
  }
  deriving forall x. Rep GetMyCommandsRequest x -> GetMyCommandsRequest
forall x. GetMyCommandsRequest -> Rep GetMyCommandsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMyCommandsRequest x -> GetMyCommandsRequest
$cfrom :: forall x. GetMyCommandsRequest -> Rep GetMyCommandsRequest x
Generic

-- | Request parameters for 'setChatMenuButton'

data SetChatMenuButtonRequest = SetChatMenuButtonRequest
  { SetChatMenuButtonRequest -> Maybe ChatId
setChatMenuButtonRequestChatId     :: Maybe ChatId     -- ^ Unique identifier for the target private chat. If not specified, default bot's menu button will be changed.
  , SetChatMenuButtonRequest -> Maybe MenuButton
setChatMenuButtonRequestMenuButton :: Maybe MenuButton -- ^ A JSON-serialized object for the new bot's menu button. Defaults to @MenuButtonDefault@.
  }
  deriving forall x.
Rep SetChatMenuButtonRequest x -> SetChatMenuButtonRequest
forall x.
SetChatMenuButtonRequest -> Rep SetChatMenuButtonRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetChatMenuButtonRequest x -> SetChatMenuButtonRequest
$cfrom :: forall x.
SetChatMenuButtonRequest -> Rep SetChatMenuButtonRequest x
Generic

-- | Request parameters for 'getChatMenuButton'

data GetChatMenuButtonRequest = GetChatMenuButtonRequest
  { GetChatMenuButtonRequest -> Maybe ChatId
getChatMenuButtonRequestChatId     :: Maybe ChatId     -- ^ Unique identifier for the target private chat. If not specified, default bot's menu button will be returned.
  }
  deriving forall x.
Rep GetChatMenuButtonRequest x -> GetChatMenuButtonRequest
forall x.
GetChatMenuButtonRequest -> Rep GetChatMenuButtonRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetChatMenuButtonRequest x -> GetChatMenuButtonRequest
$cfrom :: forall x.
GetChatMenuButtonRequest -> Rep GetChatMenuButtonRequest x
Generic

-- | Request parameters for 'setMyDefaultAdministratorRights'
data SetMyDefaultAdministratorRightsRequest = SetMyDefaultAdministratorRightsRequest
  { SetMyDefaultAdministratorRightsRequest
-> Maybe ChatAdministratorRights
setMyDefaultAdministratorRightsRequestRights      :: Maybe ChatAdministratorRights -- ^ A JSON-serialized object describing new default administrator rights. If not specified, the default administrator rights will be cleared.
  , SetMyDefaultAdministratorRightsRequest -> Maybe Bool
setMyDefaultAdministratorRightsRequestForChannels :: Maybe Bool -- ^ Pass 'True' to change the default administrator rights of the bot in channels. Otherwise, the default administrator rights of the bot for groups and supergroups will be changed.
  }
  deriving forall x.
Rep SetMyDefaultAdministratorRightsRequest x
-> SetMyDefaultAdministratorRightsRequest
forall x.
SetMyDefaultAdministratorRightsRequest
-> Rep SetMyDefaultAdministratorRightsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetMyDefaultAdministratorRightsRequest x
-> SetMyDefaultAdministratorRightsRequest
$cfrom :: forall x.
SetMyDefaultAdministratorRightsRequest
-> Rep SetMyDefaultAdministratorRightsRequest x
Generic

-- | Request parameters for 'getMyDefaultAdministratorRights'
data GetMyDefaultAdministratorRightsRequest = GetMyDefaultAdministratorRightsRequest
  { GetMyDefaultAdministratorRightsRequest -> Maybe Bool
getMyDefaultAdministratorRightsRequestForChannels :: Maybe Bool -- ^ Pass 'True' to get default administrator rights of the bot in channels. Otherwise, default administrator rights of the bot for groups and supergroups will be returned.
  }
  deriving forall x.
Rep GetMyDefaultAdministratorRightsRequest x
-> GetMyDefaultAdministratorRightsRequest
forall x.
GetMyDefaultAdministratorRightsRequest
-> Rep GetMyDefaultAdministratorRightsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetMyDefaultAdministratorRightsRequest x
-> GetMyDefaultAdministratorRightsRequest
$cfrom :: forall x.
GetMyDefaultAdministratorRightsRequest
-> Rep GetMyDefaultAdministratorRightsRequest x
Generic

foldMap deriveJSON'
  [ ''SetMyDefaultAdministratorRightsRequest
  , ''GetMyDefaultAdministratorRightsRequest
  , ''GetChatMenuButtonRequest
  , ''SetChatMenuButtonRequest
  , ''GetMyCommandsRequest
  , ''DeleteMyCommandsRequest
  , ''SetMyCommandsRequest
  , ''AnswerCallbackQueryRequest
  , ''EditChatInviteLinkRequest
  , ''PinChatMessageRequest
  , ''CreateChatInviteLinkRequest
  , ''SetChatPermissionsRequest
  , ''SetChatAdministratorCustomTitleRequest
  , ''PromoteChatMemberRequest
  , ''RestrictChatMemberRequest
  , ''UnbanChatMemberRequest
  , ''BanChatMemberRequest
  , ''GetUserProfilePhotosRequest
  , ''SendDiceRequest
  , ''SendPollRequest
  , ''SendContactRequest
  , ''SendVenueRequest
  , ''StopMessageLiveLocationRequest
  , ''EditMessageLiveLocationRequest
  , ''SendLocationRequest
  , ''CopyMessageRequest
  ]

type CopyMessage
  = "copyMessage"
  :> ReqBody '[JSON] CopyMessageRequest
  :> Post '[JSON] (Response CopyMessageId)

-- | Use this method to copy messages of any kind.
--   Service messages and invoice messages can't be
--   copied. The method is analogous to the method
--   forwardMessage, but the copied message doesn't
--   have a link to the original message.
--   Returns the MessageId of the sent message on success.
copyMessage :: CopyMessageRequest ->  ClientM (Response CopyMessageId)
copyMessage :: CopyMessageRequest -> ClientM (Response CopyMessageId)
copyMessage = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @CopyMessage)

type SendLocation = "sendLocation"
  :> ReqBody '[JSON] SendLocationRequest
  :> Post '[JSON] (Response Message)

-- | Use this method to send point on the map.
--   On success, the sent Message is returned.
sendLocation :: SendLocationRequest ->  ClientM (Response Message)
sendLocation :: SendLocationRequest -> ClientM (Response Message)
sendLocation = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendLocation)

type EditMessageLiveLocation = "editMessageLiveLocation"
  :> ReqBody '[JSON] EditMessageLiveLocationRequest
  :> Post '[JSON] (Response (Either Bool Message))

-- | Use this method to edit live location messages.
--   A location can be edited until its live_period
--   expires or editing is explicitly disabled by a
--   call to stopMessageLiveLocation. On success, if
--   the edited message is not an inline message, the
--   edited Message is returned, otherwise True is returned.
editMessageLiveLocation :: EditMessageLiveLocationRequest ->  ClientM (Response (Either Bool Message))
editMessageLiveLocation :: EditMessageLiveLocationRequest
-> ClientM (Response (Either Bool Message))
editMessageLiveLocation = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @EditMessageLiveLocation)

type StopMessageLiveLocation = "stopMessageLiveLocation"
  :> ReqBody '[JSON] StopMessageLiveLocationRequest
  :> Post '[JSON] (Response (Either Bool Message))

-- | Use this method to stop updating a live
--   location message before live_period
--   expires. On success, if the message is
--   not an inline message, the edited Message
--   is returned, otherwise True is returned.
stopMessageLiveLocation :: StopMessageLiveLocationRequest ->  ClientM (Response (Either Bool Message))
stopMessageLiveLocation :: StopMessageLiveLocationRequest
-> ClientM (Response (Either Bool Message))
stopMessageLiveLocation = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @StopMessageLiveLocation)

type SendVenue = "sendVenue"
  :> ReqBody '[JSON] SendVenueRequest
  :> Post '[JSON] (Response Message)

-- | Use this method to send information about a venue.
--   On success, the sent Message is returned.
sendVenue :: SendVenueRequest ->  ClientM (Response Message)
sendVenue :: SendVenueRequest -> ClientM (Response Message)
sendVenue = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendVenue)

type SendContact = "sendContact"
  :> ReqBody '[JSON] SendContactRequest
  :> Post '[JSON] (Response Message)

-- | Use this method to send phone contacts.
--   On success, the sent Message is returned.
sendContact :: SendContactRequest ->  ClientM (Response Message)
sendContact :: SendContactRequest -> ClientM (Response Message)
sendContact = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendContact)

type SendPoll = "sendPoll"
  :> ReqBody '[JSON] SendPollRequest
  :> Post '[JSON] (Response Message)

-- | Use this method to send a native poll.
--   On success, the sent Message is returned.
sendPoll :: SendPollRequest ->  ClientM (Response Message)
sendPoll :: SendPollRequest -> ClientM (Response Message)
sendPoll = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendPoll)

type SendDice = "sendDice"
  :> ReqBody '[JSON] SendDiceRequest
  :> Post '[JSON] (Response Message)

-- | Use this method to send an animated emoji that
--   will display a random value.
--   On success, the sent Message is returned.
sendDice :: SendDiceRequest ->  ClientM (Response Message)
sendDice :: SendDiceRequest -> ClientM (Response Message)
sendDice = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendDice)

type GetUserProfilePhotos = "getUserProfilePhotos"
  :> ReqBody '[JSON] GetUserProfilePhotosRequest
  :> Post '[JSON] (Response UserProfilePhotos)

-- | Use this method to get a list of profile pictures for a user.
--   Returns a UserProfilePhotos object.
getUserProfilePhotos :: GetUserProfilePhotosRequest ->  ClientM (Response UserProfilePhotos)
getUserProfilePhotos :: GetUserProfilePhotosRequest -> ClientM (Response UserProfilePhotos)
getUserProfilePhotos = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @GetUserProfilePhotos)

type BanChatMember = "banChatMember"
  :> ReqBody '[JSON] BanChatMemberRequest
  :> Post '[JSON] (Response Bool)

-- | Use this method to ban a user in a
--   group, a supergroup or a channel.
--   In the case of supergroups and channels,
--   the user will not be able to return to
--   the chat on their own using invite links,
--   etc., unless unbanned first. The bot must
--   be an administrator in the chat for this
--   to work and must have the appropriate
--   administrator rights.
--   Returns True on success.
banChatMember :: BanChatMemberRequest ->  ClientM (Response Bool)
banChatMember :: BanChatMemberRequest -> ClientM (Response Bool)
banChatMember = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @BanChatMember)

type UnbanChatMember = "unbanChatMember"
  :> ReqBody '[JSON] UnbanChatMemberRequest
  :> Post '[JSON] (Response Bool)

-- | Use this method to unban a previously
--   banned user in a supergroup or channel.
--   The user will not return to the group
--   or channel automatically, but will be
--   able to join via link, etc. The bot must
--   be an administrator for this to work. By
--   default, this method guarantees that after
--   the call the user is not a member of the chat,
--   but will be able to join it. So if the user is
--   a member of the chat they will also be removed
--   from the chat. If you don't want this, use the
--   parameter only_if_banned.
--   Returns True on success.
unbanChatMember :: UnbanChatMemberRequest ->  ClientM (Response Bool)
unbanChatMember :: UnbanChatMemberRequest -> ClientM (Response Bool)
unbanChatMember = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @UnbanChatMember)

type RestrictChatMember = "restrictChatMember"
  :> ReqBody '[JSON] RestrictChatMemberRequest
  :> Post '[JSON] (Response Bool)

-- | Use this method to restrict a user
--   in a supergroup. The bot must be an
--   administrator in the supergroup for
--   this to work and must have the appropriate
--   administrator rights. Pass True for all
--   permissions to lift restrictions from a
--   user.
--   Returns True on success.
restrictChatMember :: RestrictChatMemberRequest ->  ClientM (Response Bool)
restrictChatMember :: RestrictChatMemberRequest -> ClientM (Response Bool)
restrictChatMember = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @RestrictChatMember)

type PromoteChatMember = "promoteChatMember"
  :> ReqBody '[JSON] PromoteChatMemberRequest
  :> Post '[JSON] (Response Bool)

-- | Use this method to promote or demote
--   a user in a supergroup or a channel.
--   The bot must be an administrator in
--   the chat for this to work and must have
--   the appropriate administrator rights.
--   Pass False for all boolean parameters
--   to demote a user.
--   Returns True on success.
promoteChatMember ::PromoteChatMemberRequest ->  ClientM (Response Bool)
promoteChatMember :: PromoteChatMemberRequest -> ClientM (Response Bool)
promoteChatMember = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @PromoteChatMember)

type SetChatAdministratorCustomTitle = "setChatAdministratorCustomTitle"
  :> ReqBody '[JSON] SetChatAdministratorCustomTitleRequest
  :> Post '[JSON] (Response Bool)

-- | Use this method to set a custom title
--   for an administrator in a supergroup
--   promoted by the bot.
--   Returns True on success.
setChatAdministratorCustomTitle :: SetChatAdministratorCustomTitleRequest ->  ClientM (Response Bool)
setChatAdministratorCustomTitle :: SetChatAdministratorCustomTitleRequest -> ClientM (Response Bool)
setChatAdministratorCustomTitle = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SetChatAdministratorCustomTitle)

type SetChatPermissions = "setChatPermissions"
  :> ReqBody '[JSON] SetChatPermissionsRequest
  :> Post '[JSON] (Response Bool)

-- | Use this method to set default chat
--   permissions for all members. The bot
--   must be an administrator in the group
--   or a supergroup for this to work and must
--   have the can_restrict_members administrator rights.
--   Returns True on success.
setChatPermissions :: SetChatPermissionsRequest ->  ClientM (Response Bool)
setChatPermissions :: SetChatPermissionsRequest -> ClientM (Response Bool)
setChatPermissions = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SetChatPermissions)

type CreateChatInviteLink = "createChatInviteLink"
  :> ReqBody '[JSON] CreateChatInviteLinkRequest
  :> Post '[JSON] (Response ChatInviteLink)

-- | Use this method to create an additional
--   invite link for a chat. The bot must be 
--   an administrator in the chat for this to 
--   work and must have the appropriate administrator 
--   rights. The link can be revoked using the 
--   method revokeChatInviteLink. 
--   Returns the new invite link as ChatInviteLink object.
createChatInviteLink :: CreateChatInviteLinkRequest ->  ClientM (Response ChatInviteLink)
createChatInviteLink :: CreateChatInviteLinkRequest -> ClientM (Response ChatInviteLink)
createChatInviteLink = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @CreateChatInviteLink)

type EditChatInviteLink = "editChatInviteLink"
  :> ReqBody '[JSON] EditChatInviteLinkRequest
  :> Post '[JSON] (Response ChatInviteLink)

-- | Use this method to edit a non-primary
--   invite link created by the bot. The 
--   bot must be an administrator in the 
--   chat for this to work and must have 
--   the appropriate administrator rights.
--   Returns the edited invite link as a ChatInviteLink object.
editChatInviteLink :: EditChatInviteLinkRequest ->  ClientM (Response ChatInviteLink)
editChatInviteLink :: EditChatInviteLinkRequest -> ClientM (Response ChatInviteLink)
editChatInviteLink = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @EditChatInviteLink)

type PinChatMessage = "pinChatMessage"
  :> ReqBody '[JSON] PinChatMessageRequest
  :> Post '[JSON] (Response Bool)

-- | Use this method to add a message to the list 
--   of pinned messages in a chat. If the chat is 
--   not a private chat, the bot must be an administrator 
--   in the chat for this to work and must have the 
--   'can_pin_messages' administrator right in a supergroup
--   or 'can_edit_messages' administrator right in a channel. 
--   Returns True on success.
pinChatMessage :: PinChatMessageRequest ->  ClientM (Response Bool)
pinChatMessage :: PinChatMessageRequest -> ClientM (Response Bool)
pinChatMessage = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @PinChatMessage)

type AnswerCallbackQuery = "answerCallbackQuery"
  :> ReqBody '[JSON] AnswerCallbackQueryRequest
  :> Post '[JSON] (Response Bool)

-- | Use this method to send answers to callback 
--   queries sent from inline keyboards. The answer 
--   will be displayed to the user as a notification 
--   at the top of the chat screen or as an alert. 
--   On success, True is returned.
--
--  Alternatively, the user can be redirected to 
--  the specified Game URL. For this option to work, 
--  you must first create a game for your bot via 
--  @Botfather and accept the terms. Otherwise, you 
--  may use links like t.me/your_bot?start=XXXX that 
--  open your bot with a parameter.
answerCallbackQuery :: AnswerCallbackQueryRequest ->  ClientM (Response Bool)
answerCallbackQuery :: AnswerCallbackQueryRequest -> ClientM (Response Bool)
answerCallbackQuery = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @AnswerCallbackQuery)

type SetMyCommands = "setMyCommands"
  :> ReqBody '[JSON] SetMyCommandsRequest
  :> Post '[JSON] (Response Bool)

-- | Use this method to change the list of 
--   the bot's commands. See <https:\/\/core.telegram.org\/bots#commands> 
--   for more details about bot commands. 
--   Returns True on success.
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)

type DeleteMyCommands = "deleteMyCommands"
  :> ReqBody '[JSON] DeleteMyCommandsRequest
  :> Post '[JSON] (Response Bool)

-- | Use this method to delete the list of 
--   the bot's commands for the given scope 
--   and user language. After deletion, higher 
--   level commands will be shown to affected users. 
--   Returns True on success.
deleteMyCommands :: DeleteMyCommandsRequest -> ClientM (Response Bool)
deleteMyCommands :: DeleteMyCommandsRequest -> ClientM (Response Bool)
deleteMyCommands = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @DeleteMyCommands)

type GetMyCommands = "getMyCommands"
  :> ReqBody '[JSON] GetMyCommandsRequest
  :> Post '[JSON] (Response [BotCommand])

-- | Use this method to get the current list
--   of the bot's commands for the given scope 
--   and user language. Returns Array of BotCommand 
--   on success. If commands aren't set, an empty list 
--   is returned.
getMyCommands :: GetMyCommandsRequest -> ClientM (Response [BotCommand])
getMyCommands :: GetMyCommandsRequest -> ClientM (Response [BotCommand])
getMyCommands = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @GetMyCommands)

type SetChatMenuButton = "setChatMenuButton"
  :> ReqBody '[JSON] SetChatMenuButtonRequest
  :> Post '[JSON] (Response Bool)

-- | Use this method to change the bot's menu button in a private chat,
--  or the default menu button. Returns True on success.
setChatMenuButton :: SetChatMenuButtonRequest -> ClientM (Response Bool)
setChatMenuButton :: SetChatMenuButtonRequest -> ClientM (Response Bool)
setChatMenuButton = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SetChatMenuButton)

type GetChatMenuButton = "getChatMenuButton"
  :> ReqBody '[JSON] GetChatMenuButtonRequest
  :> Post '[JSON] (Response MenuButton)

-- | Use this method to get the current value
--  of the bot's menu button in a private chat, or the default menu button.
-- Returns @MenuButton@ on success.
getChatMenuButton :: GetChatMenuButtonRequest -> ClientM (Response MenuButton)
getChatMenuButton :: GetChatMenuButtonRequest -> ClientM (Response MenuButton)
getChatMenuButton = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @GetChatMenuButton)

type SetMyDefaultAdministratorRights = "setMyDefaultAdministratorRights"
  :> ReqBody '[JSON] SetMyDefaultAdministratorRightsRequest
  :> Post '[JSON] (Response Bool)

-- | Use this method to change the default administrator rights requested by the bot when it's added as an administrator to groups or channels. These rights will be suggested to users, but they are are free to modify the list before adding the bot. Returns 'True' on success.
setMyDefaultAdministratorRights
  :: SetMyDefaultAdministratorRightsRequest -> ClientM (Response Bool)
setMyDefaultAdministratorRights :: SetMyDefaultAdministratorRightsRequest -> ClientM (Response Bool)
setMyDefaultAdministratorRights = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SetMyDefaultAdministratorRights)

type GetMyDefaultAdministratorRights = "getMyDefaultAdministratorRights"
  :> ReqBody '[JSON] GetMyDefaultAdministratorRightsRequest
  :> Post '[JSON] (Response ChatAdministratorRights)

-- | Use this method to get the current default administrator rights of the bot.
-- Returns 'ChatAdministratorRights' on success.
getMyDefaultAdministratorRights
  :: GetMyDefaultAdministratorRightsRequest -> ClientM (Response ChatAdministratorRights)
getMyDefaultAdministratorRights :: GetMyDefaultAdministratorRightsRequest
-> ClientM (Response ChatAdministratorRights)
getMyDefaultAdministratorRights = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @GetMyDefaultAdministratorRights)