telegram-bot-simple-0.6.1: Easy to use library for building Telegram bots.
Safe HaskellNone
LanguageHaskell2010

Telegram.Bot.API.Methods

Synopsis

Available methods

getMe

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

getMe :: ClientM (Response User) Source #

A simple method for testing your bot's auth token. Requires no parameters. Returns basic information about the bot in form of a User object.

deleteMessage

type DeleteMessage = "deleteMessage" :> (RequiredQueryParam "chat_id" ChatId :> (RequiredQueryParam "message_id" MessageId :> Get '[JSON] (Response Bool))) Source #

Notice that deleting by POST method was bugged, so we use GET

deleteMessage :: ChatId -> MessageId -> ClientM (Response Bool) Source #

Use this method to delete message in chat. On success, the sent Bool is returned.

sendMessage

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

sendMessage :: SendMessageRequest -> ClientM (Response Message) Source #

Use this method to send text messages. On success, the sent Message is returned.

forwardMessage

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

forwardMessage :: ForwardMessageRequest -> ClientM (Response Message) Source #

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

data SomeReplyMarkup Source #

Additional interface options. A JSON-serialized object for an inline keyboard, custom reply keyboard, instructions to remove reply keyboard or to force a reply from the user.

Instances

Instances details
Generic SomeReplyMarkup Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SomeReplyMarkup :: Type -> Type #

FromJSON SomeReplyMarkup Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser SomeReplyMarkup

parseJSONList :: Value -> Parser [SomeReplyMarkup]

ToJSON SomeReplyMarkup Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

toJSON :: SomeReplyMarkup -> Value

toEncoding :: SomeReplyMarkup -> Encoding

toJSONList :: [SomeReplyMarkup] -> Value

toEncodingList :: [SomeReplyMarkup] -> Encoding

type Rep SomeReplyMarkup Source # 
Instance details

Defined in Telegram.Bot.API.Methods

data ParseMode Source #

Constructors

Markdown 
HTML 
MarkdownV2 

Instances

Instances details
Generic ParseMode Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep ParseMode :: Type -> Type #

FromJSON ParseMode Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser ParseMode

parseJSONList :: Value -> Parser [ParseMode]

ToJSON ParseMode Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

toJSON :: ParseMode -> Value

toEncoding :: ParseMode -> Encoding

toJSONList :: [ParseMode] -> Value

toEncodingList :: [ParseMode] -> Encoding

type Rep ParseMode Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep ParseMode = D1 ('MetaData "ParseMode" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "Markdown" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HTML" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MarkdownV2" 'PrefixI 'False) (U1 :: Type -> Type)))

data SendMessageRequest Source #

Request parameters for sendMessage.

Constructors

SendMessageRequest 

Fields

Instances

Instances details
Generic SendMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SendMessageRequest :: Type -> Type #

FromJSON SendMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser SendMessageRequest

parseJSONList :: Value -> Parser [SendMessageRequest]

ToJSON SendMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendMessageRequest = D1 ('MetaData "SendMessageRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SendMessageRequest" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sendMessageChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: S1 ('MetaSel ('Just "sendMessageText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "sendMessageParseMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ParseMode)) :*: (S1 ('MetaSel ('Just "sendMessageEntities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [MessageEntity])) :*: S1 ('MetaSel ('Just "sendMessageDisableWebPagePreview") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))) :*: ((S1 ('MetaSel ('Just "sendMessageDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendMessageProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "sendMessageReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId)) :*: (S1 ('MetaSel ('Just "sendMessageAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendMessageReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SomeReplyMarkup)))))))

data ForwardMessageRequest Source #

Request parameters for forwardMessage.

Constructors

ForwardMessageRequest 

Fields

Instances

Instances details
Generic ForwardMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep ForwardMessageRequest :: Type -> Type #

FromJSON ForwardMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser ForwardMessageRequest

parseJSONList :: Value -> Parser [ForwardMessageRequest]

ToJSON ForwardMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep ForwardMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep ForwardMessageRequest = D1 ('MetaData "ForwardMessageRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "ForwardMessageRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "forwardMessageChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: S1 ('MetaSel ('Just "forwardMessageFromChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId)) :*: (S1 ('MetaSel ('Just "forwardMessageDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "forwardMessageProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "forwardMessageMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MessageId)))))

sendMessage

type SendDocumentContent = "sendDocument" :> (MultipartForm Tmp SendDocumentRequest :> Post '[JSON] (Response Message)) Source #

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

sendDocument :: SendDocumentRequest -> ClientM (Response Message) Source #

Use this method to send text messages. On success, the sent Message is returned.

https://core.telegram.org/bots/api#senddocument

data SendDocumentRequest Source #

Request parameters for sendDocument

Constructors

SendDocumentRequest 

Fields

Instances

Instances details
Generic SendDocumentRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SendDocumentRequest :: Type -> Type #

ToJSON SendDocumentRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

ToMultipart Tmp SendDocumentRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

toMultipart :: SendDocumentRequest -> MultipartData Tmp

type Rep SendDocumentRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendDocumentRequest = D1 ('MetaData "SendDocumentRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SendDocumentRequest" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sendDocumentChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: (S1 ('MetaSel ('Just "sendDocumentDocument") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DocumentFile) :*: S1 ('MetaSel ('Just "sendDocumentThumb") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)))) :*: (S1 ('MetaSel ('Just "sendDocumentCaption") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "sendDocumentParseMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ParseMode)) :*: S1 ('MetaSel ('Just "sendDocumentCaptionEntities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [MessageEntity]))))) :*: ((S1 ('MetaSel ('Just "sendDocumentDisableContentTypeDetection") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "sendDocumentDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendDocumentProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: (S1 ('MetaSel ('Just "sendDocumentReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId)) :*: (S1 ('MetaSel ('Just "sendDocumentAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendDocumentReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SomeReplyMarkup)))))))

newtype DocumentFile Source #

Instances

Instances details
ToJSON DocumentFile Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

toJSON :: DocumentFile -> Value

toEncoding :: DocumentFile -> Encoding

toJSONList :: [DocumentFile] -> Value

toEncodingList :: [DocumentFile] -> Encoding

toSendDocument :: SomeChatId -> DocumentFile -> SendDocumentRequest Source #

Generate send document structure.

getFile

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

sendPhoto

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

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

newtype PhotoFile Source #

Constructors

MakePhotoFile InputFile 

Instances

Instances details
ToJSON PhotoFile Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

toJSON :: PhotoFile -> Value

toEncoding :: PhotoFile -> Encoding

toJSONList :: [PhotoFile] -> Value

toEncodingList :: [PhotoFile] -> Encoding

data SendPhotoRequest Source #

Request parameters for sendPhoto

Constructors

SendPhotoRequest 

Fields

Instances

Instances details
Generic SendPhotoRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SendPhotoRequest :: Type -> Type #

ToJSON SendPhotoRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

ToMultipart Tmp SendPhotoRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

toMultipart :: SendPhotoRequest -> MultipartData Tmp

type Rep SendPhotoRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendPhotoRequest = D1 ('MetaData "SendPhotoRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SendPhotoRequest" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sendPhotoChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: S1 ('MetaSel ('Just "sendPhotoPhoto") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PhotoFile)) :*: (S1 ('MetaSel ('Just "sendPhotoThumb") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)) :*: (S1 ('MetaSel ('Just "sendPhotoCaption") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "sendPhotoParseMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ParseMode))))) :*: ((S1 ('MetaSel ('Just "sendPhotoCaptionEntities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [MessageEntity])) :*: (S1 ('MetaSel ('Just "sendPhotoDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendPhotoProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: (S1 ('MetaSel ('Just "sendPhotoReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId)) :*: (S1 ('MetaSel ('Just "sendPhotoAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendPhotoReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SomeReplyMarkup)))))))

sendPhoto :: SendPhotoRequest -> ClientM (Response Message) Source #

Use this method to send photos. On success, the sent Message is returned.

https://core.telegram.org/bots/api#sendphoto

data CopyMessageRequest Source #

Request parameters for copyMessage.

Constructors

CopyMessageRequest 

Fields

Instances

Instances details
Generic CopyMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep CopyMessageRequest :: Type -> Type #

FromJSON CopyMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser CopyMessageRequest

parseJSONList :: Value -> Parser [CopyMessageRequest]

ToJSON CopyMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep CopyMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep CopyMessageRequest = D1 ('MetaData "CopyMessageRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "CopyMessageRequest" 'PrefixI 'True) (((S1 ('MetaSel ('Just "copyMessageChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: S1 ('MetaSel ('Just "copyMessageFromChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId)) :*: (S1 ('MetaSel ('Just "copyMessageMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MessageId) :*: (S1 ('MetaSel ('Just "copyMessageCaption") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "copyMessageParseMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ParseMode))))) :*: ((S1 ('MetaSel ('Just "copyMessageCaptionEntities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [MessageEntity])) :*: (S1 ('MetaSel ('Just "copyMessageDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "copyMessageProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: (S1 ('MetaSel ('Just "copyMessageReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId)) :*: (S1 ('MetaSel ('Just "copyMessageAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "copyMessageReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InlineKeyboardMarkup)))))))

data SendAudioRequest Source #

Request parameters for sendAudio.

Constructors

SendAudioRequest 

Fields

Instances

Instances details
Generic SendAudioRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SendAudioRequest :: Type -> Type #

ToJSON SendAudioRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

ToMultipart Tmp SendAudioRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

toMultipart :: SendAudioRequest -> MultipartData Tmp

type Rep SendAudioRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendAudioRequest = D1 ('MetaData "SendAudioRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SendAudioRequest" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sendAudioChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: (S1 ('MetaSel ('Just "sendAudioAudio") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InputFile) :*: S1 ('MetaSel ('Just "sendAudioDuration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))) :*: ((S1 ('MetaSel ('Just "sendAudioPerformer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "sendAudioTitle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "sendAudioThumb") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InputFile)) :*: S1 ('MetaSel ('Just "sendAudioCaption") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))) :*: ((S1 ('MetaSel ('Just "sendAudioParseMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ParseMode)) :*: (S1 ('MetaSel ('Just "sendAudioCaptionEntities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [MessageEntity])) :*: S1 ('MetaSel ('Just "sendAudioDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "sendAudioProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendAudioReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId))) :*: (S1 ('MetaSel ('Just "sendAudioAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendAudioReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InlineKeyboardMarkup)))))))

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

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

sendAudio :: SendAudioRequest -> ClientM (Response Message) Source #

Use this method to send audio files, if you want Telegram clients to display them in the music player. Your audio must be in the .MP3 or .M4A format. On success, the sent Message is returned. Bots can currently send audio files of up to 50 MB in size, this limit may be changed in the future.

For sending voice messages, use the sendVoice method instead.

data SendVideoRequest Source #

Request parameters for sendVideo.

Constructors

SendVideoRequest 

Fields

Instances

Instances details
Generic SendVideoRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SendVideoRequest :: Type -> Type #

ToJSON SendVideoRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

ToMultipart Tmp SendVideoRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

toMultipart :: SendVideoRequest -> MultipartData Tmp

type Rep SendVideoRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendVideoRequest = D1 ('MetaData "SendVideoRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SendVideoRequest" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sendVideoChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: (S1 ('MetaSel ('Just "sendVideoVideo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InputFile) :*: S1 ('MetaSel ('Just "sendVideoDuration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))) :*: ((S1 ('MetaSel ('Just "sendVideoWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "sendVideoHeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "sendVideoThumb") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InputFile)) :*: S1 ('MetaSel ('Just "sendVideoCaption") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))) :*: (((S1 ('MetaSel ('Just "sendVideoParseMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ParseMode)) :*: S1 ('MetaSel ('Just "sendVideoCaptionEntities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [MessageEntity]))) :*: (S1 ('MetaSel ('Just "sendVideoSupportsStreaming") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendVideoDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "sendVideoProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendVideoReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId))) :*: (S1 ('MetaSel ('Just "sendVideoAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendVideoReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InlineKeyboardMarkup)))))))

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

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

sendVideo :: SendVideoRequest -> ClientM (Response Message) Source #

Use this method to send video files, Telegram clients support mp4 videos (other formats may be sent as Document). On success, the sent Message is returned. Bots can currently send video files of up to 50 MB in size, this limit may be changed in the future.

data SendAnimationRequest Source #

Request parameters for sendAnimation.

Constructors

SendAnimationRequest 

Fields

Instances

Instances details
Generic SendAnimationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SendAnimationRequest :: Type -> Type #

ToJSON SendAnimationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

ToMultipart Tmp SendAnimationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

toMultipart :: SendAnimationRequest -> MultipartData Tmp

type Rep SendAnimationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendAnimationRequest = D1 ('MetaData "SendAnimationRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SendAnimationRequest" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sendAnimationChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: (S1 ('MetaSel ('Just "sendAnimationAnimation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InputFile) :*: S1 ('MetaSel ('Just "sendAnimationDuration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))) :*: ((S1 ('MetaSel ('Just "sendAnimationWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "sendAnimationHeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "sendAnimationThumb") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InputFile)) :*: S1 ('MetaSel ('Just "sendAnimationCaption") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))) :*: ((S1 ('MetaSel ('Just "sendAnimationParseMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ParseMode)) :*: (S1 ('MetaSel ('Just "sendAnimationCaptionEntities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [MessageEntity])) :*: S1 ('MetaSel ('Just "sendAnimationDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "sendAnimationProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendAnimationReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId))) :*: (S1 ('MetaSel ('Just "sendAnimationAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendAnimationReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InlineKeyboardMarkup)))))))

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

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

sendAnimation :: SendAnimationRequest -> ClientM (Response Message) Source #

Use this method to send animation files (GIF or H.264/MPEG-4 AVC video without sound). On success, the sent Message is returned. Bots can currently send animation files of up to 50 MB in size, this limit may be changed in the future.

data SendVoiceRequest Source #

Request parameters for sendVoice.

Constructors

SendVoiceRequest 

Fields

Instances

Instances details
Generic SendVoiceRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SendVoiceRequest :: Type -> Type #

ToJSON SendVoiceRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

ToMultipart Tmp SendVoiceRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

toMultipart :: SendVoiceRequest -> MultipartData Tmp

type Rep SendVoiceRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendVoiceRequest = D1 ('MetaData "SendVoiceRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SendVoiceRequest" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sendVoiceChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: S1 ('MetaSel ('Just "sendVoiceVoice") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InputFile)) :*: (S1 ('MetaSel ('Just "sendVoiceCaption") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "sendVoiceParseMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ParseMode)) :*: S1 ('MetaSel ('Just "sendVoiceCaptionEntities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [MessageEntity]))))) :*: ((S1 ('MetaSel ('Just "sendVoiceDuration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "sendVoiceDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendVoiceProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: (S1 ('MetaSel ('Just "sendVoiceReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId)) :*: (S1 ('MetaSel ('Just "sendVoiceAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendVoiceReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InlineKeyboardMarkup)))))))

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

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

sendVoice :: SendVoiceRequest -> ClientM (Response Message) Source #

Use this method to send audio files, if you want Telegram clients to display the file as a playable voice message. For this to work, your audio must be in an .OGG file encoded with OPUS (other formats may be sent as Audio or Document). On success, the sent Message is returned. Bots can currently send voice messages of up to 50 MB in size, this limit may be changed in the future.

data SendVideoNoteRequest Source #

Request parameters for sendVideoNote.

Constructors

SendVideoNoteRequest 

Fields

Instances

Instances details
Generic SendVideoNoteRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SendVideoNoteRequest :: Type -> Type #

ToJSON SendVideoNoteRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

ToMultipart Tmp SendVideoNoteRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

toMultipart :: SendVideoNoteRequest -> MultipartData Tmp

type Rep SendVideoNoteRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendVideoNoteRequest = D1 ('MetaData "SendVideoNoteRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SendVideoNoteRequest" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sendVideoNoteChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: S1 ('MetaSel ('Just "sendVideoNoteVideoNote") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InputFile)) :*: (S1 ('MetaSel ('Just "sendVideoNoteDuration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "sendVideoNoteLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "sendVideoNoteThumb") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InputFile))))) :*: ((S1 ('MetaSel ('Just "sendVideoNoteDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendVideoNoteProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "sendVideoNoteReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId)) :*: (S1 ('MetaSel ('Just "sendVideoNoteAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendVideoNoteReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InlineKeyboardMarkup)))))))

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

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

sendVideoNote :: SendVideoNoteRequest -> ClientM (Response Message) Source #

As of v.4.0, Telegram clients support rounded square mp4 videos of up to 1 minute long. Use this method to send video messages. On success, the sent Message is returned.

data SendMediaGroupRequest Source #

Request parameters for sendMediaGroup.

Constructors

SendMediaGroupRequest 

Fields

Instances

Instances details
Generic SendMediaGroupRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SendMediaGroupRequest :: Type -> Type #

ToJSON SendMediaGroupRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendMediaGroupRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendMediaGroupRequest = D1 ('MetaData "SendMediaGroupRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SendMediaGroupRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "sendMediaGroupChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: (S1 ('MetaSel ('Just "sendMediaGroupMedia") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [InputMedia]) :*: S1 ('MetaSel ('Just "sendMediaGroupDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "sendMediaGroupProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendMediaGroupReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId))) :*: (S1 ('MetaSel ('Just "sendMediaGroupAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendMediaGroupReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InlineKeyboardMarkup))))))

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

sendMediaGroup :: SendMediaGroupRequest -> ClientM (Response [Message]) Source #

Use this method to send a group of photos, videos, documents or audios as an album. Documents and audio files can be only grouped in an album with messages of the same type. On success, an array of Messages that were sent is returned.

data SendLocationRequest Source #

Request parameters for sendLocation.

Constructors

SendLocationRequest 

Fields

Instances

Instances details
Generic SendLocationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SendLocationRequest :: Type -> Type #

FromJSON SendLocationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser SendLocationRequest

parseJSONList :: Value -> Parser [SendLocationRequest]

ToJSON SendLocationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendLocationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendLocationRequest = D1 ('MetaData "SendLocationRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SendLocationRequest" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sendLocationChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: (S1 ('MetaSel ('Just "sendLocationLatitude") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float) :*: S1 ('MetaSel ('Just "sendLocationLongitude") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))) :*: (S1 ('MetaSel ('Just "sendLocationHorizontalAccuracy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Float)) :*: (S1 ('MetaSel ('Just "sendLocationLivePeriod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "sendLocationHeading") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))))) :*: ((S1 ('MetaSel ('Just "sendLocationProximityAlertRadius") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "sendLocationDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendLocationProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: (S1 ('MetaSel ('Just "sendLocationReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId)) :*: (S1 ('MetaSel ('Just "sendLocationAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendLocationReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InlineKeyboardMarkup)))))))

data EditMessageLiveLocationRequest Source #

Request parameters for editMessageLiveLocation.

Constructors

EditMessageLiveLocationRequest 

Fields

Instances

Instances details
Generic EditMessageLiveLocationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep EditMessageLiveLocationRequest :: Type -> Type #

FromJSON EditMessageLiveLocationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

ToJSON EditMessageLiveLocationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep EditMessageLiveLocationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep EditMessageLiveLocationRequest = D1 ('MetaData "EditMessageLiveLocationRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "EditMessageLiveLocationRequest" 'PrefixI 'True) (((S1 ('MetaSel ('Just "editMessageLiveLocationChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SomeChatId)) :*: S1 ('MetaSel ('Just "editMessageLiveLocationMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId))) :*: (S1 ('MetaSel ('Just "editMessageLiveLocationInlineMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "editMessageLiveLocationLatitude") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))) :*: ((S1 ('MetaSel ('Just "editMessageLiveLocationLongitude") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float) :*: S1 ('MetaSel ('Just "editMessageLiveLocationHorizontalAccuracy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Float))) :*: (S1 ('MetaSel ('Just "editMessageLiveLocationHeading") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "editMessageLiveLocationProximityAlertRadius") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "editMessageLiveLocationReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InlineKeyboardMarkup)))))))

data StopMessageLiveLocationRequest Source #

Request parameters for stopMessageLiveLocation.

Constructors

StopMessageLiveLocationRequest 

Fields

Instances

Instances details
Generic StopMessageLiveLocationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep StopMessageLiveLocationRequest :: Type -> Type #

FromJSON StopMessageLiveLocationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

ToJSON StopMessageLiveLocationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep StopMessageLiveLocationRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep StopMessageLiveLocationRequest = D1 ('MetaData "StopMessageLiveLocationRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "StopMessageLiveLocationRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "stopMessageLiveLocationChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SomeChatId)) :*: S1 ('MetaSel ('Just "stopMessageLiveLocationMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId))) :*: (S1 ('MetaSel ('Just "stopMessageLiveLocationInlineMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "stopMessageLiveLocationReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InlineKeyboardMarkup)))))

data SendVenueRequest Source #

Request parameters for sendVenue.

Constructors

SendVenueRequest 

Fields

Instances

Instances details
Generic SendVenueRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SendVenueRequest :: Type -> Type #

FromJSON SendVenueRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser SendVenueRequest

parseJSONList :: Value -> Parser [SendVenueRequest]

ToJSON SendVenueRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendVenueRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendVenueRequest = D1 ('MetaData "SendVenueRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SendVenueRequest" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sendVenueChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: (S1 ('MetaSel ('Just "sendVenueLatitude") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float) :*: S1 ('MetaSel ('Just "sendVenueLongitude") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))) :*: ((S1 ('MetaSel ('Just "sendVenueTitle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "sendVenueAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "sendVenueFoursquareId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "sendVenueFoursquareType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))) :*: ((S1 ('MetaSel ('Just "sendVenueGooglePlaceId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "sendVenueGooglePlaceType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "sendVenueDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "sendVenueProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendVenueReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId))) :*: (S1 ('MetaSel ('Just "sendVenueAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendVenueReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InlineKeyboardMarkup)))))))

data SendContactRequest Source #

Request parameters for sendContact.

Constructors

SendContactRequest 

Fields

Instances

Instances details
Generic SendContactRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SendContactRequest :: Type -> Type #

FromJSON SendContactRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser SendContactRequest

parseJSONList :: Value -> Parser [SendContactRequest]

ToJSON SendContactRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendContactRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendContactRequest = D1 ('MetaData "SendContactRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SendContactRequest" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sendContactChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: S1 ('MetaSel ('Just "sendContactPhoneNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "sendContactFirstName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "sendContactLastName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "sendContactVcard") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) :*: ((S1 ('MetaSel ('Just "sendContactDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendContactProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "sendContactReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId)) :*: (S1 ('MetaSel ('Just "sendContactAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendContactReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InlineKeyboardMarkup)))))))

data SendPollRequest Source #

Request parameters for sendPoll.

Constructors

SendPollRequest 

Fields

Instances

Instances details
Generic SendPollRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SendPollRequest :: Type -> Type #

FromJSON SendPollRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser SendPollRequest

parseJSONList :: Value -> Parser [SendPollRequest]

ToJSON SendPollRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

toJSON :: SendPollRequest -> Value

toEncoding :: SendPollRequest -> Encoding

toJSONList :: [SendPollRequest] -> Value

toEncodingList :: [SendPollRequest] -> Encoding

type Rep SendPollRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendPollRequest = D1 ('MetaData "SendPollRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SendPollRequest" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "sendPollChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: S1 ('MetaSel ('Just "sendPollQuestion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "sendPollOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: S1 ('MetaSel ('Just "sendPollIsAnonymous") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "sendPollType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "sendPollAllowsMultipleAnswers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "sendPollCorrectOptionId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: (S1 ('MetaSel ('Just "sendPollExplanation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "sendPollExplanationParseMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ParseMode)))))) :*: (((S1 ('MetaSel ('Just "sendPollExplanationEntities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [MessageEntity])) :*: S1 ('MetaSel ('Just "sendPollOpenPeriod") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "sendPollCloseDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "sendPollIsClosed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "sendPollDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendPollProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "sendPollReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId)) :*: (S1 ('MetaSel ('Just "sendPollAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendPollReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InlineKeyboardMarkup))))))))

data SendDiceRequest Source #

Request parameters for sendDice.

Constructors

SendDiceRequest 

Fields

Instances

Instances details
Generic SendDiceRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SendDiceRequest :: Type -> Type #

FromJSON SendDiceRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser SendDiceRequest

parseJSONList :: Value -> Parser [SendDiceRequest]

ToJSON SendDiceRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

toJSON :: SendDiceRequest -> Value

toEncoding :: SendDiceRequest -> Encoding

toJSONList :: [SendDiceRequest] -> Value

toEncodingList :: [SendDiceRequest] -> Encoding

type Rep SendDiceRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SendDiceRequest = D1 ('MetaData "SendDiceRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SendDiceRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "sendDiceChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: (S1 ('MetaSel ('Just "sendDiceEmoji") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "sendDiceDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "sendDiceProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendDiceReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId))) :*: (S1 ('MetaSel ('Just "sendDiceAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendDiceReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InlineKeyboardMarkup))))))

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

sendChatAction Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> Text

Type of action to broadcast. Choose one, depending on what the user is about to receive: typing for text messages, upload_photo for photos, record_video or upload_video for videos, record_voice or upload_voice for voice notes, upload_document for general files, choose_sticker for stickers, find_location for location data, record_video_note or upload_video_note for video notes.

-> ClientM (Response Bool) 

Use this method when you need to tell the user that something is happening on the bot's side. The status is set for 5 seconds or less (when a message arrives from your bot, Telegram clients clear its typing status). Returns True on success.

Example: The ImageBot needs some time to process a request and upload the image. Instead of sending a text message along the lines of “Retrieving image, please wait…”, the bot may use sendChatAction with action = upload_photo. The user will see a “sending photo” status for the bot.

We only recommend using this method when a response from the bot will take a noticeable amount of time to arrive.

data GetUserProfilePhotosRequest Source #

Request parameters for getUserProfilePhotos.

Constructors

GetUserProfilePhotosRequest 

Fields

Instances

Instances details
Generic GetUserProfilePhotosRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep GetUserProfilePhotosRequest :: Type -> Type #

FromJSON GetUserProfilePhotosRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

ToJSON GetUserProfilePhotosRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep GetUserProfilePhotosRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep GetUserProfilePhotosRequest = D1 ('MetaData "GetUserProfilePhotosRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "GetUserProfilePhotosRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "getUserProfilePhotosUserId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UserId) :*: (S1 ('MetaSel ('Just "getUserProfilePhotosOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "getUserProfilePhotosLimit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))))

data BanChatMemberRequest Source #

Request parameters for banChatMember.

Constructors

BanChatMemberRequest 

Fields

  • banChatMemberChatId :: SomeChatId

    Unique identifier for the target chat or username of the target channel (in the format @channelusername)

  • banChatMemberUserId :: UserId

    Unique identifier of the target user

  • banChatMemberUntilDate :: Maybe Int

    Date when the user will be unbanned, unix time. If user is banned for more than 366 days or less than 30 seconds from the current time they are considered to be banned forever. Applied for supergroups and channels only.

  • banChatMemberRevokeMessages :: Maybe Bool

    Pass True to delete all messages from the chat for the user that is being removed. If False, the user will be able to see messages in the group that were sent before the user was removed. Always True for supergroups and channels.

Instances

Instances details
Generic BanChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep BanChatMemberRequest :: Type -> Type #

FromJSON BanChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser BanChatMemberRequest

parseJSONList :: Value -> Parser [BanChatMemberRequest]

ToJSON BanChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep BanChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep BanChatMemberRequest = D1 ('MetaData "BanChatMemberRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "BanChatMemberRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "banChatMemberChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: S1 ('MetaSel ('Just "banChatMemberUserId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UserId)) :*: (S1 ('MetaSel ('Just "banChatMemberUntilDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "banChatMemberRevokeMessages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))))

data UnbanChatMemberRequest Source #

Request parameters for unbanChatMember.

Constructors

UnbanChatMemberRequest 

Fields

Instances

Instances details
Generic UnbanChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep UnbanChatMemberRequest :: Type -> Type #

FromJSON UnbanChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser UnbanChatMemberRequest

parseJSONList :: Value -> Parser [UnbanChatMemberRequest]

ToJSON UnbanChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep UnbanChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep UnbanChatMemberRequest = D1 ('MetaData "UnbanChatMemberRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "UnbanChatMemberRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "unbanChatMemberChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: (S1 ('MetaSel ('Just "unbanChatMemberUserId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UserId) :*: S1 ('MetaSel ('Just "unbanChatMemberOnlyIfBanned") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))))

data RestrictChatMemberRequest Source #

Request parameters for restrictChatMember.

Constructors

RestrictChatMemberRequest 

Fields

Instances

Instances details
Generic RestrictChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep RestrictChatMemberRequest :: Type -> Type #

FromJSON RestrictChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser RestrictChatMemberRequest

parseJSONList :: Value -> Parser [RestrictChatMemberRequest]

ToJSON RestrictChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep RestrictChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep RestrictChatMemberRequest = D1 ('MetaData "RestrictChatMemberRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "RestrictChatMemberRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "restrictChatMemberChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: S1 ('MetaSel ('Just "restrictChatMemberUserId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UserId)) :*: (S1 ('MetaSel ('Just "restrictChatMemberPermissions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChatPermissions) :*: S1 ('MetaSel ('Just "restrictChatMemberUntilDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))))

data PromoteChatMemberRequest Source #

Request parameters for promoteChatMember.

Constructors

PromoteChatMemberRequest 

Fields

Instances

Instances details
Generic PromoteChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep PromoteChatMemberRequest :: Type -> Type #

FromJSON PromoteChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser PromoteChatMemberRequest

parseJSONList :: Value -> Parser [PromoteChatMemberRequest]

ToJSON PromoteChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep PromoteChatMemberRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep PromoteChatMemberRequest = D1 ('MetaData "PromoteChatMemberRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "PromoteChatMemberRequest" 'PrefixI 'True) (((S1 ('MetaSel ('Just "promoteChatMemberChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: (S1 ('MetaSel ('Just "promoteChatMemberUserId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UserId) :*: S1 ('MetaSel ('Just "promoteChatMemberIsAnonymous") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: (S1 ('MetaSel ('Just "promoteChatMemberCanManageChat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "promoteChatMemberCanPostMessages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "promoteChatMemberCanEditMessages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))) :*: ((S1 ('MetaSel ('Just "promoteChatMemberCanDeleteMessages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "promoteChatMemberCanManageVideoChats") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "promoteChatMemberCanRestrictMembers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "promoteChatMemberCanPromoteMembers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "promoteChatMemberCanChangeInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "promoteChatMemberCanInviteUsers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "promoteChatMemberCanPinMessages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))))))

data SetChatAdministratorCustomTitleRequest Source #

Request parameters for setChatAdministratorCustomTitle.

Constructors

SetChatAdministratorCustomTitleRequest 

Fields

Instances

Instances details
Generic SetChatAdministratorCustomTitleRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

FromJSON SetChatAdministratorCustomTitleRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

ToJSON SetChatAdministratorCustomTitleRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SetChatAdministratorCustomTitleRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SetChatAdministratorCustomTitleRequest = D1 ('MetaData "SetChatAdministratorCustomTitleRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SetChatAdministratorCustomTitleRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "setChatAdministratorCustomTitleChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: (S1 ('MetaSel ('Just "setChatAdministratorCustomTitleUserId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UserId) :*: S1 ('MetaSel ('Just "setChatAdministratorCustomTitleCustomTitle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))

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

banChatSenderChat Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> ChatId

Unique identifier of the target sender chat

-> ClientM (Response Bool) 

Use this method to ban a channel chat in a supergroup or a channel. Until the chat is unbanned, the owner of the banned chat won't be able to send messages on behalf of any of their channels. The bot must be an administrator in the supergroup or channel for this to work and must have the appropriate administrator rights. Returns True on success.

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

unbanChatSenderChat Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> ChatId

Unique identifier of the target sender chat

-> ClientM (Response Bool) 

Use this method to unban a previously banned channel chat in a supergroup or channel. The bot must be an administrator for this to work and must have the appropriate administrator rights. Returns True on success.

data SetChatPermissionsRequest Source #

Request parameters for setChatPermissions.

Constructors

SetChatPermissionsRequest 

Fields

Instances

Instances details
Generic SetChatPermissionsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SetChatPermissionsRequest :: Type -> Type #

FromJSON SetChatPermissionsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser SetChatPermissionsRequest

parseJSONList :: Value -> Parser [SetChatPermissionsRequest]

ToJSON SetChatPermissionsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SetChatPermissionsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SetChatPermissionsRequest = D1 ('MetaData "SetChatPermissionsRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SetChatPermissionsRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "setChatPermissionsChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: S1 ('MetaSel ('Just "setChatPermissionsPermissions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChatPermissions)))

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

exportChatInviteLink Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> ClientM (Response Text) 

Use this method to generate a new primary invite link for a chat; any previously generated primary link is revoked. The bot must be an administrator in the chat for this to work and must have the appropriate administrator rights. Returns the new invite link as String on success.

data CreateChatInviteLinkRequest Source #

Request parameters for createChatInviteLink.

Constructors

CreateChatInviteLinkRequest 

Fields

Instances

Instances details
Generic CreateChatInviteLinkRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep CreateChatInviteLinkRequest :: Type -> Type #

FromJSON CreateChatInviteLinkRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

ToJSON CreateChatInviteLinkRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep CreateChatInviteLinkRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep CreateChatInviteLinkRequest = D1 ('MetaData "CreateChatInviteLinkRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "CreateChatInviteLinkRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "createChatInviteLinkChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: S1 ('MetaSel ('Just "createChatInviteLinkName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "createChatInviteLinkExpireDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer)) :*: (S1 ('MetaSel ('Just "createChatInviteLinkMemberLimit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "createChatInviteLinkCreatesJoinRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))))

data EditChatInviteLinkRequest Source #

Request parameters for editChatInviteLink.

Constructors

EditChatInviteLinkRequest 

Fields

Instances

Instances details
Generic EditChatInviteLinkRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep EditChatInviteLinkRequest :: Type -> Type #

FromJSON EditChatInviteLinkRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser EditChatInviteLinkRequest

parseJSONList :: Value -> Parser [EditChatInviteLinkRequest]

ToJSON EditChatInviteLinkRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep EditChatInviteLinkRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep EditChatInviteLinkRequest = D1 ('MetaData "EditChatInviteLinkRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "EditChatInviteLinkRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "editChatInviteLinkChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: (S1 ('MetaSel ('Just "editChatInviteLinkInviteLink") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "editChatInviteLinkName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))) :*: (S1 ('MetaSel ('Just "editChatInviteLinkExpireDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer)) :*: (S1 ('MetaSel ('Just "editChatInviteLinkMemberLimit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "editChatInviteLinkCreatesJoinRequest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))))

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

revokeChatInviteLink Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> Text

The invite link to revoke

-> ClientM (Response ChatInviteLink) 

Use this method to revoke an invite link created by the bot. If the primary link is revoked, a new link is automatically generated. The bot must be an administrator in the chat for this to work and must have the appropriate administrator rights. Returns the revoked invite link as ChatInviteLink object.

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

approveChatJoinRequest Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> UserId

Unique identifier of the target user

-> ClientM (Response Bool) 

Use this method to approve a chat join request. The bot must be an administrator in the chat for this to work and must have the can_invite_users administrator right. Returns True on success.

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

declineChatJoinRequest Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> UserId

Unique identifier of the target user

-> ClientM (Response Bool) 

Use this method to decline a chat join request. The bot must be an administrator in the chat for this to work and must have the can_invite_users administrator right. Returns True on success.

data SetChatPhotoRequest Source #

Request parameters for setChatPhoto.

Constructors

SetChatPhotoRequest 

Fields

Instances

Instances details
ToMultipart Tmp SetChatPhotoRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

toMultipart :: SetChatPhotoRequest -> MultipartData Tmp

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

setChatPhoto :: SetChatPhotoRequest -> ClientM (Response Bool) Source #

Use this method to set a new profile photo for the chat. Photos can't be changed for private chats. The bot must be an administrator in the chat for this to work and must have the appropriate administrator rights. Returns True on success.

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

deleteChatPhoto Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> ClientM (Response Bool) 

Use this method to delete a chat photo. Photos can't be changed for private chats. The bot must be an administrator in the chat for this to work and must have the appropriate administrator rights. Returns True on success.

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

setChatTitle Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> Text

New chat title, 0-255 characters

-> ClientM (Response Bool) 

Use this method to change the title of a chat. Titles can't be changed for private chats. The bot must be an administrator in the chat for this to work and must have the appropriate administrator rights. Returns True on success.

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

setChatDescription Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> Maybe Text

New chat description, 0-255 characters

-> ClientM (Response Bool) 

Use this method to change the description of a group, a supergroup or a channel. The bot must be an administrator in the chat for this to work and must have the appropriate administrator rights. Returns True on success.

data PinChatMessageRequest Source #

Request parameters for pinChatMessage.

Constructors

PinChatMessageRequest 

Fields

Instances

Instances details
Generic PinChatMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep PinChatMessageRequest :: Type -> Type #

FromJSON PinChatMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser PinChatMessageRequest

parseJSONList :: Value -> Parser [PinChatMessageRequest]

ToJSON PinChatMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep PinChatMessageRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep PinChatMessageRequest = D1 ('MetaData "PinChatMessageRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "PinChatMessageRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "pinChatMessageChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeChatId) :*: (S1 ('MetaSel ('Just "pinChatMessageMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MessageId) :*: S1 ('MetaSel ('Just "pinChatMessageDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))))

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

unpinChatMessage Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> Maybe MessageId

Identifier of a message to unpin. If not specified, the most recent pinned message (by sending date) will be unpinned.

-> ClientM (Response Bool) 

Use this method to remove a message from the list of pinned messages in a chat. If the chat is not a private chat, the bot must be an administrator in the chat for this to work and must have the can_pin_messages administrator right in a supergroup or can_edit_messages administrator right in a channel. Returns True on success.

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

unpinAllChatMessages Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> ClientM (Response Bool) 

Use this method to clear the list of pinned messages in a chat. If the chat is not a private chat, the bot must be an administrator in the chat for this to work and must have the can_pin_messages administrator right in a supergroup or can_edit_messages administrator right in a channel. Returns True on success.

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

leaveChat Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> ClientM (Response Bool) 

Use this method for your bot to leave a group, supergroup or channel. Returns True on success.

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

getChat Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> ClientM (Response Chat) 

Use this method to get up to date information about the chat (current name of the user for one-on-one conversations, current username of a user, group or channel, etc.). Returns a Chat object on success.

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

getChatAdministrators Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> ClientM (Response [ChatMember]) 

Use this method to get a list of administrators in a chat. On success, returns an Array of ChatMember objects that contains information about all chat administrators except other bots. If the chat is a group or a supergroup and no administrators were appointed, only the creator will be returned.

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

getChatMemberCount Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> ClientM (Response Integer) 

Use this method to get the number of members in a chat. Returns Int on success.

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

getChatMember Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> UserId

Unique identifier of the target user

-> ClientM (Response ChatMember) 

Use this method to get information about a member of a chat. Returns a ChatMember object on success.

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

setChatStickerSet Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> Text

Name of the sticker set to be set as the group sticker set

-> ClientM (Response Bool) 

Use this method to set a new group sticker set for a supergroup. The bot must be an administrator in the chat for this to work and must have the appropriate administrator rights. Use the field can_set_sticker_set optionally returned in getChat requests to check if the bot can use this method. Returns True on success.

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

deleteChatStickerSet Source #

Arguments

:: SomeChatId

Unique identifier for the target chat or username of the target supergroup (in the format @supergroupusername)

-> ClientM (Response Bool) 

Use this method to delete a group sticker set from a supergroup. The bot must be an administrator in the chat for this to work and must have the appropriate administrator rights. Use the field can_set_sticker_set optionally returned in getChat requests to check if the bot can use this method. Returns True on success.

data AnswerCallbackQueryRequest Source #

Request parameters for answerCallbackQuery.

Constructors

AnswerCallbackQueryRequest 

Fields

  • answerCallbackQueryCallbackQueryId :: CallbackQueryId

    Unique identifier for the query to be answered

  • answerCallbackQueryText :: Maybe Text

    Text of the notification. If not specified, nothing will be shown to the user, 0-200 characters

  • answerCallbackQueryShowAlert :: Maybe Bool

    If True, an alert will be shown by the client instead of a notification at the top of the chat screen. Defaults to false.

  • answerCallbackQueryUrl :: Maybe Text

    URL that will be opened by the user's client. If you have created a Game and accepted the conditions via @Botfather, specify the URL that opens your game — note that this will only work if the query comes from a callback_game button.

    Otherwise, you may use links like t.me/your_bot?start=XXXX that open your bot with a parameter.

  • answerCallbackQueryCacheTime :: Maybe Integer

    The maximum amount of time in seconds that the result of the callback query may be cached client-side. Telegram apps will support caching starting in version 3.14. Defaults to 0.

Instances

Instances details
Generic AnswerCallbackQueryRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep AnswerCallbackQueryRequest :: Type -> Type #

FromJSON AnswerCallbackQueryRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

ToJSON AnswerCallbackQueryRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep AnswerCallbackQueryRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep AnswerCallbackQueryRequest = D1 ('MetaData "AnswerCallbackQueryRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "AnswerCallbackQueryRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "answerCallbackQueryCallbackQueryId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CallbackQueryId) :*: S1 ('MetaSel ('Just "answerCallbackQueryText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "answerCallbackQueryShowAlert") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "answerCallbackQueryUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "answerCallbackQueryCacheTime") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Integer))))))

data SetMyCommandsRequest Source #

Request parameters for setMyCommands.

Constructors

SetMyCommandsRequest 

Fields

  • setMyCommandsCommands :: [BotCommand]

    A JSON-serialized list of bot commands to be set as the list of the bot's commands. At most 100 commands can be specified.

  • setMyCommandsScope :: Maybe BotCommandScope

    A JSON-serialized object, describing scope of users for which the commands are relevant. Defaults to BotCommandScopeDefault.

  • setMyCommandsLanguageCode :: Maybe Text

    A two-letter ISO 639-1 language code. If empty, commands will be applied to all users from the given scope, for whose language there are no dedicated commands

Instances

Instances details
Generic SetMyCommandsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SetMyCommandsRequest :: Type -> Type #

FromJSON SetMyCommandsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser SetMyCommandsRequest

parseJSONList :: Value -> Parser [SetMyCommandsRequest]

ToJSON SetMyCommandsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SetMyCommandsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SetMyCommandsRequest = D1 ('MetaData "SetMyCommandsRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SetMyCommandsRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "setMyCommandsCommands") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BotCommand]) :*: (S1 ('MetaSel ('Just "setMyCommandsScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BotCommandScope)) :*: S1 ('MetaSel ('Just "setMyCommandsLanguageCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))

data DeleteMyCommandsRequest Source #

Request parameters for deleteMyCommands.

Constructors

DeleteMyCommandsRequest 

Fields

Instances

Instances details
Generic DeleteMyCommandsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep DeleteMyCommandsRequest :: Type -> Type #

FromJSON DeleteMyCommandsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser DeleteMyCommandsRequest

parseJSONList :: Value -> Parser [DeleteMyCommandsRequest]

ToJSON DeleteMyCommandsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep DeleteMyCommandsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep DeleteMyCommandsRequest = D1 ('MetaData "DeleteMyCommandsRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "DeleteMyCommandsRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "deleteMyCommandsScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BotCommandScope)) :*: S1 ('MetaSel ('Just "deleteMyCommandsLanguageCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))

data GetMyCommandsRequest Source #

Request parameters for getMyCommands.

Constructors

GetMyCommandsRequest 

Fields

Instances

Instances details
Generic GetMyCommandsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep GetMyCommandsRequest :: Type -> Type #

FromJSON GetMyCommandsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser GetMyCommandsRequest

parseJSONList :: Value -> Parser [GetMyCommandsRequest]

ToJSON GetMyCommandsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep GetMyCommandsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep GetMyCommandsRequest = D1 ('MetaData "GetMyCommandsRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "GetMyCommandsRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMyCommandsScope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BotCommandScope)) :*: S1 ('MetaSel ('Just "getMyCommandsLanguageCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))

data SetChatMenuButtonRequest Source #

Request parameters for setChatMenuButton

Constructors

SetChatMenuButtonRequest 

Fields

Instances

Instances details
Generic SetChatMenuButtonRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SetChatMenuButtonRequest :: Type -> Type #

FromJSON SetChatMenuButtonRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser SetChatMenuButtonRequest

parseJSONList :: Value -> Parser [SetChatMenuButtonRequest]

ToJSON SetChatMenuButtonRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SetChatMenuButtonRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SetChatMenuButtonRequest = D1 ('MetaData "SetChatMenuButtonRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SetChatMenuButtonRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "setChatMenuButtonRequestChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ChatId)) :*: S1 ('MetaSel ('Just "setChatMenuButtonRequestMenuButton") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MenuButton))))

data GetChatMenuButtonRequest Source #

Request parameters for getChatMenuButton

Constructors

GetChatMenuButtonRequest 

Fields

Instances

Instances details
Generic GetChatMenuButtonRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep GetChatMenuButtonRequest :: Type -> Type #

FromJSON GetChatMenuButtonRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser GetChatMenuButtonRequest

parseJSONList :: Value -> Parser [GetChatMenuButtonRequest]

ToJSON GetChatMenuButtonRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep GetChatMenuButtonRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep GetChatMenuButtonRequest = D1 ('MetaData "GetChatMenuButtonRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "GetChatMenuButtonRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "getChatMenuButtonRequestChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ChatId))))

data SetMyDefaultAdministratorRightsRequest Source #

Request parameters for setMyDefaultAdministratorRights

Constructors

SetMyDefaultAdministratorRightsRequest 

Fields

Instances

Instances details
Generic SetMyDefaultAdministratorRightsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

FromJSON SetMyDefaultAdministratorRightsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

ToJSON SetMyDefaultAdministratorRightsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SetMyDefaultAdministratorRightsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SetMyDefaultAdministratorRightsRequest = D1 ('MetaData "SetMyDefaultAdministratorRightsRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "SetMyDefaultAdministratorRightsRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "setMyDefaultAdministratorRightsRequestRights") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ChatAdministratorRights)) :*: S1 ('MetaSel ('Just "setMyDefaultAdministratorRightsRequestForChannels") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))

data GetMyDefaultAdministratorRightsRequest Source #

Request parameters for getMyDefaultAdministratorRights

Constructors

GetMyDefaultAdministratorRightsRequest 

Fields

Instances

Instances details
Generic GetMyDefaultAdministratorRightsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

FromJSON GetMyDefaultAdministratorRightsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

ToJSON GetMyDefaultAdministratorRightsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep GetMyDefaultAdministratorRightsRequest Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep GetMyDefaultAdministratorRightsRequest = D1 ('MetaData "GetMyDefaultAdministratorRightsRequest" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.6.1-inplace" 'False) (C1 ('MetaCons "GetMyDefaultAdministratorRightsRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMyDefaultAdministratorRightsRequestForChannels") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))

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

copyMessage :: CopyMessageRequest -> ClientM (Response CopyMessageId) Source #

Use this method to copy messages of any kind. Service messages and invoice messages can't be copied. The method is analogous to the method forwardMessage, but the copied message doesn't have a link to the original message. Returns the MessageId of the sent message on success.

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

sendLocation :: SendLocationRequest -> ClientM (Response Message) Source #

Use this method to send point on the map. On success, the sent Message is returned.

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

editMessageLiveLocation :: EditMessageLiveLocationRequest -> ClientM (Response (Either Bool Message)) Source #

Use this method to edit live location messages. A location can be edited until its live_period expires or editing is explicitly disabled by a call to stopMessageLiveLocation. On success, if the edited message is not an inline message, the edited Message is returned, otherwise True is returned.

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

stopMessageLiveLocation :: StopMessageLiveLocationRequest -> ClientM (Response (Either Bool Message)) Source #

Use this method to stop updating a live location message before live_period expires. On success, if the message is not an inline message, the edited Message is returned, otherwise True is returned.

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

sendVenue :: SendVenueRequest -> ClientM (Response Message) Source #

Use this method to send information about a venue. On success, the sent Message is returned.

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

sendContact :: SendContactRequest -> ClientM (Response Message) Source #

Use this method to send phone contacts. On success, the sent Message is returned.

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

sendPoll :: SendPollRequest -> ClientM (Response Message) Source #

Use this method to send a native poll. On success, the sent Message is returned.

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

sendDice :: SendDiceRequest -> ClientM (Response Message) Source #

Use this method to send an animated emoji that will display a random value. On success, the sent Message is returned.

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

getUserProfilePhotos :: GetUserProfilePhotosRequest -> ClientM (Response UserProfilePhotos) Source #

Use this method to get a list of profile pictures for a user. Returns a UserProfilePhotos object.

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

banChatMember :: BanChatMemberRequest -> ClientM (Response Bool) Source #

Use this method to ban a user in a group, a supergroup or a channel. In the case of supergroups and channels, the user will not be able to return to the chat on their own using invite links, etc., unless unbanned first. The bot must be an administrator in the chat for this to work and must have the appropriate administrator rights. Returns True on success.

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

unbanChatMember :: UnbanChatMemberRequest -> ClientM (Response Bool) Source #

Use this method to unban a previously banned user in a supergroup or channel. The user will not return to the group or channel automatically, but will be able to join via link, etc. The bot must be an administrator for this to work. By default, this method guarantees that after the call the user is not a member of the chat, but will be able to join it. So if the user is a member of the chat they will also be removed from the chat. If you don't want this, use the parameter only_if_banned. Returns True on success.

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

restrictChatMember :: RestrictChatMemberRequest -> ClientM (Response Bool) Source #

Use this method to restrict a user in a supergroup. The bot must be an administrator in the supergroup for this to work and must have the appropriate administrator rights. Pass True for all permissions to lift restrictions from a user. Returns True on success.

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

promoteChatMember :: PromoteChatMemberRequest -> ClientM (Response Bool) Source #

Use this method to promote or demote a user in a supergroup or a channel. The bot must be an administrator in the chat for this to work and must have the appropriate administrator rights. Pass False for all boolean parameters to demote a user. Returns True on success.

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

setChatAdministratorCustomTitle :: SetChatAdministratorCustomTitleRequest -> ClientM (Response Bool) Source #

Use this method to set a custom title for an administrator in a supergroup promoted by the bot. Returns True on success.

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

setChatPermissions :: SetChatPermissionsRequest -> ClientM (Response Bool) Source #

Use this method to set default chat permissions for all members. The bot must be an administrator in the group or a supergroup for this to work and must have the can_restrict_members administrator rights. Returns True on success.

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

createChatInviteLink :: CreateChatInviteLinkRequest -> ClientM (Response ChatInviteLink) Source #

Use this method to create an additional invite link for a chat. The bot must be an administrator in the chat for this to work and must have the appropriate administrator rights. The link can be revoked using the method revokeChatInviteLink. Returns the new invite link as ChatInviteLink object.

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

editChatInviteLink :: EditChatInviteLinkRequest -> ClientM (Response ChatInviteLink) Source #

Use this method to edit a non-primary invite link created by the bot. The bot must be an administrator in the chat for this to work and must have the appropriate administrator rights. Returns the edited invite link as a ChatInviteLink object.

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

pinChatMessage :: PinChatMessageRequest -> ClientM (Response Bool) Source #

Use this method to add a message to the list of pinned messages in a chat. If the chat is not a private chat, the bot must be an administrator in the chat for this to work and must have the can_pin_messages administrator right in a supergroup or can_edit_messages administrator right in a channel. Returns True on success.

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

answerCallbackQuery :: AnswerCallbackQueryRequest -> ClientM (Response Bool) Source #

Use this method to send answers to callback queries sent from inline keyboards. The answer will be displayed to the user as a notification at the top of the chat screen or as an alert. On success, True is returned.

Alternatively, the user can be redirected to the specified Game URL. For this option to work, you must first create a game for your bot via @Botfather and accept the terms. Otherwise, you may use links like t.me/your_bot?start=XXXX that open your bot with a parameter.

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

setMyCommands :: SetMyCommandsRequest -> ClientM (Response Bool) Source #

Use this method to change the list of the bot's commands. See https://core.telegram.org/bots#commands for more details about bot commands. Returns True on success.

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

deleteMyCommands :: DeleteMyCommandsRequest -> ClientM (Response Bool) Source #

Use this method to delete the list of the bot's commands for the given scope and user language. After deletion, higher level commands will be shown to affected users. Returns True on success.

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

getMyCommands :: GetMyCommandsRequest -> ClientM (Response [BotCommand]) Source #

Use this method to get the current list of the bot's commands for the given scope and user language. Returns Array of BotCommand on success. If commands aren't set, an empty list is returned.

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

setChatMenuButton :: SetChatMenuButtonRequest -> ClientM (Response Bool) Source #

Use this method to change the bot's menu button in a private chat, or the default menu button. Returns True on success.

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

getChatMenuButton :: GetChatMenuButtonRequest -> ClientM (Response MenuButton) Source #

Use this method to get the current value of the bot's menu button in a private chat, or the default menu button. Returns MenuButton on success.

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

setMyDefaultAdministratorRights :: SetMyDefaultAdministratorRightsRequest -> ClientM (Response Bool) Source #

Use this method to change the default administrator rights requested by the bot when it's added as an administrator to groups or channels. These rights will be suggested to users, but they are are free to modify the list before adding the bot. Returns True on success.

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

getMyDefaultAdministratorRights :: GetMyDefaultAdministratorRightsRequest -> ClientM (Response ChatAdministratorRights) Source #

Use this method to get the current default administrator rights of the bot. Returns ChatAdministratorRights on success.