{-# 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 ((<&>))
type GetMe = "getMe" :> Get '[JSON] (Response User)
getMe :: ClientM (Response User)
getMe :: ClientM (Response User)
getMe = Proxy GetMe -> Client ClientM GetMe
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy GetMe
forall k (t :: k). Proxy t
Proxy @GetMe)
type DeleteMessage = "deleteMessage"
:> RequiredQueryParam "chat_id" ChatId
:> RequiredQueryParam "message_id" MessageId
:> Get '[JSON] (Response Bool)
deleteMessage :: ChatId -> MessageId -> ClientM (Response Bool)
deleteMessage :: ChatId -> MessageId -> ClientM (Response Bool)
deleteMessage = Proxy DeleteMessage -> Client ClientM DeleteMessage
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy DeleteMessage
forall k (t :: k). Proxy t
Proxy @DeleteMessage)
type SendMessage
= "sendMessage" :> ReqBody '[JSON] SendMessageRequest :> Post '[JSON] (Response Message)
sendMessage :: SendMessageRequest -> ClientM (Response Message)
sendMessage :: SendMessageRequest -> ClientM (Response Message)
sendMessage = Proxy SendMessage -> Client ClientM SendMessage
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendMessage
forall k (t :: k). Proxy t
Proxy @SendMessage)
type ForwardMessage
= "forwardMessage" :> ReqBody '[JSON] ForwardMessageRequest :> Post '[JSON] (Response Message)
forwardMessage :: ForwardMessageRequest -> ClientM (Response Message)
forwardMessage :: ForwardMessageRequest -> ClientM (Response Message)
forwardMessage = Proxy ForwardMessage -> Client ClientM ForwardMessage
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy ForwardMessage
forall k (t :: k). Proxy t
Proxy @ForwardMessage)
data SomeReplyMarkup
= SomeInlineKeyboardMarkup InlineKeyboardMarkup
| SomeReplyKeyboardMarkup ReplyKeyboardMarkup
| SomeReplyKeyboardRemove ReplyKeyboardRemove
| SomeForceReply ForceReply
deriving ((forall x. SomeReplyMarkup -> Rep SomeReplyMarkup x)
-> (forall x. Rep SomeReplyMarkup x -> SomeReplyMarkup)
-> Generic SomeReplyMarkup
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 = SomeReplyMarkup -> Value
forall a. (Generic a, GSomeJSON (Rep a)) => a -> Value
genericSomeToJSON
instance FromJSON SomeReplyMarkup where parseJSON :: Value -> Parser SomeReplyMarkup
parseJSON = Value -> Parser SomeReplyMarkup
forall a. (Generic a, GSomeJSON (Rep a)) => Value -> Parser a
genericSomeParseJSON
data ParseMode
= Markdown
| HTML
| MarkdownV2
deriving ((forall x. ParseMode -> Rep ParseMode x)
-> (forall x. Rep ParseMode x -> ParseMode) -> Generic ParseMode
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
data SendMessageRequest = SendMessageRequest
{ SendMessageRequest -> SomeChatId
sendMessageChatId :: SomeChatId
, SendMessageRequest -> Text
sendMessageText :: Text
, SendMessageRequest -> Maybe ParseMode
sendMessageParseMode :: Maybe ParseMode
, SendMessageRequest -> Maybe [MessageEntity]
sendMessageEntities :: Maybe [MessageEntity]
, SendMessageRequest -> Maybe Bool
sendMessageDisableWebPagePreview :: Maybe Bool
, SendMessageRequest -> Maybe Bool
sendMessageDisableNotification :: Maybe Bool
, SendMessageRequest -> Maybe Bool
sendMessageProtectContent :: Maybe Bool
, SendMessageRequest -> Maybe MessageId
sendMessageReplyToMessageId :: Maybe MessageId
, SendMessageRequest -> Maybe Bool
sendMessageAllowSendingWithoutReply :: Maybe Bool
, SendMessageRequest -> Maybe SomeReplyMarkup
sendMessageReplyMarkup :: Maybe SomeReplyMarkup
} deriving ((forall x. SendMessageRequest -> Rep SendMessageRequest x)
-> (forall x. Rep SendMessageRequest x -> SendMessageRequest)
-> Generic SendMessageRequest
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 = SendMessageRequest -> Value
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 = Value -> Parser SendMessageRequest
forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON
data ForwardMessageRequest = ForwardMessageRequest
{ ForwardMessageRequest -> SomeChatId
forwardMessageChatId :: SomeChatId
, ForwardMessageRequest -> SomeChatId
forwardMessageFromChatId :: SomeChatId
, ForwardMessageRequest -> Maybe Bool
forwardMessageDisableNotification :: Maybe Bool
, ForwardMessageRequest -> Maybe Bool
forwardMessageProtectContent :: Maybe Bool
, ForwardMessageRequest -> MessageId
forwardMessageMessageId :: MessageId
} deriving ((forall x. ForwardMessageRequest -> Rep ForwardMessageRequest x)
-> (forall x. Rep ForwardMessageRequest x -> ForwardMessageRequest)
-> Generic ForwardMessageRequest
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 = ForwardMessageRequest -> Value
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 = Value -> Parser ForwardMessageRequest
forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON
type SendDocumentContent
= "sendDocument"
:> MultipartForm Tmp SendDocumentRequest
:> Post '[JSON] (Response Message)
type SendDocumentLink
= "sendDocument"
:> ReqBody '[JSON] SendDocumentRequest
:> Post '[JSON] (Response Message)
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 <- IO ByteString -> ClientM ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
Proxy SendDocumentContent
-> (ByteString, SendDocumentRequest) -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendDocumentContent
forall k (t :: k). Proxy t
Proxy @SendDocumentContent) (ByteString
boundary, SendDocumentRequest
r)
DocumentFile
_ -> Proxy SendDocumentLink
-> SendDocumentRequest -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendDocumentLink
forall k (t :: k). Proxy t
Proxy @SendDocumentLink) SendDocumentRequest
r
data SendDocumentRequest = SendDocumentRequest
{ SendDocumentRequest -> SomeChatId
sendDocumentChatId :: SomeChatId
, SendDocumentRequest -> DocumentFile
sendDocumentDocument :: DocumentFile
, SendDocumentRequest -> Maybe FilePath
sendDocumentThumb :: Maybe FilePath
, SendDocumentRequest -> Maybe Text
sendDocumentCaption :: Maybe Text
, SendDocumentRequest -> Maybe ParseMode
sendDocumentParseMode :: Maybe ParseMode
, SendDocumentRequest -> Maybe [MessageEntity]
sendDocumentCaptionEntities :: Maybe [MessageEntity]
, SendDocumentRequest -> Maybe Bool
sendDocumentDisableContentTypeDetection :: Maybe Bool
, SendDocumentRequest -> Maybe Bool
sendDocumentDisableNotification :: Maybe Bool
, SendDocumentRequest -> Maybe Bool
sendDocumentProtectContent :: Maybe Bool
, SendDocumentRequest -> Maybe MessageId
sendDocumentReplyToMessageId :: Maybe MessageId
, SendDocumentRequest -> Maybe Bool
sendDocumentAllowSendingWithoutReply :: Maybe Bool
, SendDocumentRequest -> Maybe SomeReplyMarkup
sendDocumentReplyMarkup :: Maybe SomeReplyMarkup
}
deriving (forall x. SendDocumentRequest -> Rep SendDocumentRequest x)
-> (forall x. Rep SendDocumentRequest x -> SendDocumentRequest)
-> Generic SendDocumentRequest
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
(DocumentFile -> Value)
-> (DocumentFile -> Encoding)
-> ([DocumentFile] -> Value)
-> ([DocumentFile] -> Encoding)
-> ToJSON DocumentFile
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) -> (Void# -> r) -> r
DocumentFileId x = MakeDocumentFile (InputFileId x)
pattern DocumentUrl :: Text -> DocumentFile
pattern $bDocumentUrl :: Text -> DocumentFile
$mDocumentUrl :: forall r. DocumentFile -> (Text -> r) -> (Void# -> r) -> r
DocumentUrl x = MakeDocumentFile (FileUrl x)
pattern DocumentFile :: FilePath -> ContentType -> DocumentFile
pattern $bDocumentFile :: FilePath -> Text -> DocumentFile
$mDocumentFile :: forall r.
DocumentFile -> (FilePath -> Text -> r) -> (Void# -> 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
..} = [Input] -> [FileData Tmp] -> MultipartData Tmp
forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [FileData Tmp]
files where
fields :: [Input]
fields =
[ Text -> Text -> Input
Input Text
"document" (Text -> Input) -> Text -> Input
forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ FilePath
"attach://file"
, Text -> Text -> Input
Input Text
"chat_id" (Text -> Input) -> Text -> Input
forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendDocumentChatId of
SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> FilePath
forall a. Show a => a -> FilePath
show Integer
chat_id
SomeChatUsername Text
txt -> Text
txt
] [Input] -> [Input] -> [Input]
forall a. Semigroup a => a -> a -> a
<>
( (([Input] -> [Input])
-> (FilePath -> [Input] -> [Input])
-> Maybe FilePath
-> [Input]
-> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\FilePath
_ -> ((Text -> Text -> Input
Input Text
"thumb" Text
"attach://thumb")Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe FilePath
sendDocumentThumb)
([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (([Input] -> [Input])
-> (Text -> [Input] -> [Input]) -> Maybe Text -> [Input] -> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\Text
t -> ((Text -> Text -> Input
Input Text
"caption" Text
t)Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe Text
sendDocumentCaption)
([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (([Input] -> [Input])
-> (ParseMode -> [Input] -> [Input])
-> Maybe ParseMode
-> [Input]
-> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\ParseMode
t -> ((Text -> Text -> Input
Input Text
"parse_mode" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ ParseMode -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText ParseMode
t))Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe ParseMode
sendDocumentParseMode)
([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (([Input] -> [Input])
-> ([MessageEntity] -> [Input] -> [Input])
-> Maybe [MessageEntity]
-> [Input]
-> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\[MessageEntity]
t -> ((Text -> Text -> Input
Input Text
"caption_entities" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [MessageEntity] -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText [MessageEntity]
t))Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe [MessageEntity]
sendDocumentCaptionEntities)
([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (([Input] -> [Input])
-> (Bool -> [Input] -> [Input]) -> Maybe Bool -> [Input] -> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\Bool
t -> ((Text -> Text -> Input
Input Text
"disable_notification" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t))Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe Bool
sendDocumentDisableNotification)
([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (([Input] -> [Input])
-> (Bool -> [Input] -> [Input]) -> Maybe Bool -> [Input] -> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\Bool
t -> ((Text -> Text -> Input
Input Text
"disable_content_type_detection" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t))Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe Bool
sendDocumentDisableContentTypeDetection)
([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (([Input] -> [Input])
-> (MessageId -> [Input] -> [Input])
-> Maybe MessageId
-> [Input]
-> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\MessageId
t -> ((Text -> Text -> Input
Input Text
"reply_to_message_id" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ MessageId -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t))Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe MessageId
sendDocumentReplyToMessageId)
([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (([Input] -> [Input])
-> (Bool -> [Input] -> [Input]) -> Maybe Bool -> [Input] -> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\Bool
t -> ((Text -> Text -> Input
Input Text
"allow_sending_without_reply" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t))Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe Bool
sendDocumentAllowSendingWithoutReply)
([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (([Input] -> [Input])
-> (SomeReplyMarkup -> [Input] -> [Input])
-> Maybe SomeReplyMarkup
-> [Input]
-> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\SomeReplyMarkup
t -> ((Text -> Text -> Input
Input Text
"reply_markup" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ SomeReplyMarkup -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText SomeReplyMarkup
t))Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe SomeReplyMarkup
sendDocumentReplyMarkup)
[])
files :: [FileData Tmp]
files
= (Text -> Text -> Text -> MultipartResult Tmp -> FileData Tmp
forall tag.
Text -> Text -> Text -> MultipartResult tag -> FileData tag
FileData Text
"file" (FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeFileName FilePath
path) Text
ct FilePath
MultipartResult Tmp
path)
FileData Tmp -> [FileData Tmp] -> [FileData Tmp]
forall a. a -> [a] -> [a]
: [FileData Tmp]
-> (FilePath -> [FileData Tmp]) -> Maybe FilePath -> [FileData Tmp]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\FilePath
t -> [Text -> Text -> Text -> MultipartResult Tmp -> FileData Tmp
forall tag.
Text -> Text -> Text -> MultipartResult tag -> FileData tag
FileData Text
"thumb" (FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeFileName FilePath
t) Text
"image/jpeg" FilePath
MultipartResult Tmp
t]) Maybe FilePath
sendDocumentThumb
DocumentFile FilePath
path Text
ct = DocumentFile
sendDocumentDocument
instance ToJSON SendDocumentRequest where toJSON :: SendDocumentRequest -> Value
toJSON = SendDocumentRequest -> Value
forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
toSendDocument :: SomeChatId -> DocumentFile -> SendDocumentRequest
toSendDocument :: SomeChatId -> DocumentFile -> SendDocumentRequest
toSendDocument SomeChatId
ch DocumentFile
df = SendDocumentRequest :: SomeChatId
-> DocumentFile
-> Maybe FilePath
-> Maybe Text
-> Maybe ParseMode
-> Maybe [MessageEntity]
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe MessageId
-> Maybe Bool
-> Maybe SomeReplyMarkup
-> SendDocumentRequest
SendDocumentRequest
{ sendDocumentChatId :: SomeChatId
sendDocumentChatId = SomeChatId
ch
, sendDocumentDocument :: DocumentFile
sendDocumentDocument = DocumentFile
df
, sendDocumentThumb :: Maybe FilePath
sendDocumentThumb = Maybe FilePath
forall a. Maybe a
Nothing
, sendDocumentCaption :: Maybe Text
sendDocumentCaption = Maybe Text
forall a. Maybe a
Nothing
, sendDocumentParseMode :: Maybe ParseMode
sendDocumentParseMode = Maybe ParseMode
forall a. Maybe a
Nothing
, sendDocumentCaptionEntities :: Maybe [MessageEntity]
sendDocumentCaptionEntities = Maybe [MessageEntity]
forall a. Maybe a
Nothing
, sendDocumentDisableContentTypeDetection :: Maybe Bool
sendDocumentDisableContentTypeDetection = Maybe Bool
forall a. Maybe a
Nothing
, sendDocumentDisableNotification :: Maybe Bool
sendDocumentDisableNotification = Maybe Bool
forall a. Maybe a
Nothing
, sendDocumentProtectContent :: Maybe Bool
sendDocumentProtectContent = Maybe Bool
forall a. Maybe a
Nothing
, sendDocumentReplyToMessageId :: Maybe MessageId
sendDocumentReplyToMessageId = Maybe MessageId
forall a. Maybe a
Nothing
, sendDocumentAllowSendingWithoutReply :: Maybe Bool
sendDocumentAllowSendingWithoutReply = Maybe Bool
forall a. Maybe a
Nothing
, sendDocumentReplyMarkup :: Maybe SomeReplyMarkup
sendDocumentReplyMarkup = Maybe SomeReplyMarkup
forall a. Maybe a
Nothing
}
type GetFile
= "getFile"
:> RequiredQueryParam "file_id" FileId
:> Get '[JSON] (Response File)
getFile :: FileId -> ClientM (Response File)
getFile :: FileId -> ClientM (Response File)
getFile = Proxy GetFile -> Client ClientM GetFile
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy GetFile
forall k (t :: k). Proxy t
Proxy @GetFile)
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
(PhotoFile -> Value)
-> (PhotoFile -> Encoding)
-> ([PhotoFile] -> Value)
-> ([PhotoFile] -> Encoding)
-> ToJSON PhotoFile
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) -> (Void# -> r) -> r
PhotoFileId x = MakePhotoFile (InputFileId x)
pattern PhotoUrl :: Text -> PhotoFile
pattern $bPhotoUrl :: Text -> PhotoFile
$mPhotoUrl :: forall r. PhotoFile -> (Text -> r) -> (Void# -> r) -> r
PhotoUrl x = MakePhotoFile (FileUrl x)
pattern PhotoFile :: FilePath -> ContentType -> PhotoFile
pattern $bPhotoFile :: FilePath -> Text -> PhotoFile
$mPhotoFile :: forall r. PhotoFile -> (FilePath -> Text -> r) -> (Void# -> r) -> r
PhotoFile x y = MakePhotoFile (InputFile x y)
data SendPhotoRequest = SendPhotoRequest
{ SendPhotoRequest -> SomeChatId
sendPhotoChatId :: SomeChatId
, SendPhotoRequest -> PhotoFile
sendPhotoPhoto :: PhotoFile
, SendPhotoRequest -> Maybe FilePath
sendPhotoThumb :: Maybe FilePath
, SendPhotoRequest -> Maybe Text
sendPhotoCaption :: Maybe Text
, SendPhotoRequest -> Maybe ParseMode
sendPhotoParseMode :: Maybe ParseMode
, SendPhotoRequest -> Maybe [MessageEntity]
sendPhotoCaptionEntities :: Maybe [MessageEntity]
, SendPhotoRequest -> Maybe Bool
sendPhotoDisableNotification :: Maybe Bool
, SendPhotoRequest -> Maybe Bool
sendPhotoProtectContent :: Maybe Bool
, SendPhotoRequest -> Maybe MessageId
sendPhotoReplyToMessageId :: Maybe MessageId
, SendPhotoRequest -> Maybe Bool
sendPhotoAllowSendingWithoutReply :: Maybe Bool
, SendPhotoRequest -> Maybe SomeReplyMarkup
sendPhotoReplyMarkup :: Maybe SomeReplyMarkup
}
deriving (forall x. SendPhotoRequest -> Rep SendPhotoRequest x)
-> (forall x. Rep SendPhotoRequest x -> SendPhotoRequest)
-> Generic SendPhotoRequest
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
..} = [Input] -> [FileData Tmp] -> MultipartData Tmp
forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [FileData Tmp]
files where
fields :: [Input]
fields =
[ Text -> Text -> Input
Input Text
"photo" (Text -> Input) -> Text -> Input
forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ FilePath
"attach://file"
, Text -> Text -> Input
Input Text
"chat_id" (Text -> Input) -> Text -> Input
forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendPhotoChatId of
SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> FilePath
forall a. Show a => a -> FilePath
show Integer
chat_id
SomeChatUsername Text
txt -> Text
txt
] [Input] -> [Input] -> [Input]
forall a. Semigroup a => a -> a -> a
<>
( (([Input] -> [Input])
-> (FilePath -> [Input] -> [Input])
-> Maybe FilePath
-> [Input]
-> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\FilePath
_ -> ((Text -> Text -> Input
Input Text
"thumb" Text
"attach://thumb")Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe FilePath
sendPhotoThumb)
([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (([Input] -> [Input])
-> (Text -> [Input] -> [Input]) -> Maybe Text -> [Input] -> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\Text
t -> ((Text -> Text -> Input
Input Text
"caption" Text
t)Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe Text
sendPhotoCaption)
([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (([Input] -> [Input])
-> (ParseMode -> [Input] -> [Input])
-> Maybe ParseMode
-> [Input]
-> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\ParseMode
t -> ((Text -> Text -> Input
Input Text
"parse_mode" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ ParseMode -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText ParseMode
t))Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe ParseMode
sendPhotoParseMode)
([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (([Input] -> [Input])
-> ([MessageEntity] -> [Input] -> [Input])
-> Maybe [MessageEntity]
-> [Input]
-> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\[MessageEntity]
t -> ((Text -> Text -> Input
Input Text
"caption_entities" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [MessageEntity] -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText [MessageEntity]
t))Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe [MessageEntity]
sendPhotoCaptionEntities)
([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (([Input] -> [Input])
-> (Bool -> [Input] -> [Input]) -> Maybe Bool -> [Input] -> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\Bool
t -> ((Text -> Text -> Input
Input Text
"disable_notification" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t))Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe Bool
sendPhotoDisableNotification)
([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (([Input] -> [Input])
-> (MessageId -> [Input] -> [Input])
-> Maybe MessageId
-> [Input]
-> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\MessageId
t -> ((Text -> Text -> Input
Input Text
"reply_to_message_id" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ MessageId -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t))Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe MessageId
sendPhotoReplyToMessageId)
([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (([Input] -> [Input])
-> (Bool -> [Input] -> [Input]) -> Maybe Bool -> [Input] -> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\Bool
t -> ((Text -> Text -> Input
Input Text
"allow_sending_without_reply" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t))Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe Bool
sendPhotoAllowSendingWithoutReply)
([Input] -> [Input]) -> [Input] -> [Input]
forall a b. (a -> b) -> a -> b
$ (([Input] -> [Input])
-> (SomeReplyMarkup -> [Input] -> [Input])
-> Maybe SomeReplyMarkup
-> [Input]
-> [Input]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Input] -> [Input]
forall a. a -> a
id (\SomeReplyMarkup
t -> ((Text -> Text -> Input
Input Text
"reply_markup" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ SomeReplyMarkup -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText SomeReplyMarkup
t))Input -> [Input] -> [Input]
forall a. a -> [a] -> [a]
:)) Maybe SomeReplyMarkup
sendPhotoReplyMarkup)
[])
files :: [FileData Tmp]
files
= (Text -> Text -> Text -> MultipartResult Tmp -> FileData Tmp
forall tag.
Text -> Text -> Text -> MultipartResult tag -> FileData tag
FileData Text
"file" (FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeFileName FilePath
path) Text
ct FilePath
MultipartResult Tmp
path)
FileData Tmp -> [FileData Tmp] -> [FileData Tmp]
forall a. a -> [a] -> [a]
: [FileData Tmp]
-> (FilePath -> [FileData Tmp]) -> Maybe FilePath -> [FileData Tmp]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (\FilePath
t -> [Text -> Text -> Text -> MultipartResult Tmp -> FileData Tmp
forall tag.
Text -> Text -> Text -> MultipartResult tag -> FileData tag
FileData Text
"thumb" (FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath
takeFileName FilePath
t) Text
"image/jpeg" FilePath
MultipartResult Tmp
t]) Maybe FilePath
sendPhotoThumb
PhotoFile FilePath
path Text
ct = PhotoFile
sendPhotoPhoto
instance ToJSON SendPhotoRequest where toJSON :: SendPhotoRequest -> Value
toJSON = SendPhotoRequest -> Value
forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
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 <- IO ByteString -> ClientM ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
Proxy SendPhotoContent
-> (ByteString, SendPhotoRequest) -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendPhotoContent
forall k (t :: k). Proxy t
Proxy @SendPhotoContent) (ByteString
boundary, SendPhotoRequest
r)
PhotoFile
_ -> Proxy SendPhotoLink
-> SendPhotoRequest -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendPhotoLink
forall k (t :: k). Proxy t
Proxy @SendPhotoLink) SendPhotoRequest
r
data CopyMessageRequest = CopyMessageRequest
{ CopyMessageRequest -> SomeChatId
copyMessageChatId :: SomeChatId
, CopyMessageRequest -> SomeChatId
copyMessageFromChatId :: SomeChatId
, CopyMessageRequest -> MessageId
copyMessageMessageId :: MessageId
, CopyMessageRequest -> Maybe Text
copyMessageCaption :: Maybe Text
, CopyMessageRequest -> Maybe ParseMode
copyMessageParseMode :: Maybe ParseMode
, CopyMessageRequest -> Maybe [MessageEntity]
copyMessageCaptionEntities :: Maybe [MessageEntity]
, CopyMessageRequest -> Maybe Bool
copyMessageDisableNotification :: Maybe Bool
, CopyMessageRequest -> Maybe Bool
copyMessageProtectContent :: Maybe Bool
, CopyMessageRequest -> Maybe MessageId
copyMessageReplyToMessageId :: Maybe MessageId
, CopyMessageRequest -> Maybe Bool
copyMessageAllowSendingWithoutReply :: Maybe Bool
, CopyMessageRequest -> Maybe InlineKeyboardMarkup
copyMessageReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x. CopyMessageRequest -> Rep CopyMessageRequest x)
-> (forall x. Rep CopyMessageRequest x -> CopyMessageRequest)
-> Generic CopyMessageRequest
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
data SendAudioRequest = SendAudioRequest
{ SendAudioRequest -> SomeChatId
sendAudioChatId :: SomeChatId
, SendAudioRequest -> InputFile
sendAudioAudio :: InputFile
, SendAudioRequest -> Maybe Int
sendAudioDuration :: Maybe Int
, SendAudioRequest -> Maybe Text
sendAudioPerformer :: Maybe Text
, SendAudioRequest -> Maybe Text
sendAudioTitle :: Maybe Text
, SendAudioRequest -> Maybe InputFile
sendAudioThumb :: Maybe InputFile
, SendAudioRequest -> Maybe Text
sendAudioCaption :: Maybe Text
, SendAudioRequest -> Maybe ParseMode
sendAudioParseMode :: Maybe ParseMode
, SendAudioRequest -> Maybe [MessageEntity]
sendAudioCaptionEntities :: Maybe [MessageEntity]
, SendAudioRequest -> Maybe Bool
sendAudioDisableNotification :: Maybe Bool
, SendAudioRequest -> Maybe Bool
sendAudioProtectContent :: Maybe Bool
, SendAudioRequest -> Maybe MessageId
sendAudioReplyToMessageId :: Maybe MessageId
, SendAudioRequest -> Maybe Bool
sendAudioAllowSendingWithoutReply :: Maybe Bool
, SendAudioRequest -> Maybe InlineKeyboardMarkup
sendAudioReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x. SendAudioRequest -> Rep SendAudioRequest x)
-> (forall x. Rep SendAudioRequest x -> SendAudioRequest)
-> Generic SendAudioRequest
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 = SendAudioRequest -> Value
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
..} =
(MultipartData Tmp -> MultipartData Tmp)
-> (InputFile -> MultipartData Tmp -> MultipartData Tmp)
-> Maybe InputFile
-> MultipartData Tmp
-> MultipartData Tmp
forall b a. b -> (a -> b) -> Maybe a -> b
maybe MultipartData Tmp -> MultipartData Tmp
forall a. a -> a
id (Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"thumb") Maybe InputFile
sendAudioThumb (MultipartData Tmp -> MultipartData Tmp)
-> MultipartData Tmp -> MultipartData Tmp
forall a b. (a -> b) -> a -> b
$
Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"audio" InputFile
sendAudioAudio (MultipartData Tmp -> MultipartData Tmp)
-> MultipartData Tmp -> MultipartData Tmp
forall a b. (a -> b) -> a -> b
$
[Input] -> [FileData Tmp] -> MultipartData Tmp
forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [] where
fields :: [Input]
fields =
[ Text -> Text -> Input
Input Text
"chat_id" (Text -> Input) -> Text -> Input
forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendAudioChatId of
SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> FilePath
forall a. Show a => a -> FilePath
show Integer
chat_id
SomeChatUsername Text
txt -> Text
txt
] [Input] -> [Input] -> [Input]
forall a. Semigroup a => a -> a -> a
<> [Maybe Input] -> [Input]
forall a. [Maybe a] -> [a]
catMaybes
[ Maybe Text
sendAudioCaption Maybe Text -> (Text -> Input) -> Maybe Input
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 Maybe ParseMode -> (ParseMode -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ ParseMode -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText ParseMode
t)
, Maybe [MessageEntity]
sendAudioCaptionEntities Maybe [MessageEntity] -> ([MessageEntity] -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [MessageEntity] -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText [MessageEntity]
t)
, Maybe Int
sendAudioDuration Maybe Int -> (Int -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Int
t -> Text -> Text -> Input
Input Text
"duration" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
, Maybe Text
sendAudioPerformer Maybe Text -> (Text -> Input) -> Maybe Input
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 Maybe Text -> (Text -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Text
t -> Text -> Text -> Input
Input Text
"title" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Text
t)
, Maybe Bool
sendAudioDisableNotification Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"disable_notification" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe Bool
sendAudioProtectContent Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"protected_content" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe MessageId
sendAudioReplyToMessageId Maybe MessageId -> (MessageId -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ MessageId -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t)
, Maybe Bool
sendAudioAllowSendingWithoutReply Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"allow_sending_without_reply" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe InlineKeyboardMarkup
sendAudioReplyMarkup Maybe InlineKeyboardMarkup
-> (InlineKeyboardMarkup -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ InlineKeyboardMarkup -> Text
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)
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 <- IO ByteString -> ClientM ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
Proxy SendAudioContent
-> (ByteString, SendAudioRequest) -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendAudioContent
forall k (t :: k). Proxy t
Proxy @SendAudioContent) (ByteString
boundary, SendAudioRequest
r)
(InputFile
_, Just InputFile{}) -> do
ByteString
boundary <- IO ByteString -> ClientM ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
Proxy SendAudioContent
-> (ByteString, SendAudioRequest) -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendAudioContent
forall k (t :: k). Proxy t
Proxy @SendAudioContent) (ByteString
boundary, SendAudioRequest
r)
(InputFile, Maybe InputFile)
_ -> Proxy SendAudioLink
-> SendAudioRequest -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendAudioLink
forall k (t :: k). Proxy t
Proxy @SendAudioLink) SendAudioRequest
r
data SendVideoRequest = SendVideoRequest
{ SendVideoRequest -> SomeChatId
sendVideoChatId :: SomeChatId
, SendVideoRequest -> InputFile
sendVideoVideo :: InputFile
, SendVideoRequest -> Maybe Int
sendVideoDuration :: Maybe Int
, SendVideoRequest -> Maybe Int
sendVideoWidth :: Maybe Int
, SendVideoRequest -> Maybe Int
sendVideoHeight :: Maybe Int
, SendVideoRequest -> Maybe InputFile
sendVideoThumb :: Maybe InputFile
, SendVideoRequest -> Maybe Text
sendVideoCaption :: Maybe Text
, SendVideoRequest -> Maybe ParseMode
sendVideoParseMode :: Maybe ParseMode
, SendVideoRequest -> Maybe [MessageEntity]
sendVideoCaptionEntities :: Maybe [MessageEntity]
, SendVideoRequest -> Maybe Bool
sendVideoSupportsStreaming :: Maybe Bool
, SendVideoRequest -> Maybe Bool
sendVideoDisableNotification :: Maybe Bool
, SendVideoRequest -> Maybe Bool
sendVideoProtectContent :: Maybe Bool
, SendVideoRequest -> Maybe MessageId
sendVideoReplyToMessageId :: Maybe MessageId
, SendVideoRequest -> Maybe Bool
sendVideoAllowSendingWithoutReply :: Maybe Bool
, SendVideoRequest -> Maybe InlineKeyboardMarkup
sendVideoReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x. SendVideoRequest -> Rep SendVideoRequest x)
-> (forall x. Rep SendVideoRequest x -> SendVideoRequest)
-> Generic SendVideoRequest
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 = SendVideoRequest -> Value
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
..} =
(MultipartData Tmp -> MultipartData Tmp)
-> (InputFile -> MultipartData Tmp -> MultipartData Tmp)
-> Maybe InputFile
-> MultipartData Tmp
-> MultipartData Tmp
forall b a. b -> (a -> b) -> Maybe a -> b
maybe MultipartData Tmp -> MultipartData Tmp
forall a. a -> a
id (Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"thumb") Maybe InputFile
sendVideoThumb (MultipartData Tmp -> MultipartData Tmp)
-> MultipartData Tmp -> MultipartData Tmp
forall a b. (a -> b) -> a -> b
$
Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"video" InputFile
sendVideoVideo (MultipartData Tmp -> MultipartData Tmp)
-> MultipartData Tmp -> MultipartData Tmp
forall a b. (a -> b) -> a -> b
$
[Input] -> [FileData Tmp] -> MultipartData Tmp
forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [] where
fields :: [Input]
fields =
[ Text -> Text -> Input
Input Text
"chat_id" (Text -> Input) -> Text -> Input
forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendVideoChatId of
SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> FilePath
forall a. Show a => a -> FilePath
show Integer
chat_id
SomeChatUsername Text
txt -> Text
txt
] [Input] -> [Input] -> [Input]
forall a. Semigroup a => a -> a -> a
<> [Maybe Input] -> [Input]
forall a. [Maybe a] -> [a]
catMaybes
[ Maybe Text
sendVideoCaption Maybe Text -> (Text -> Input) -> Maybe Input
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 Maybe ParseMode -> (ParseMode -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ ParseMode -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText ParseMode
t)
, Maybe [MessageEntity]
sendVideoCaptionEntities Maybe [MessageEntity] -> ([MessageEntity] -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [MessageEntity] -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText [MessageEntity]
t)
, Maybe Int
sendVideoDuration Maybe Int -> (Int -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Int
t -> Text -> Text -> Input
Input Text
"duration" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
, Maybe Int
sendVideoWidth Maybe Int -> (Int -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Int
t -> Text -> Text -> Input
Input Text
"width" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
, Maybe Int
sendVideoHeight Maybe Int -> (Int -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Int
t -> Text -> Text -> Input
Input Text
"height" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
, Maybe Bool
sendVideoDisableNotification Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"disable_notification" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe Bool
sendVideoSupportsStreaming Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"supports_streaming" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe Bool
sendVideoProtectContent Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"protected_content" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe MessageId
sendVideoReplyToMessageId Maybe MessageId -> (MessageId -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ MessageId -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t)
, Maybe Bool
sendVideoAllowSendingWithoutReply Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"allow_sending_without_reply" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe InlineKeyboardMarkup
sendVideoReplyMarkup Maybe InlineKeyboardMarkup
-> (InlineKeyboardMarkup -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ InlineKeyboardMarkup -> Text
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)
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 <- IO ByteString -> ClientM ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
Proxy SendVideoContent
-> (ByteString, SendVideoRequest) -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendVideoContent
forall k (t :: k). Proxy t
Proxy @SendVideoContent) (ByteString
boundary, SendVideoRequest
r)
(InputFile
_, Just InputFile{}) -> do
ByteString
boundary <- IO ByteString -> ClientM ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
Proxy SendVideoContent
-> (ByteString, SendVideoRequest) -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendVideoContent
forall k (t :: k). Proxy t
Proxy @SendVideoContent) (ByteString
boundary, SendVideoRequest
r)
(InputFile, Maybe InputFile)
_ -> Proxy SendVideoLink
-> SendVideoRequest -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendVideoLink
forall k (t :: k). Proxy t
Proxy @SendVideoLink) SendVideoRequest
r
data SendAnimationRequest = SendAnimationRequest
{ SendAnimationRequest -> SomeChatId
sendAnimationChatId :: SomeChatId
, SendAnimationRequest -> InputFile
sendAnimationAnimation :: InputFile
, SendAnimationRequest -> Maybe Int
sendAnimationDuration :: Maybe Int
, SendAnimationRequest -> Maybe Int
sendAnimationWidth :: Maybe Int
, SendAnimationRequest -> Maybe Int
sendAnimationHeight :: Maybe Int
, SendAnimationRequest -> Maybe InputFile
sendAnimationThumb :: Maybe InputFile
, SendAnimationRequest -> Maybe Text
sendAnimationCaption :: Maybe Text
, SendAnimationRequest -> Maybe ParseMode
sendAnimationParseMode :: Maybe ParseMode
, SendAnimationRequest -> Maybe [MessageEntity]
sendAnimationCaptionEntities :: Maybe [MessageEntity]
, SendAnimationRequest -> Maybe Bool
sendAnimationDisableNotification :: Maybe Bool
, SendAnimationRequest -> Maybe Bool
sendAnimationProtectContent :: Maybe Bool
, SendAnimationRequest -> Maybe MessageId
sendAnimationReplyToMessageId :: Maybe MessageId
, SendAnimationRequest -> Maybe Bool
sendAnimationAllowSendingWithoutReply :: Maybe Bool
, SendAnimationRequest -> Maybe InlineKeyboardMarkup
sendAnimationReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x. SendAnimationRequest -> Rep SendAnimationRequest x)
-> (forall x. Rep SendAnimationRequest x -> SendAnimationRequest)
-> Generic SendAnimationRequest
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 = SendAnimationRequest -> Value
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
..} =
(MultipartData Tmp -> MultipartData Tmp)
-> (InputFile -> MultipartData Tmp -> MultipartData Tmp)
-> Maybe InputFile
-> MultipartData Tmp
-> MultipartData Tmp
forall b a. b -> (a -> b) -> Maybe a -> b
maybe MultipartData Tmp -> MultipartData Tmp
forall a. a -> a
id (Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"thumb") Maybe InputFile
sendAnimationThumb (MultipartData Tmp -> MultipartData Tmp)
-> MultipartData Tmp -> MultipartData Tmp
forall a b. (a -> b) -> a -> b
$
Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"animation" InputFile
sendAnimationAnimation (MultipartData Tmp -> MultipartData Tmp)
-> MultipartData Tmp -> MultipartData Tmp
forall a b. (a -> b) -> a -> b
$
[Input] -> [FileData Tmp] -> MultipartData Tmp
forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [] where
fields :: [Input]
fields =
[ Text -> Text -> Input
Input Text
"chat_id" (Text -> Input) -> Text -> Input
forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendAnimationChatId of
SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> FilePath
forall a. Show a => a -> FilePath
show Integer
chat_id
SomeChatUsername Text
txt -> Text
txt
] [Input] -> [Input] -> [Input]
forall a. Semigroup a => a -> a -> a
<> [Maybe Input] -> [Input]
forall a. [Maybe a] -> [a]
catMaybes
[ Maybe Text
sendAnimationCaption Maybe Text -> (Text -> Input) -> Maybe Input
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 Maybe ParseMode -> (ParseMode -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ ParseMode -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText ParseMode
t)
, Maybe [MessageEntity]
sendAnimationCaptionEntities Maybe [MessageEntity] -> ([MessageEntity] -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [MessageEntity] -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText [MessageEntity]
t)
, Maybe Int
sendAnimationDuration Maybe Int -> (Int -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Int
t -> Text -> Text -> Input
Input Text
"duration" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
, Maybe Int
sendAnimationWidth Maybe Int -> (Int -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Int
t -> Text -> Text -> Input
Input Text
"width" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
, Maybe Int
sendAnimationHeight Maybe Int -> (Int -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Int
t -> Text -> Text -> Input
Input Text
"height" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
, Maybe Bool
sendAnimationDisableNotification Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"disable_notification" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe Bool
sendAnimationProtectContent Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"protected_content" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe MessageId
sendAnimationReplyToMessageId Maybe MessageId -> (MessageId -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ MessageId -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t)
, Maybe Bool
sendAnimationAllowSendingWithoutReply Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"allow_sending_without_reply" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe InlineKeyboardMarkup
sendAnimationReplyMarkup Maybe InlineKeyboardMarkup
-> (InlineKeyboardMarkup -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ InlineKeyboardMarkup -> Text
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)
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 <- IO ByteString -> ClientM ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
Proxy SendAnimationContent
-> (ByteString, SendAnimationRequest) -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendAnimationContent
forall k (t :: k). Proxy t
Proxy @SendAnimationContent) (ByteString
boundary, SendAnimationRequest
r)
(InputFile
_, Just InputFile{}) -> do
ByteString
boundary <- IO ByteString -> ClientM ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
Proxy SendAnimationContent
-> (ByteString, SendAnimationRequest) -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendAnimationContent
forall k (t :: k). Proxy t
Proxy @SendAnimationContent) (ByteString
boundary, SendAnimationRequest
r)
(InputFile, Maybe InputFile)
_ -> Proxy SendAnimationLink
-> SendAnimationRequest -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendAnimationLink
forall k (t :: k). Proxy t
Proxy @SendAnimationLink) SendAnimationRequest
r
data SendVoiceRequest = SendVoiceRequest
{ SendVoiceRequest -> SomeChatId
sendVoiceChatId :: SomeChatId
, SendVoiceRequest -> InputFile
sendVoiceVoice :: InputFile
, SendVoiceRequest -> Maybe Text
sendVoiceCaption :: Maybe Text
, SendVoiceRequest -> Maybe ParseMode
sendVoiceParseMode :: Maybe ParseMode
, SendVoiceRequest -> Maybe [MessageEntity]
sendVoiceCaptionEntities :: Maybe [MessageEntity]
, SendVoiceRequest -> Maybe Int
sendVoiceDuration :: Maybe Int
, SendVoiceRequest -> Maybe Bool
sendVoiceDisableNotification :: Maybe Bool
, SendVoiceRequest -> Maybe Bool
sendVoiceProtectContent :: Maybe Bool
, SendVoiceRequest -> Maybe MessageId
sendVoiceReplyToMessageId :: Maybe MessageId
, SendVoiceRequest -> Maybe Bool
sendVoiceAllowSendingWithoutReply :: Maybe Bool
, SendVoiceRequest -> Maybe InlineKeyboardMarkup
sendVoiceReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x. SendVoiceRequest -> Rep SendVoiceRequest x)
-> (forall x. Rep SendVoiceRequest x -> SendVoiceRequest)
-> Generic SendVoiceRequest
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 = SendVoiceRequest -> Value
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 (MultipartData Tmp -> MultipartData Tmp)
-> MultipartData Tmp -> MultipartData Tmp
forall a b. (a -> b) -> a -> b
$
[Input] -> [FileData Tmp] -> MultipartData Tmp
forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [] where
fields :: [Input]
fields =
[ Text -> Text -> Input
Input Text
"chat_id" (Text -> Input) -> Text -> Input
forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendVoiceChatId of
SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> FilePath
forall a. Show a => a -> FilePath
show Integer
chat_id
SomeChatUsername Text
txt -> Text
txt
] [Input] -> [Input] -> [Input]
forall a. Semigroup a => a -> a -> a
<> [Maybe Input] -> [Input]
forall a. [Maybe a] -> [a]
catMaybes
[ Maybe Text
sendVoiceCaption Maybe Text -> (Text -> Input) -> Maybe Input
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 Maybe ParseMode -> (ParseMode -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ ParseMode -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText ParseMode
t)
, Maybe [MessageEntity]
sendVoiceCaptionEntities Maybe [MessageEntity] -> ([MessageEntity] -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ [MessageEntity] -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText [MessageEntity]
t)
, Maybe Int
sendVoiceDuration Maybe Int -> (Int -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Int
t -> Text -> Text -> Input
Input Text
"duration" (Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText Int
t)
, Maybe Bool
sendVoiceProtectContent Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"protected_content" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe Bool
sendVoiceDisableNotification Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"disable_notification" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe MessageId
sendVoiceReplyToMessageId Maybe MessageId -> (MessageId -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ MessageId -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t)
, Maybe Bool
sendVoiceAllowSendingWithoutReply Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"allow_sending_without_reply" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe InlineKeyboardMarkup
sendVoiceReplyMarkup Maybe InlineKeyboardMarkup
-> (InlineKeyboardMarkup -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ InlineKeyboardMarkup -> Text
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)
sendVoice :: SendVoiceRequest -> ClientM (Response Message)
sendVoice :: SendVoiceRequest -> ClientM (Response Message)
sendVoice SendVoiceRequest
r = case SendVoiceRequest -> InputFile
sendVoiceVoice SendVoiceRequest
r of
InputFile{} -> do
ByteString
boundary <- IO ByteString -> ClientM ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
Proxy SendVoiceContent
-> (ByteString, SendVoiceRequest) -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendVoiceContent
forall k (t :: k). Proxy t
Proxy @SendVoiceContent) (ByteString
boundary, SendVoiceRequest
r)
InputFile
_ -> Proxy SendVoiceLink
-> SendVoiceRequest -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendVoiceLink
forall k (t :: k). Proxy t
Proxy @SendVoiceLink) SendVoiceRequest
r
data SendVideoNoteRequest = SendVideoNoteRequest
{ SendVideoNoteRequest -> SomeChatId
sendVideoNoteChatId :: SomeChatId
, SendVideoNoteRequest -> InputFile
sendVideoNoteVideoNote :: InputFile
, SendVideoNoteRequest -> Maybe Int
sendVideoNoteDuration :: Maybe Int
, SendVideoNoteRequest -> Maybe Int
sendVideoNoteLength :: Maybe Int
, SendVideoNoteRequest -> Maybe InputFile
sendVideoNoteThumb :: Maybe InputFile
, SendVideoNoteRequest -> Maybe Bool
sendVideoNoteDisableNotification :: Maybe Bool
, SendVideoNoteRequest -> Maybe Bool
sendVideoNoteProtectContent :: Maybe Bool
, SendVideoNoteRequest -> Maybe MessageId
sendVideoNoteReplyToMessageId :: Maybe MessageId
, SendVideoNoteRequest -> Maybe Bool
sendVideoNoteAllowSendingWithoutReply :: Maybe Bool
, SendVideoNoteRequest -> Maybe InlineKeyboardMarkup
sendVideoNoteReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x. SendVideoNoteRequest -> Rep SendVideoNoteRequest x)
-> (forall x. Rep SendVideoNoteRequest x -> SendVideoNoteRequest)
-> Generic SendVideoNoteRequest
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 = SendVideoNoteRequest -> Value
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
..} =
(MultipartData Tmp -> MultipartData Tmp)
-> (InputFile -> MultipartData Tmp -> MultipartData Tmp)
-> Maybe InputFile
-> MultipartData Tmp
-> MultipartData Tmp
forall b a. b -> (a -> b) -> Maybe a -> b
maybe MultipartData Tmp -> MultipartData Tmp
forall a. a -> a
id (Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"thumb") Maybe InputFile
sendVideoNoteThumb (MultipartData Tmp -> MultipartData Tmp)
-> MultipartData Tmp -> MultipartData Tmp
forall a b. (a -> b) -> a -> b
$
Text -> InputFile -> MultipartData Tmp -> MultipartData Tmp
makeFile Text
"video_note" InputFile
sendVideoNoteVideoNote (MultipartData Tmp -> MultipartData Tmp)
-> MultipartData Tmp -> MultipartData Tmp
forall a b. (a -> b) -> a -> b
$
[Input] -> [FileData Tmp] -> MultipartData Tmp
forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields [] where
fields :: [Input]
fields =
[ Text -> Text -> Input
Input Text
"chat_id" (Text -> Input) -> Text -> Input
forall a b. (a -> b) -> a -> b
$ case SomeChatId
sendVideoNoteChatId of
SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> FilePath
forall a. Show a => a -> FilePath
show Integer
chat_id
SomeChatUsername Text
txt -> Text
txt
] [Input] -> [Input] -> [Input]
forall a. Semigroup a => a -> a -> a
<> [Maybe Input] -> [Input]
forall a. [Maybe a] -> [a]
catMaybes
[ Maybe Bool
sendVideoNoteDisableNotification Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"disable_notification" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe Bool
sendVideoNoteProtectContent Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"protected_content" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe MessageId
sendVideoNoteReplyToMessageId Maybe MessageId -> (MessageId -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ MessageId -> Text
forall a. ToJSON a => a -> Text
encodeToLazyText MessageId
t)
, Maybe Bool
sendVideoNoteAllowSendingWithoutReply Maybe Bool -> (Bool -> Input) -> Maybe Input
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&>
\Bool
t -> Text -> Text -> Input
Input Text
"allow_sending_without_reply" (Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
t)
, Maybe InlineKeyboardMarkup
sendVideoNoteReplyMarkup Maybe InlineKeyboardMarkup
-> (InlineKeyboardMarkup -> Input) -> Maybe Input
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 (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ InlineKeyboardMarkup -> Text
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)
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 <- IO ByteString -> ClientM ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
Proxy SendVideoNoteContent
-> (ByteString, SendVideoNoteRequest) -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendVideoNoteContent
forall k (t :: k). Proxy t
Proxy @SendVideoNoteContent) (ByteString
boundary, SendVideoNoteRequest
r)
(InputFile
_, Just InputFile{}) -> do
ByteString
boundary <- IO ByteString -> ClientM ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
Proxy SendVideoNoteContent
-> (ByteString, SendVideoNoteRequest) -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendVideoNoteContent
forall k (t :: k). Proxy t
Proxy @SendVideoNoteContent) (ByteString
boundary, SendVideoNoteRequest
r)
(InputFile, Maybe InputFile)
_ -> Proxy SendVideoNoteLink
-> SendVideoNoteRequest -> ClientM (Response Message)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendVideoNoteLink
forall k (t :: k). Proxy t
Proxy @SendVideoNoteLink) SendVideoNoteRequest
r
data SendMediaGroupRequest = SendMediaGroupRequest
{ SendMediaGroupRequest -> SomeChatId
sendMediaGroupChatId :: SomeChatId
, SendMediaGroupRequest -> [InputMedia]
sendMediaGroupMedia :: [InputMedia]
, SendMediaGroupRequest -> Maybe Bool
sendMediaGroupDisableNotification :: Maybe Bool
, SendMediaGroupRequest -> Maybe Bool
sendMediaGroupProtectContent :: Maybe Bool
, SendMediaGroupRequest -> Maybe MessageId
sendMediaGroupReplyToMessageId :: Maybe MessageId
, SendMediaGroupRequest -> Maybe Bool
sendMediaGroupAllowSendingWithoutReply :: Maybe Bool
, SendMediaGroupRequest -> Maybe InlineKeyboardMarkup
sendMediaGroupReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x. SendMediaGroupRequest -> Rep SendMediaGroupRequest x)
-> (forall x. Rep SendMediaGroupRequest x -> SendMediaGroupRequest)
-> Generic SendMediaGroupRequest
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 = SendMediaGroupRequest -> Value
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])
sendMediaGroup :: SendMediaGroupRequest -> ClientM (Response [Message])
sendMediaGroup :: SendMediaGroupRequest -> ClientM (Response [Message])
sendMediaGroup = Proxy SendMediaGroup -> Client ClientM SendMediaGroup
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendMediaGroup
forall k (t :: k). Proxy t
Proxy @SendMediaGroup)
data SendLocationRequest = SendLocationRequest
{ SendLocationRequest -> SomeChatId
sendLocationChatId :: SomeChatId
, SendLocationRequest -> Float
sendLocationLatitude :: Float
, SendLocationRequest -> Float
sendLocationLongitude :: Float
, SendLocationRequest -> Maybe Float
sendLocationHorizontalAccuracy :: Maybe Float
, SendLocationRequest -> Int
sendLocationLivePeriod :: Int
, SendLocationRequest -> Maybe Int
sendLocationHeading :: Maybe Int
, SendLocationRequest -> Maybe Int
sendLocationProximityAlertRadius :: Maybe Int
, SendLocationRequest -> Maybe Bool
sendLocationDisableNotification :: Maybe Bool
, SendLocationRequest -> Maybe Bool
sendLocationProtectContent :: Maybe Bool
, SendLocationRequest -> Maybe MessageId
sendLocationReplyToMessageId :: Maybe MessageId
, SendLocationRequest -> Maybe Bool
sendLocationAllowSendingWithoutReply :: Maybe Bool
, SendLocationRequest -> Maybe InlineKeyboardMarkup
sendLocationReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x. SendLocationRequest -> Rep SendLocationRequest x)
-> (forall x. Rep SendLocationRequest x -> SendLocationRequest)
-> Generic SendLocationRequest
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
data EditMessageLiveLocationRequest = EditMessageLiveLocationRequest
{ EditMessageLiveLocationRequest -> Maybe SomeChatId
editMessageLiveLocationChatId :: Maybe SomeChatId
, EditMessageLiveLocationRequest -> Maybe MessageId
editMessageLiveLocationMessageId :: Maybe MessageId
, EditMessageLiveLocationRequest -> Maybe Text
editMessageLiveLocationInlineMessageId :: Maybe Text
, EditMessageLiveLocationRequest -> Float
editMessageLiveLocationLatitude :: Float
, EditMessageLiveLocationRequest -> Float
editMessageLiveLocationLongitude :: Float
, EditMessageLiveLocationRequest -> Maybe Float
editMessageLiveLocationHorizontalAccuracy :: Maybe Float
, EditMessageLiveLocationRequest -> Maybe Int
editMessageLiveLocationHeading :: Maybe Int
, EditMessageLiveLocationRequest -> Maybe Int
editMessageLiveLocationProximityAlertRadius :: Maybe Int
, EditMessageLiveLocationRequest -> Maybe InlineKeyboardMarkup
editMessageLiveLocationReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x.
EditMessageLiveLocationRequest
-> Rep EditMessageLiveLocationRequest x)
-> (forall x.
Rep EditMessageLiveLocationRequest x
-> EditMessageLiveLocationRequest)
-> Generic EditMessageLiveLocationRequest
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
data StopMessageLiveLocationRequest = StopMessageLiveLocationRequest
{ StopMessageLiveLocationRequest -> Maybe SomeChatId
stopMessageLiveLocationChatId :: Maybe SomeChatId
, StopMessageLiveLocationRequest -> Maybe MessageId
stopMessageLiveLocationMessageId :: Maybe MessageId
, StopMessageLiveLocationRequest -> Maybe Text
stopMessageLiveLocationInlineMessageId :: Maybe Text
, StopMessageLiveLocationRequest -> Maybe InlineKeyboardMarkup
stopMessageLiveLocationReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x.
StopMessageLiveLocationRequest
-> Rep StopMessageLiveLocationRequest x)
-> (forall x.
Rep StopMessageLiveLocationRequest x
-> StopMessageLiveLocationRequest)
-> Generic StopMessageLiveLocationRequest
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
data SendVenueRequest = SendVenueRequest
{ SendVenueRequest -> SomeChatId
sendVenueChatId :: SomeChatId
, SendVenueRequest -> Float
sendVenueLatitude :: Float
, SendVenueRequest -> Float
sendVenueLongitude :: Float
, SendVenueRequest -> Text
sendVenueTitle :: Text
, SendVenueRequest -> Text
sendVenueAddress :: Text
, SendVenueRequest -> Maybe Text
sendVenueFoursquareId :: Maybe Text
, SendVenueRequest -> Maybe Text
sendVenueFoursquareType :: Maybe Text
, SendVenueRequest -> Maybe Text
sendVenueGooglePlaceId :: Maybe Text
, SendVenueRequest -> Maybe Text
sendVenueGooglePlaceType :: Maybe Text
, SendVenueRequest -> Maybe Bool
sendVenueDisableNotification :: Maybe Bool
, SendVenueRequest -> Maybe Bool
sendVenueProtectContent :: Maybe Bool
, SendVenueRequest -> Maybe MessageId
sendVenueReplyToMessageId :: Maybe MessageId
, SendVenueRequest -> Maybe Bool
sendVenueAllowSendingWithoutReply :: Maybe Bool
, SendVenueRequest -> Maybe InlineKeyboardMarkup
sendVenueReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x. SendVenueRequest -> Rep SendVenueRequest x)
-> (forall x. Rep SendVenueRequest x -> SendVenueRequest)
-> Generic SendVenueRequest
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
data SendContactRequest = SendContactRequest
{ SendContactRequest -> SomeChatId
sendContactChatId :: SomeChatId
, SendContactRequest -> Text
sendContactPhoneNumber :: Text
, SendContactRequest -> Text
sendContactFirstName :: Text
, SendContactRequest -> Text
sendContactLastName :: Text
, SendContactRequest -> Text
sendContactVcard :: Text
, SendContactRequest -> Maybe Bool
sendContactDisableNotification :: Maybe Bool
, SendContactRequest -> Maybe Bool
sendContactProtectContent :: Maybe Bool
, SendContactRequest -> Maybe MessageId
sendContactReplyToMessageId :: Maybe MessageId
, SendContactRequest -> Maybe Bool
sendContactAllowSendingWithoutReply :: Maybe Bool
, SendContactRequest -> Maybe InlineKeyboardMarkup
sendContactReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x. SendContactRequest -> Rep SendContactRequest x)
-> (forall x. Rep SendContactRequest x -> SendContactRequest)
-> Generic SendContactRequest
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
data SendPollRequest = SendPollRequest
{ SendPollRequest -> SomeChatId
sendPollChatId :: SomeChatId
, SendPollRequest -> Text
sendPollQuestion :: Text
, SendPollRequest -> [Text]
sendPollOptions :: [Text]
, SendPollRequest -> Maybe Bool
sendPollIsAnonymous :: Maybe Bool
, SendPollRequest -> Maybe Text
sendPollType :: Maybe Text
, SendPollRequest -> Maybe Bool
sendPollAllowsMultipleAnswers :: Maybe Bool
, SendPollRequest -> Maybe Int
sendPollCorrectOptionId :: Maybe Int
, SendPollRequest -> Maybe Text
sendPollExplanation :: Maybe Text
, SendPollRequest -> Maybe ParseMode
sendPollExplanationParseMode :: Maybe ParseMode
, SendPollRequest -> Maybe [MessageEntity]
sendPollExplanationEntities :: Maybe [MessageEntity]
, SendPollRequest -> Maybe Int
sendPollOpenPeriod :: Maybe Int
, SendPollRequest -> Maybe Int
sendPollCloseDate :: Maybe Int
, SendPollRequest -> Maybe Bool
sendPollIsClosed :: Maybe Bool
, SendPollRequest -> Maybe Bool
sendPollDisableNotification :: Maybe Bool
, SendPollRequest -> Maybe Bool
sendPollProtectContent :: Maybe Bool
, SendPollRequest -> Maybe MessageId
sendPollReplyToMessageId :: Maybe MessageId
, SendPollRequest -> Maybe Bool
sendPollAllowSendingWithoutReply :: Maybe Bool
, SendPollRequest -> Maybe InlineKeyboardMarkup
sendPollReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x. SendPollRequest -> Rep SendPollRequest x)
-> (forall x. Rep SendPollRequest x -> SendPollRequest)
-> Generic SendPollRequest
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
data SendDiceRequest = SendDiceRequest
{ SendDiceRequest -> SomeChatId
sendDiceChatId :: SomeChatId
, SendDiceRequest -> Maybe Text
sendDiceEmoji :: Maybe Text
, SendDiceRequest -> Maybe Bool
sendDiceDisableNotification :: Maybe Bool
, SendDiceRequest -> Maybe Bool
sendDiceProtectContent :: Maybe Bool
, SendDiceRequest -> Maybe MessageId
sendDiceReplyToMessageId :: Maybe MessageId
, SendDiceRequest -> Maybe Bool
sendDiceAllowSendingWithoutReply :: Maybe Bool
, SendDiceRequest -> Maybe InlineKeyboardMarkup
sendDiceReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x. SendDiceRequest -> Rep SendDiceRequest x)
-> (forall x. Rep SendDiceRequest x -> SendDiceRequest)
-> Generic SendDiceRequest
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)
sendChatAction :: SomeChatId
-> Text
-> ClientM (Response Bool)
sendChatAction :: SomeChatId -> Text -> ClientM (Response Bool)
sendChatAction = Proxy SendChatAction -> Client ClientM SendChatAction
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendChatAction
forall k (t :: k). Proxy t
Proxy @SendChatAction)
data GetUserProfilePhotosRequest = GetUserProfilePhotosRequest
{ GetUserProfilePhotosRequest -> UserId
getUserProfilePhotosUserId :: UserId
, GetUserProfilePhotosRequest -> Maybe Int
getUserProfilePhotosOffset :: Maybe Int
, GetUserProfilePhotosRequest -> Maybe Int
getUserProfilePhotosLimit :: Maybe Int
}
deriving (forall x.
GetUserProfilePhotosRequest -> Rep GetUserProfilePhotosRequest x)
-> (forall x.
Rep GetUserProfilePhotosRequest x -> GetUserProfilePhotosRequest)
-> Generic GetUserProfilePhotosRequest
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
data BanChatMemberRequest = BanChatMemberRequest
{ BanChatMemberRequest -> SomeChatId
banChatMemberChatId :: SomeChatId
, BanChatMemberRequest -> UserId
banChatMemberUserId :: UserId
, BanChatMemberRequest -> Maybe Int
banChatMemberUntilDate :: Maybe Int
, BanChatMemberRequest -> Maybe Bool
banChatMemberRevokeMessages :: Maybe Bool
}
deriving (forall x. BanChatMemberRequest -> Rep BanChatMemberRequest x)
-> (forall x. Rep BanChatMemberRequest x -> BanChatMemberRequest)
-> Generic BanChatMemberRequest
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
data UnbanChatMemberRequest = UnbanChatMemberRequest
{ UnbanChatMemberRequest -> SomeChatId
unbanChatMemberChatId :: SomeChatId
, UnbanChatMemberRequest -> UserId
unbanChatMemberUserId :: UserId
, UnbanChatMemberRequest -> Maybe Bool
unbanChatMemberOnlyIfBanned :: Maybe Bool
}
deriving (forall x. UnbanChatMemberRequest -> Rep UnbanChatMemberRequest x)
-> (forall x.
Rep UnbanChatMemberRequest x -> UnbanChatMemberRequest)
-> Generic UnbanChatMemberRequest
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
data RestrictChatMemberRequest = RestrictChatMemberRequest
{ RestrictChatMemberRequest -> SomeChatId
restrictChatMemberChatId :: SomeChatId
, RestrictChatMemberRequest -> UserId
restrictChatMemberUserId :: UserId
, RestrictChatMemberRequest -> ChatPermissions
restrictChatMemberPermissions :: ChatPermissions
, RestrictChatMemberRequest -> Maybe Int
restrictChatMemberUntilDate :: Maybe Int
}
deriving (forall x.
RestrictChatMemberRequest -> Rep RestrictChatMemberRequest x)
-> (forall x.
Rep RestrictChatMemberRequest x -> RestrictChatMemberRequest)
-> Generic RestrictChatMemberRequest
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
data PromoteChatMemberRequest = PromoteChatMemberRequest
{ PromoteChatMemberRequest -> SomeChatId
promoteChatMemberChatId :: SomeChatId
, PromoteChatMemberRequest -> UserId
promoteChatMemberUserId :: UserId
, PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberIsAnonymous :: Maybe Bool
, PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanManageChat :: Maybe Bool
, PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanPostMessages :: Maybe Bool
, PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanEditMessages :: Maybe Bool
, PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanDeleteMessages :: Maybe Bool
, PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanManageVideoChats :: Maybe Bool
, PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanRestrictMembers :: Maybe Bool
, PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanPromoteMembers :: Maybe Bool
, PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanChangeInfo :: Maybe Bool
, PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanInviteUsers :: Maybe Bool
, PromoteChatMemberRequest -> Maybe Bool
promoteChatMemberCanPinMessages :: Maybe Bool
}
deriving (forall x.
PromoteChatMemberRequest -> Rep PromoteChatMemberRequest x)
-> (forall x.
Rep PromoteChatMemberRequest x -> PromoteChatMemberRequest)
-> Generic PromoteChatMemberRequest
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
data SetChatAdministratorCustomTitleRequest = SetChatAdministratorCustomTitleRequest
{ SetChatAdministratorCustomTitleRequest -> SomeChatId
setChatAdministratorCustomTitleChatId :: SomeChatId
, SetChatAdministratorCustomTitleRequest -> UserId
setChatAdministratorCustomTitleUserId :: UserId
, SetChatAdministratorCustomTitleRequest -> Text
setChatAdministratorCustomTitleCustomTitle :: Text
}
deriving (forall x.
SetChatAdministratorCustomTitleRequest
-> Rep SetChatAdministratorCustomTitleRequest x)
-> (forall x.
Rep SetChatAdministratorCustomTitleRequest x
-> SetChatAdministratorCustomTitleRequest)
-> Generic SetChatAdministratorCustomTitleRequest
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)
banChatSenderChat :: SomeChatId
-> ChatId
-> ClientM (Response Bool)
banChatSenderChat :: SomeChatId -> ChatId -> ClientM (Response Bool)
banChatSenderChat = Proxy BanChatSenderChat -> Client ClientM BanChatSenderChat
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy BanChatSenderChat
forall k (t :: k). Proxy t
Proxy @BanChatSenderChat)
type UnbanChatSenderChat = "unbanChatSenderChat"
:> RequiredQueryParam "chat_id" SomeChatId
:> RequiredQueryParam "sender_chat_id" ChatId
:> Post '[JSON] (Response Bool)
unbanChatSenderChat :: SomeChatId
-> ChatId
-> ClientM (Response Bool)
unbanChatSenderChat :: SomeChatId -> ChatId -> ClientM (Response Bool)
unbanChatSenderChat = Proxy UnbanChatSenderChat -> Client ClientM UnbanChatSenderChat
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy UnbanChatSenderChat
forall k (t :: k). Proxy t
Proxy @UnbanChatSenderChat)
data SetChatPermissionsRequest = SetChatPermissionsRequest
{ SetChatPermissionsRequest -> SomeChatId
setChatPermissionsChatId :: SomeChatId
, SetChatPermissionsRequest -> ChatPermissions
setChatPermissionsPermissions :: ChatPermissions
}
deriving (forall x.
SetChatPermissionsRequest -> Rep SetChatPermissionsRequest x)
-> (forall x.
Rep SetChatPermissionsRequest x -> SetChatPermissionsRequest)
-> Generic SetChatPermissionsRequest
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)
exportChatInviteLink :: SomeChatId
-> ClientM (Response Text)
exportChatInviteLink :: SomeChatId -> ClientM (Response Text)
exportChatInviteLink = Proxy ExportChatInviteLink -> Client ClientM ExportChatInviteLink
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy ExportChatInviteLink
forall k (t :: k). Proxy t
Proxy @ExportChatInviteLink)
data CreateChatInviteLinkRequest = CreateChatInviteLinkRequest
{ CreateChatInviteLinkRequest -> SomeChatId
createChatInviteLinkChatId :: SomeChatId
, CreateChatInviteLinkRequest -> Maybe Text
createChatInviteLinkName :: Maybe Text
, CreateChatInviteLinkRequest -> Maybe Integer
createChatInviteLinkExpireDate :: Maybe Integer
, CreateChatInviteLinkRequest -> Maybe Int
createChatInviteLinkMemberLimit :: Maybe Int
, CreateChatInviteLinkRequest -> Maybe Bool
createChatInviteLinkCreatesJoinRequest :: Maybe Bool
}
deriving (forall x.
CreateChatInviteLinkRequest -> Rep CreateChatInviteLinkRequest x)
-> (forall x.
Rep CreateChatInviteLinkRequest x -> CreateChatInviteLinkRequest)
-> Generic CreateChatInviteLinkRequest
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
data EditChatInviteLinkRequest = EditChatInviteLinkRequest
{ EditChatInviteLinkRequest -> SomeChatId
editChatInviteLinkChatId :: SomeChatId
, EditChatInviteLinkRequest -> Text
editChatInviteLinkInviteLink :: Text
, EditChatInviteLinkRequest -> Maybe Text
editChatInviteLinkName :: Maybe Text
, EditChatInviteLinkRequest -> Maybe Integer
editChatInviteLinkExpireDate :: Maybe Integer
, EditChatInviteLinkRequest -> Maybe Int
editChatInviteLinkMemberLimit :: Maybe Int
, EditChatInviteLinkRequest -> Maybe Bool
editChatInviteLinkCreatesJoinRequest :: Maybe Bool
}
deriving (forall x.
EditChatInviteLinkRequest -> Rep EditChatInviteLinkRequest x)
-> (forall x.
Rep EditChatInviteLinkRequest x -> EditChatInviteLinkRequest)
-> Generic EditChatInviteLinkRequest
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)
revokeChatInviteLink :: SomeChatId
-> Text
-> ClientM (Response ChatInviteLink)
revokeChatInviteLink :: SomeChatId -> Text -> ClientM (Response ChatInviteLink)
revokeChatInviteLink = Proxy RevokeChatInviteLink -> Client ClientM RevokeChatInviteLink
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy RevokeChatInviteLink
forall k (t :: k). Proxy t
Proxy @RevokeChatInviteLink)
type ApproveChatJoinRequest = "approveChatJoinRequest"
:> RequiredQueryParam "chat_id" SomeChatId
:> RequiredQueryParam "user_id" UserId
:> Post '[JSON] (Response Bool)
approveChatJoinRequest :: SomeChatId
-> UserId
-> ClientM (Response Bool)
approveChatJoinRequest :: SomeChatId -> UserId -> ClientM (Response Bool)
approveChatJoinRequest = Proxy ApproveChatJoinRequest
-> Client ClientM ApproveChatJoinRequest
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy ApproveChatJoinRequest
forall k (t :: k). Proxy t
Proxy @ApproveChatJoinRequest)
type DeclineChatJoinRequest = "declineChatJoinRequest"
:> RequiredQueryParam "chat_id" SomeChatId
:> RequiredQueryParam "user_id" UserId
:> Post '[JSON] (Response Bool)
declineChatJoinRequest :: SomeChatId
-> UserId
-> ClientM (Response Bool)
declineChatJoinRequest :: SomeChatId -> UserId -> ClientM (Response Bool)
declineChatJoinRequest = Proxy DeclineChatJoinRequest
-> Client ClientM DeclineChatJoinRequest
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy DeclineChatJoinRequest
forall k (t :: k). Proxy t
Proxy @DeclineChatJoinRequest)
data SetChatPhotoRequest = SetChatPhotoRequest
{ SetChatPhotoRequest -> SomeChatId
setChatPhotoChatId :: SomeChatId
, SetChatPhotoRequest -> InputFile
setChatPhotoPhoto :: InputFile
}
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 ([Input] -> [FileData Tmp] -> MultipartData Tmp
forall tag. [Input] -> [FileData tag] -> MultipartData tag
MultipartData [Input]
fields []) where
fields :: [Input]
fields =
[ Text -> Text -> Input
Input Text
"chat_id" (Text -> Input) -> Text -> Input
forall a b. (a -> b) -> a -> b
$ case SomeChatId
setChatPhotoChatId of
SomeChatId (ChatId Integer
chat_id) -> FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ Integer -> FilePath
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)
setChatPhoto :: SetChatPhotoRequest -> ClientM (Response Bool)
setChatPhoto :: SetChatPhotoRequest -> ClientM (Response Bool)
setChatPhoto SetChatPhotoRequest
r =do
ByteString
boundary <- IO ByteString -> ClientM ByteString
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO ByteString
genBoundary
Proxy SetChatPhoto
-> (ByteString, SetChatPhotoRequest) -> ClientM (Response Bool)
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SetChatPhoto
forall k (t :: k). Proxy t
Proxy @SetChatPhoto) (ByteString
boundary, SetChatPhotoRequest
r)
type DeleteChatPhoto = "deleteChatPhoto"
:> RequiredQueryParam "chat_id" SomeChatId
:> Post '[JSON] (Response Bool)
deleteChatPhoto :: SomeChatId
-> ClientM (Response Bool)
deleteChatPhoto :: SomeChatId -> ClientM (Response Bool)
deleteChatPhoto = Proxy DeleteChatPhoto -> Client ClientM DeleteChatPhoto
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy DeleteChatPhoto
forall k (t :: k). Proxy t
Proxy @DeleteChatPhoto)
type SetChatTitle = "setChatTitle"
:> RequiredQueryParam "chat_id" SomeChatId
:> RequiredQueryParam "title" Text
:> Post '[JSON] (Response Bool)
setChatTitle :: SomeChatId
-> Text
-> ClientM (Response Bool)
setChatTitle :: SomeChatId -> Text -> ClientM (Response Bool)
setChatTitle = Proxy SetChatTitle -> Client ClientM SetChatTitle
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SetChatTitle
forall k (t :: k). Proxy t
Proxy @SetChatTitle)
type SetChatDescription = "setChatDescription"
:> RequiredQueryParam "chat_id" SomeChatId
:> QueryParam "description" Text
:> Post '[JSON] (Response Bool)
setChatDescription :: SomeChatId
-> Maybe Text
-> ClientM (Response Bool)
setChatDescription :: SomeChatId -> Maybe Text -> ClientM (Response Bool)
setChatDescription = Proxy SetChatDescription -> Client ClientM SetChatDescription
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SetChatDescription
forall k (t :: k). Proxy t
Proxy @SetChatDescription)
data PinChatMessageRequest = PinChatMessageRequest
{ PinChatMessageRequest -> SomeChatId
pinChatMessageChatId :: SomeChatId
, PinChatMessageRequest -> MessageId
pinChatMessageMessageId :: MessageId
, PinChatMessageRequest -> Maybe Bool
pinChatMessageDisableNotification :: Maybe Bool
}
deriving (forall x. PinChatMessageRequest -> Rep PinChatMessageRequest x)
-> (forall x. Rep PinChatMessageRequest x -> PinChatMessageRequest)
-> Generic PinChatMessageRequest
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)
unpinChatMessage :: SomeChatId
-> Maybe MessageId
-> ClientM (Response Bool)
unpinChatMessage :: SomeChatId -> Maybe MessageId -> ClientM (Response Bool)
unpinChatMessage = Proxy UnpinChatMessage -> Client ClientM UnpinChatMessage
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy UnpinChatMessage
forall k (t :: k). Proxy t
Proxy @UnpinChatMessage)
type UnpinAllChatMessages = "unpinAllChatMessages"
:> RequiredQueryParam "chat_id" SomeChatId
:> Post '[JSON] (Response Bool)
unpinAllChatMessages :: SomeChatId
-> ClientM (Response Bool)
unpinAllChatMessages :: SomeChatId -> ClientM (Response Bool)
unpinAllChatMessages = Proxy UnpinAllChatMessages -> Client ClientM UnpinAllChatMessages
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy UnpinAllChatMessages
forall k (t :: k). Proxy t
Proxy @UnpinAllChatMessages)
type LeaveChat = "leaveChat"
:> RequiredQueryParam "chat_id" SomeChatId
:> Post '[JSON] (Response Bool)
leaveChat :: SomeChatId
-> ClientM (Response Bool)
leaveChat :: SomeChatId -> ClientM (Response Bool)
leaveChat = Proxy LeaveChat -> Client ClientM LeaveChat
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy LeaveChat
forall k (t :: k). Proxy t
Proxy @LeaveChat)
type GetChat = "getChat"
:> RequiredQueryParam "chat_id" SomeChatId
:> Post '[JSON] (Response Chat)
getChat :: SomeChatId
-> ClientM (Response Chat)
getChat :: SomeChatId -> ClientM (Response Chat)
getChat = Proxy GetChat -> Client ClientM GetChat
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy GetChat
forall k (t :: k). Proxy t
Proxy @GetChat)
type GetChatAdministrators = "getChatAdministrators"
:> RequiredQueryParam "chat_id" SomeChatId
:> Post '[JSON] (Response [ChatMember])
getChatAdministrators :: SomeChatId
-> ClientM (Response [ChatMember])
getChatAdministrators :: SomeChatId -> ClientM (Response [ChatMember])
getChatAdministrators = Proxy GetChatAdministrators -> Client ClientM GetChatAdministrators
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy GetChatAdministrators
forall k (t :: k). Proxy t
Proxy @GetChatAdministrators)
type GetChatMemberCount = "getChatMemberCount"
:> RequiredQueryParam "chat_id" SomeChatId
:> Post '[JSON] (Response Integer)
getChatMemberCount :: SomeChatId
-> ClientM (Response Integer)
getChatMemberCount :: SomeChatId -> ClientM (Response Integer)
getChatMemberCount = Proxy GetChatMemberCount -> Client ClientM GetChatMemberCount
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy GetChatMemberCount
forall k (t :: k). Proxy t
Proxy @GetChatMemberCount)
type GetChatMember = "getChatMember"
:> RequiredQueryParam "chat_id" SomeChatId
:> RequiredQueryParam "user_id" UserId
:> Post '[JSON] (Response ChatMember)
getChatMember :: SomeChatId
-> UserId
-> ClientM (Response ChatMember)
getChatMember :: SomeChatId -> UserId -> ClientM (Response ChatMember)
getChatMember = Proxy GetChatMember -> Client ClientM GetChatMember
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy GetChatMember
forall k (t :: k). Proxy t
Proxy @GetChatMember)
type SetChatStickerSet = "setChatStickerSet"
:> RequiredQueryParam "chat_id" SomeChatId
:> RequiredQueryParam "sticker_set_name" Text
:> Post '[JSON] (Response Bool)
setChatStickerSet :: SomeChatId
-> Text
-> ClientM (Response Bool)
setChatStickerSet :: SomeChatId -> Text -> ClientM (Response Bool)
setChatStickerSet = Proxy SetChatStickerSet -> Client ClientM SetChatStickerSet
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SetChatStickerSet
forall k (t :: k). Proxy t
Proxy @SetChatStickerSet)
type DeleteChatStickerSet = "deleteChatStickerSet"
:> RequiredQueryParam "chat_id" SomeChatId
:> Post '[JSON] (Response Bool)
deleteChatStickerSet :: SomeChatId
-> ClientM (Response Bool)
deleteChatStickerSet :: SomeChatId -> ClientM (Response Bool)
deleteChatStickerSet = Proxy DeleteChatStickerSet -> Client ClientM DeleteChatStickerSet
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy DeleteChatStickerSet
forall k (t :: k). Proxy t
Proxy @DeleteChatStickerSet)
data AnswerCallbackQueryRequest = AnswerCallbackQueryRequest
{ AnswerCallbackQueryRequest -> CallbackQueryId
answerCallbackQueryCallbackQueryId :: CallbackQueryId
, AnswerCallbackQueryRequest -> Maybe Text
answerCallbackQueryText :: Maybe Text
, AnswerCallbackQueryRequest -> Maybe Bool
answerCallbackQueryShowAlert :: Maybe Bool
, AnswerCallbackQueryRequest -> Maybe Text
answerCallbackQueryUrl :: Maybe Text
, AnswerCallbackQueryRequest -> Maybe Integer
answerCallbackQueryCacheTime :: Maybe Integer
}
deriving (forall x.
AnswerCallbackQueryRequest -> Rep AnswerCallbackQueryRequest x)
-> (forall x.
Rep AnswerCallbackQueryRequest x -> AnswerCallbackQueryRequest)
-> Generic AnswerCallbackQueryRequest
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
data SetMyCommandsRequest = SetMyCommandsRequest
{ SetMyCommandsRequest -> [BotCommand]
setMyCommandsCommands :: [BotCommand]
, SetMyCommandsRequest -> Maybe BotCommandScope
setMyCommandsScope :: Maybe BotCommandScope
, SetMyCommandsRequest -> Maybe Text
setMyCommandsLanguageCode :: Maybe Text
}
deriving (forall x. SetMyCommandsRequest -> Rep SetMyCommandsRequest x)
-> (forall x. Rep SetMyCommandsRequest x -> SetMyCommandsRequest)
-> Generic SetMyCommandsRequest
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
data DeleteMyCommandsRequest = DeleteMyCommandsRequest
{ DeleteMyCommandsRequest -> Maybe BotCommandScope
deleteMyCommandsScope :: Maybe BotCommandScope
, DeleteMyCommandsRequest -> Maybe Text
deleteMyCommandsLanguageCode :: Maybe Text
}
deriving (forall x.
DeleteMyCommandsRequest -> Rep DeleteMyCommandsRequest x)
-> (forall x.
Rep DeleteMyCommandsRequest x -> DeleteMyCommandsRequest)
-> Generic DeleteMyCommandsRequest
forall x. Rep DeleteMyCommandsRequest x -> DeleteMyCommandsRequest
forall x. DeleteMyCommandsRequest -> Rep DeleteMyCommandsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteMyCommandsRequest x -> DeleteMyCommandsRequest
$cfrom :: forall x. DeleteMyCommandsRequest -> Rep DeleteMyCommandsRequest x
Generic
data GetMyCommandsRequest = GetMyCommandsRequest
{ GetMyCommandsRequest -> Maybe BotCommandScope
getMyCommandsScope :: Maybe BotCommandScope
, GetMyCommandsRequest -> Maybe Text
getMyCommandsLanguageCode :: Maybe Text
}
deriving (forall x. GetMyCommandsRequest -> Rep GetMyCommandsRequest x)
-> (forall x. Rep GetMyCommandsRequest x -> GetMyCommandsRequest)
-> Generic GetMyCommandsRequest
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
data =
{ :: Maybe ChatId
, :: Maybe MenuButton
}
deriving (forall x.
SetChatMenuButtonRequest -> Rep SetChatMenuButtonRequest x)
-> (forall x.
Rep SetChatMenuButtonRequest x -> SetChatMenuButtonRequest)
-> Generic SetChatMenuButtonRequest
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
data =
{ :: Maybe ChatId
}
deriving (forall x.
GetChatMenuButtonRequest -> Rep GetChatMenuButtonRequest x)
-> (forall x.
Rep GetChatMenuButtonRequest x -> GetChatMenuButtonRequest)
-> Generic GetChatMenuButtonRequest
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
data SetMyDefaultAdministratorRightsRequest = SetMyDefaultAdministratorRightsRequest
{ SetMyDefaultAdministratorRightsRequest
-> Maybe ChatAdministratorRights
setMyDefaultAdministratorRightsRequestRights :: Maybe ChatAdministratorRights
, SetMyDefaultAdministratorRightsRequest -> Maybe Bool
setMyDefaultAdministratorRightsRequestForChannels :: Maybe Bool
}
deriving (forall x.
SetMyDefaultAdministratorRightsRequest
-> Rep SetMyDefaultAdministratorRightsRequest x)
-> (forall x.
Rep SetMyDefaultAdministratorRightsRequest x
-> SetMyDefaultAdministratorRightsRequest)
-> Generic SetMyDefaultAdministratorRightsRequest
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
data GetMyDefaultAdministratorRightsRequest = GetMyDefaultAdministratorRightsRequest
{ GetMyDefaultAdministratorRightsRequest -> Maybe Bool
getMyDefaultAdministratorRightsRequestForChannels :: Maybe Bool
}
deriving (forall x.
GetMyDefaultAdministratorRightsRequest
-> Rep GetMyDefaultAdministratorRightsRequest x)
-> (forall x.
Rep GetMyDefaultAdministratorRightsRequest x
-> GetMyDefaultAdministratorRightsRequest)
-> Generic GetMyDefaultAdministratorRightsRequest
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)
copyMessage :: CopyMessageRequest -> ClientM (Response CopyMessageId)
copyMessage :: CopyMessageRequest -> ClientM (Response CopyMessageId)
copyMessage = Proxy CopyMessage -> Client ClientM CopyMessage
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy CopyMessage
forall k (t :: k). Proxy t
Proxy @CopyMessage)
type SendLocation = "sendLocation"
:> ReqBody '[JSON] SendLocationRequest
:> Post '[JSON] (Response Message)
sendLocation :: SendLocationRequest -> ClientM (Response Message)
sendLocation :: SendLocationRequest -> ClientM (Response Message)
sendLocation = Proxy SendLocation -> Client ClientM SendLocation
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendLocation
forall k (t :: k). Proxy t
Proxy @SendLocation)
type EditMessageLiveLocation = "editMessageLiveLocation"
:> ReqBody '[JSON] EditMessageLiveLocationRequest
:> Post '[JSON] (Response (Either Bool Message))
editMessageLiveLocation :: EditMessageLiveLocationRequest -> ClientM (Response (Either Bool Message))
editMessageLiveLocation :: EditMessageLiveLocationRequest
-> ClientM (Response (Either Bool Message))
editMessageLiveLocation = Proxy EditMessageLiveLocation
-> Client ClientM EditMessageLiveLocation
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy EditMessageLiveLocation
forall k (t :: k). Proxy t
Proxy @EditMessageLiveLocation)
type StopMessageLiveLocation = "stopMessageLiveLocation"
:> ReqBody '[JSON] StopMessageLiveLocationRequest
:> Post '[JSON] (Response (Either Bool Message))
stopMessageLiveLocation :: StopMessageLiveLocationRequest -> ClientM (Response (Either Bool Message))
stopMessageLiveLocation :: StopMessageLiveLocationRequest
-> ClientM (Response (Either Bool Message))
stopMessageLiveLocation = Proxy StopMessageLiveLocation
-> Client ClientM StopMessageLiveLocation
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy StopMessageLiveLocation
forall k (t :: k). Proxy t
Proxy @StopMessageLiveLocation)
type SendVenue = "sendVenue"
:> ReqBody '[JSON] SendVenueRequest
:> Post '[JSON] (Response Message)
sendVenue :: SendVenueRequest -> ClientM (Response Message)
sendVenue :: SendVenueRequest -> ClientM (Response Message)
sendVenue = Proxy SendVenue -> Client ClientM SendVenue
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendVenue
forall k (t :: k). Proxy t
Proxy @SendVenue)
type SendContact = "sendContact"
:> ReqBody '[JSON] SendContactRequest
:> Post '[JSON] (Response Message)
sendContact :: SendContactRequest -> ClientM (Response Message)
sendContact :: SendContactRequest -> ClientM (Response Message)
sendContact = Proxy SendContact -> Client ClientM SendContact
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendContact
forall k (t :: k). Proxy t
Proxy @SendContact)
type SendPoll = "sendPoll"
:> ReqBody '[JSON] SendPollRequest
:> Post '[JSON] (Response Message)
sendPoll :: SendPollRequest -> ClientM (Response Message)
sendPoll :: SendPollRequest -> ClientM (Response Message)
sendPoll = Proxy SendPoll -> Client ClientM SendPoll
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendPoll
forall k (t :: k). Proxy t
Proxy @SendPoll)
type SendDice = "sendDice"
:> ReqBody '[JSON] SendDiceRequest
:> Post '[JSON] (Response Message)
sendDice :: SendDiceRequest -> ClientM (Response Message)
sendDice :: SendDiceRequest -> ClientM (Response Message)
sendDice = Proxy SendDice -> Client ClientM SendDice
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SendDice
forall k (t :: k). Proxy t
Proxy @SendDice)
type GetUserProfilePhotos = "getUserProfilePhotos"
:> ReqBody '[JSON] GetUserProfilePhotosRequest
:> Post '[JSON] (Response UserProfilePhotos)
getUserProfilePhotos :: GetUserProfilePhotosRequest -> ClientM (Response UserProfilePhotos)
getUserProfilePhotos :: GetUserProfilePhotosRequest -> ClientM (Response UserProfilePhotos)
getUserProfilePhotos = Proxy GetUserProfilePhotos -> Client ClientM GetUserProfilePhotos
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy GetUserProfilePhotos
forall k (t :: k). Proxy t
Proxy @GetUserProfilePhotos)
type BanChatMember = "banChatMember"
:> ReqBody '[JSON] BanChatMemberRequest
:> Post '[JSON] (Response Bool)
banChatMember :: BanChatMemberRequest -> ClientM (Response Bool)
banChatMember :: BanChatMemberRequest -> ClientM (Response Bool)
banChatMember = Proxy BanChatMember -> Client ClientM BanChatMember
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy BanChatMember
forall k (t :: k). Proxy t
Proxy @BanChatMember)
type UnbanChatMember = "unbanChatMember"
:> ReqBody '[JSON] UnbanChatMemberRequest
:> Post '[JSON] (Response Bool)
unbanChatMember :: UnbanChatMemberRequest -> ClientM (Response Bool)
unbanChatMember :: UnbanChatMemberRequest -> ClientM (Response Bool)
unbanChatMember = Proxy UnbanChatMember -> Client ClientM UnbanChatMember
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy UnbanChatMember
forall k (t :: k). Proxy t
Proxy @UnbanChatMember)
type RestrictChatMember = "restrictChatMember"
:> ReqBody '[JSON] RestrictChatMemberRequest
:> Post '[JSON] (Response Bool)
restrictChatMember :: RestrictChatMemberRequest -> ClientM (Response Bool)
restrictChatMember :: RestrictChatMemberRequest -> ClientM (Response Bool)
restrictChatMember = Proxy RestrictChatMember -> Client ClientM RestrictChatMember
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy RestrictChatMember
forall k (t :: k). Proxy t
Proxy @RestrictChatMember)
type PromoteChatMember = "promoteChatMember"
:> ReqBody '[JSON] PromoteChatMemberRequest
:> Post '[JSON] (Response Bool)
promoteChatMember ::PromoteChatMemberRequest -> ClientM (Response Bool)
promoteChatMember :: PromoteChatMemberRequest -> ClientM (Response Bool)
promoteChatMember = Proxy PromoteChatMember -> Client ClientM PromoteChatMember
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy PromoteChatMember
forall k (t :: k). Proxy t
Proxy @PromoteChatMember)
type SetChatAdministratorCustomTitle = "setChatAdministratorCustomTitle"
:> ReqBody '[JSON] SetChatAdministratorCustomTitleRequest
:> Post '[JSON] (Response Bool)
setChatAdministratorCustomTitle :: SetChatAdministratorCustomTitleRequest -> ClientM (Response Bool)
setChatAdministratorCustomTitle :: SetChatAdministratorCustomTitleRequest -> ClientM (Response Bool)
setChatAdministratorCustomTitle = Proxy SetChatAdministratorCustomTitle
-> Client ClientM SetChatAdministratorCustomTitle
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SetChatAdministratorCustomTitle
forall k (t :: k). Proxy t
Proxy @SetChatAdministratorCustomTitle)
type SetChatPermissions = "setChatPermissions"
:> ReqBody '[JSON] SetChatPermissionsRequest
:> Post '[JSON] (Response Bool)
setChatPermissions :: SetChatPermissionsRequest -> ClientM (Response Bool)
setChatPermissions :: SetChatPermissionsRequest -> ClientM (Response Bool)
setChatPermissions = Proxy SetChatPermissions -> Client ClientM SetChatPermissions
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SetChatPermissions
forall k (t :: k). Proxy t
Proxy @SetChatPermissions)
type CreateChatInviteLink = "createChatInviteLink"
:> ReqBody '[JSON] CreateChatInviteLinkRequest
:> Post '[JSON] (Response ChatInviteLink)
createChatInviteLink :: CreateChatInviteLinkRequest -> ClientM (Response ChatInviteLink)
createChatInviteLink :: CreateChatInviteLinkRequest -> ClientM (Response ChatInviteLink)
createChatInviteLink = Proxy CreateChatInviteLink -> Client ClientM CreateChatInviteLink
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy CreateChatInviteLink
forall k (t :: k). Proxy t
Proxy @CreateChatInviteLink)
type EditChatInviteLink = "editChatInviteLink"
:> ReqBody '[JSON] EditChatInviteLinkRequest
:> Post '[JSON] (Response ChatInviteLink)
editChatInviteLink :: EditChatInviteLinkRequest -> ClientM (Response ChatInviteLink)
editChatInviteLink :: EditChatInviteLinkRequest -> ClientM (Response ChatInviteLink)
editChatInviteLink = Proxy EditChatInviteLink -> Client ClientM EditChatInviteLink
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy EditChatInviteLink
forall k (t :: k). Proxy t
Proxy @EditChatInviteLink)
type PinChatMessage = "pinChatMessage"
:> ReqBody '[JSON] PinChatMessageRequest
:> Post '[JSON] (Response Bool)
pinChatMessage :: PinChatMessageRequest -> ClientM (Response Bool)
pinChatMessage :: PinChatMessageRequest -> ClientM (Response Bool)
pinChatMessage = Proxy PinChatMessage -> Client ClientM PinChatMessage
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy PinChatMessage
forall k (t :: k). Proxy t
Proxy @PinChatMessage)
type AnswerCallbackQuery = "answerCallbackQuery"
:> ReqBody '[JSON] AnswerCallbackQueryRequest
:> Post '[JSON] (Response Bool)
answerCallbackQuery :: AnswerCallbackQueryRequest -> ClientM (Response Bool)
answerCallbackQuery :: AnswerCallbackQueryRequest -> ClientM (Response Bool)
answerCallbackQuery = Proxy AnswerCallbackQuery -> Client ClientM AnswerCallbackQuery
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy AnswerCallbackQuery
forall k (t :: k). Proxy t
Proxy @AnswerCallbackQuery)
type SetMyCommands = "setMyCommands"
:> ReqBody '[JSON] SetMyCommandsRequest
:> Post '[JSON] (Response Bool)
setMyCommands :: SetMyCommandsRequest -> ClientM (Response Bool)
setMyCommands :: SetMyCommandsRequest -> ClientM (Response Bool)
setMyCommands = Proxy SetMyCommands -> Client ClientM SetMyCommands
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SetMyCommands
forall k (t :: k). Proxy t
Proxy @SetMyCommands)
type DeleteMyCommands = "deleteMyCommands"
:> ReqBody '[JSON] DeleteMyCommandsRequest
:> Post '[JSON] (Response Bool)
deleteMyCommands :: DeleteMyCommandsRequest -> ClientM (Response Bool)
deleteMyCommands :: DeleteMyCommandsRequest -> ClientM (Response Bool)
deleteMyCommands = Proxy DeleteMyCommands -> Client ClientM DeleteMyCommands
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy DeleteMyCommands
forall k (t :: k). Proxy t
Proxy @DeleteMyCommands)
type GetMyCommands = "getMyCommands"
:> ReqBody '[JSON] GetMyCommandsRequest
:> Post '[JSON] (Response [BotCommand])
getMyCommands :: GetMyCommandsRequest -> ClientM (Response [BotCommand])
getMyCommands :: GetMyCommandsRequest -> ClientM (Response [BotCommand])
getMyCommands = Proxy GetMyCommands -> Client ClientM GetMyCommands
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy GetMyCommands
forall k (t :: k). Proxy t
Proxy @GetMyCommands)
type = "setChatMenuButton"
:> ReqBody '[JSON] SetChatMenuButtonRequest
:> Post '[JSON] (Response Bool)
setChatMenuButton :: SetChatMenuButtonRequest -> ClientM (Response Bool)
= Proxy SetChatMenuButton -> Client ClientM SetChatMenuButton
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SetChatMenuButton
forall k (t :: k). Proxy t
Proxy @SetChatMenuButton)
type = "getChatMenuButton"
:> ReqBody '[JSON] GetChatMenuButtonRequest
:> Post '[JSON] (Response MenuButton)
getChatMenuButton :: GetChatMenuButtonRequest -> ClientM (Response MenuButton)
= Proxy GetChatMenuButton -> Client ClientM GetChatMenuButton
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy GetChatMenuButton
forall k (t :: k). Proxy t
Proxy @GetChatMenuButton)
type SetMyDefaultAdministratorRights = "setMyDefaultAdministratorRights"
:> ReqBody '[JSON] SetMyDefaultAdministratorRightsRequest
:> Post '[JSON] (Response Bool)
setMyDefaultAdministratorRights
:: SetMyDefaultAdministratorRightsRequest -> ClientM (Response Bool)
setMyDefaultAdministratorRights :: SetMyDefaultAdministratorRightsRequest -> ClientM (Response Bool)
setMyDefaultAdministratorRights = Proxy SetMyDefaultAdministratorRights
-> Client ClientM SetMyDefaultAdministratorRights
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy SetMyDefaultAdministratorRights
forall k (t :: k). Proxy t
Proxy @SetMyDefaultAdministratorRights)
type GetMyDefaultAdministratorRights = "getMyDefaultAdministratorRights"
:> ReqBody '[JSON] GetMyDefaultAdministratorRightsRequest
:> Post '[JSON] (Response ChatAdministratorRights)
getMyDefaultAdministratorRights
:: GetMyDefaultAdministratorRightsRequest -> ClientM (Response ChatAdministratorRights)
getMyDefaultAdministratorRights :: GetMyDefaultAdministratorRightsRequest
-> ClientM (Response ChatAdministratorRights)
getMyDefaultAdministratorRights = Proxy GetMyDefaultAdministratorRights
-> Client ClientM GetMyDefaultAdministratorRights
forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (Proxy GetMyDefaultAdministratorRights
forall k (t :: k). Proxy t
Proxy @GetMyDefaultAdministratorRights)