Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type GetMe = "getMe" :> Get '[JSON] (Response User)
- getMe :: ClientM (Response User)
- type DeleteMessage = "deleteMessage" :> (RequiredQueryParam "chat_id" ChatId :> (RequiredQueryParam "message_id" MessageId :> Get '[JSON] (Response Bool)))
- deleteMessage :: ChatId -> MessageId -> ClientM (Response Bool)
- type SendMessage = "sendMessage" :> (ReqBody '[JSON] SendMessageRequest :> Post '[JSON] (Response Message))
- sendMessage :: SendMessageRequest -> ClientM (Response Message)
- type ForwardMessage = "forwardMessage" :> (ReqBody '[JSON] ForwardMessageRequest :> Post '[JSON] (Response Message))
- forwardMessage :: ForwardMessageRequest -> ClientM (Response Message)
- data SomeReplyMarkup
- data ParseMode
- = Markdown
- | HTML
- | MarkdownV2
- data SendMessageRequest = SendMessageRequest {
- sendMessageChatId :: SomeChatId
- sendMessageText :: Text
- sendMessageParseMode :: Maybe ParseMode
- sendMessageEntities :: Maybe [MessageEntity]
- sendMessageDisableWebPagePreview :: Maybe Bool
- sendMessageDisableNotification :: Maybe Bool
- sendMessageProtectContent :: Maybe Bool
- sendMessageReplyToMessageId :: Maybe MessageId
- sendMessageAllowSendingWithoutReply :: Maybe Bool
- sendMessageReplyMarkup :: Maybe SomeReplyMarkup
- data ForwardMessageRequest = ForwardMessageRequest {}
- type SendDocumentContent = "sendDocument" :> (MultipartForm Tmp SendDocumentRequest :> Post '[JSON] (Response Message))
- type SendDocumentLink = "sendDocument" :> (ReqBody '[JSON] SendDocumentRequest :> Post '[JSON] (Response Message))
- sendDocument :: SendDocumentRequest -> ClientM (Response Message)
- data SendDocumentRequest = SendDocumentRequest {
- sendDocumentChatId :: SomeChatId
- sendDocumentDocument :: DocumentFile
- sendDocumentThumb :: Maybe FilePath
- sendDocumentCaption :: Maybe Text
- sendDocumentParseMode :: Maybe ParseMode
- sendDocumentCaptionEntities :: Maybe [MessageEntity]
- sendDocumentDisableContentTypeDetection :: Maybe Bool
- sendDocumentDisableNotification :: Maybe Bool
- sendDocumentProtectContent :: Maybe Bool
- sendDocumentReplyToMessageId :: Maybe MessageId
- sendDocumentAllowSendingWithoutReply :: Maybe Bool
- sendDocumentReplyMarkup :: Maybe SomeReplyMarkup
- newtype DocumentFile = MakeDocumentFile InputFile
- pattern DocumentFileId :: FileId -> DocumentFile
- pattern DocumentUrl :: Text -> DocumentFile
- pattern DocumentFile :: FilePath -> ContentType -> DocumentFile
- toSendDocument :: SomeChatId -> DocumentFile -> SendDocumentRequest
- type GetFile = "getFile" :> (RequiredQueryParam "file_id" FileId :> Get '[JSON] (Response File))
- getFile :: FileId -> ClientM (Response File)
- type SendPhotoContent = "sendPhoto" :> (MultipartForm Tmp SendPhotoRequest :> Post '[JSON] (Response Message))
- type SendPhotoLink = "sendPhoto" :> (ReqBody '[JSON] SendPhotoRequest :> Post '[JSON] (Response Message))
- newtype PhotoFile = MakePhotoFile InputFile
- pattern PhotoFileId :: FileId -> PhotoFile
- pattern PhotoUrl :: Text -> PhotoFile
- pattern PhotoFile :: FilePath -> ContentType -> PhotoFile
- data SendPhotoRequest = SendPhotoRequest {
- sendPhotoChatId :: SomeChatId
- sendPhotoPhoto :: PhotoFile
- sendPhotoThumb :: Maybe FilePath
- sendPhotoCaption :: Maybe Text
- sendPhotoParseMode :: Maybe ParseMode
- sendPhotoCaptionEntities :: Maybe [MessageEntity]
- sendPhotoDisableNotification :: Maybe Bool
- sendPhotoProtectContent :: Maybe Bool
- sendPhotoReplyToMessageId :: Maybe MessageId
- sendPhotoAllowSendingWithoutReply :: Maybe Bool
- sendPhotoReplyMarkup :: Maybe SomeReplyMarkup
- sendPhoto :: SendPhotoRequest -> ClientM (Response Message)
- data CopyMessageRequest = CopyMessageRequest {
- copyMessageChatId :: SomeChatId
- copyMessageFromChatId :: SomeChatId
- copyMessageMessageId :: MessageId
- copyMessageCaption :: Maybe Text
- copyMessageParseMode :: Maybe ParseMode
- copyMessageCaptionEntities :: Maybe [MessageEntity]
- copyMessageDisableNotification :: Maybe Bool
- copyMessageProtectContent :: Maybe Bool
- copyMessageReplyToMessageId :: Maybe MessageId
- copyMessageAllowSendingWithoutReply :: Maybe Bool
- copyMessageReplyMarkup :: Maybe InlineKeyboardMarkup
- data SendAudioRequest = SendAudioRequest {
- sendAudioChatId :: SomeChatId
- sendAudioAudio :: InputFile
- sendAudioDuration :: Maybe Int
- sendAudioPerformer :: Maybe Text
- sendAudioTitle :: Maybe Text
- sendAudioThumb :: Maybe InputFile
- sendAudioCaption :: Maybe Text
- sendAudioParseMode :: Maybe ParseMode
- sendAudioCaptionEntities :: Maybe [MessageEntity]
- sendAudioDisableNotification :: Maybe Bool
- sendAudioProtectContent :: Maybe Bool
- sendAudioReplyToMessageId :: Maybe MessageId
- sendAudioAllowSendingWithoutReply :: Maybe Bool
- sendAudioReplyMarkup :: Maybe InlineKeyboardMarkup
- type SendAudioContent = "sendAudio" :> (MultipartForm Tmp SendAudioRequest :> Post '[JSON] (Response Message))
- type SendAudioLink = "sendAudio" :> (ReqBody '[JSON] SendAudioRequest :> Post '[JSON] (Response Message))
- sendAudio :: SendAudioRequest -> ClientM (Response Message)
- data SendVideoRequest = SendVideoRequest {
- sendVideoChatId :: SomeChatId
- sendVideoVideo :: InputFile
- sendVideoDuration :: Maybe Int
- sendVideoWidth :: Maybe Int
- sendVideoHeight :: Maybe Int
- sendVideoThumb :: Maybe InputFile
- sendVideoCaption :: Maybe Text
- sendVideoParseMode :: Maybe ParseMode
- sendVideoCaptionEntities :: Maybe [MessageEntity]
- sendVideoSupportsStreaming :: Maybe Bool
- sendVideoDisableNotification :: Maybe Bool
- sendVideoProtectContent :: Maybe Bool
- sendVideoReplyToMessageId :: Maybe MessageId
- sendVideoAllowSendingWithoutReply :: Maybe Bool
- sendVideoReplyMarkup :: Maybe InlineKeyboardMarkup
- type SendVideoContent = "sendVideo" :> (MultipartForm Tmp SendVideoRequest :> Post '[JSON] (Response Message))
- type SendVideoLink = "sendVideo" :> (ReqBody '[JSON] SendVideoRequest :> Post '[JSON] (Response Message))
- sendVideo :: SendVideoRequest -> ClientM (Response Message)
- data SendAnimationRequest = SendAnimationRequest {
- sendAnimationChatId :: SomeChatId
- sendAnimationAnimation :: InputFile
- sendAnimationDuration :: Maybe Int
- sendAnimationWidth :: Maybe Int
- sendAnimationHeight :: Maybe Int
- sendAnimationThumb :: Maybe InputFile
- sendAnimationCaption :: Maybe Text
- sendAnimationParseMode :: Maybe ParseMode
- sendAnimationCaptionEntities :: Maybe [MessageEntity]
- sendAnimationDisableNotification :: Maybe Bool
- sendAnimationProtectContent :: Maybe Bool
- sendAnimationReplyToMessageId :: Maybe MessageId
- sendAnimationAllowSendingWithoutReply :: Maybe Bool
- sendAnimationReplyMarkup :: Maybe InlineKeyboardMarkup
- type SendAnimationContent = "sendAnimation" :> (MultipartForm Tmp SendAnimationRequest :> Post '[JSON] (Response Message))
- type SendAnimationLink = "sendAnimation" :> (ReqBody '[JSON] SendAnimationRequest :> Post '[JSON] (Response Message))
- sendAnimation :: SendAnimationRequest -> ClientM (Response Message)
- data SendVoiceRequest = SendVoiceRequest {
- sendVoiceChatId :: SomeChatId
- sendVoiceVoice :: InputFile
- sendVoiceCaption :: Maybe Text
- sendVoiceParseMode :: Maybe ParseMode
- sendVoiceCaptionEntities :: Maybe [MessageEntity]
- sendVoiceDuration :: Maybe Int
- sendVoiceDisableNotification :: Maybe Bool
- sendVoiceProtectContent :: Maybe Bool
- sendVoiceReplyToMessageId :: Maybe MessageId
- sendVoiceAllowSendingWithoutReply :: Maybe Bool
- sendVoiceReplyMarkup :: Maybe InlineKeyboardMarkup
- type SendVoiceContent = "sendVoice" :> (MultipartForm Tmp SendVoiceRequest :> Post '[JSON] (Response Message))
- type SendVoiceLink = "sendVoice" :> (ReqBody '[JSON] SendVoiceRequest :> Post '[JSON] (Response Message))
- sendVoice :: SendVoiceRequest -> ClientM (Response Message)
- data SendVideoNoteRequest = SendVideoNoteRequest {
- sendVideoNoteChatId :: SomeChatId
- sendVideoNoteVideoNote :: InputFile
- sendVideoNoteDuration :: Maybe Int
- sendVideoNoteLength :: Maybe Int
- sendVideoNoteThumb :: Maybe InputFile
- sendVideoNoteDisableNotification :: Maybe Bool
- sendVideoNoteProtectContent :: Maybe Bool
- sendVideoNoteReplyToMessageId :: Maybe MessageId
- sendVideoNoteAllowSendingWithoutReply :: Maybe Bool
- sendVideoNoteReplyMarkup :: Maybe InlineKeyboardMarkup
- type SendVideoNoteContent = "sendVideoNote" :> (MultipartForm Tmp SendVideoNoteRequest :> Post '[JSON] (Response Message))
- type SendVideoNoteLink = "sendVideoNote" :> (ReqBody '[JSON] SendVideoNoteRequest :> Post '[JSON] (Response Message))
- sendVideoNote :: SendVideoNoteRequest -> ClientM (Response Message)
- data SendMediaGroupRequest = SendMediaGroupRequest {
- sendMediaGroupChatId :: SomeChatId
- sendMediaGroupMedia :: [InputMedia]
- sendMediaGroupDisableNotification :: Maybe Bool
- sendMediaGroupProtectContent :: Maybe Bool
- sendMediaGroupReplyToMessageId :: Maybe MessageId
- sendMediaGroupAllowSendingWithoutReply :: Maybe Bool
- sendMediaGroupReplyMarkup :: Maybe InlineKeyboardMarkup
- type SendMediaGroup = "sendMediaGroup" :> (ReqBody '[JSON] SendMediaGroupRequest :> Post '[JSON] (Response [Message]))
- sendMediaGroup :: SendMediaGroupRequest -> ClientM (Response [Message])
- data SendLocationRequest = SendLocationRequest {
- sendLocationChatId :: SomeChatId
- sendLocationLatitude :: Float
- sendLocationLongitude :: Float
- sendLocationHorizontalAccuracy :: Maybe Float
- sendLocationLivePeriod :: Int
- sendLocationHeading :: Maybe Int
- sendLocationProximityAlertRadius :: Maybe Int
- sendLocationDisableNotification :: Maybe Bool
- sendLocationProtectContent :: Maybe Bool
- sendLocationReplyToMessageId :: Maybe MessageId
- sendLocationAllowSendingWithoutReply :: Maybe Bool
- sendLocationReplyMarkup :: Maybe InlineKeyboardMarkup
- data EditMessageLiveLocationRequest = EditMessageLiveLocationRequest {
- editMessageLiveLocationChatId :: Maybe SomeChatId
- editMessageLiveLocationMessageId :: Maybe MessageId
- editMessageLiveLocationInlineMessageId :: Maybe Text
- editMessageLiveLocationLatitude :: Float
- editMessageLiveLocationLongitude :: Float
- editMessageLiveLocationHorizontalAccuracy :: Maybe Float
- editMessageLiveLocationHeading :: Maybe Int
- editMessageLiveLocationProximityAlertRadius :: Maybe Int
- editMessageLiveLocationReplyMarkup :: Maybe InlineKeyboardMarkup
- data StopMessageLiveLocationRequest = StopMessageLiveLocationRequest {}
- data SendVenueRequest = SendVenueRequest {
- sendVenueChatId :: SomeChatId
- sendVenueLatitude :: Float
- sendVenueLongitude :: Float
- sendVenueTitle :: Text
- sendVenueAddress :: Text
- sendVenueFoursquareId :: Maybe Text
- sendVenueFoursquareType :: Maybe Text
- sendVenueGooglePlaceId :: Maybe Text
- sendVenueGooglePlaceType :: Maybe Text
- sendVenueDisableNotification :: Maybe Bool
- sendVenueProtectContent :: Maybe Bool
- sendVenueReplyToMessageId :: Maybe MessageId
- sendVenueAllowSendingWithoutReply :: Maybe Bool
- sendVenueReplyMarkup :: Maybe InlineKeyboardMarkup
- data SendContactRequest = SendContactRequest {
- sendContactChatId :: SomeChatId
- sendContactPhoneNumber :: Text
- sendContactFirstName :: Text
- sendContactLastName :: Text
- sendContactVcard :: Text
- sendContactDisableNotification :: Maybe Bool
- sendContactProtectContent :: Maybe Bool
- sendContactReplyToMessageId :: Maybe MessageId
- sendContactAllowSendingWithoutReply :: Maybe Bool
- sendContactReplyMarkup :: Maybe InlineKeyboardMarkup
- data SendPollRequest = SendPollRequest {
- sendPollChatId :: SomeChatId
- sendPollQuestion :: Text
- sendPollOptions :: [Text]
- sendPollIsAnonymous :: Maybe Bool
- sendPollType :: Maybe Text
- sendPollAllowsMultipleAnswers :: Maybe Bool
- sendPollCorrectOptionId :: Maybe Int
- sendPollExplanation :: Maybe Text
- sendPollExplanationParseMode :: Maybe ParseMode
- sendPollExplanationEntities :: Maybe [MessageEntity]
- sendPollOpenPeriod :: Maybe Int
- sendPollCloseDate :: Maybe Int
- sendPollIsClosed :: Maybe Bool
- sendPollDisableNotification :: Maybe Bool
- sendPollProtectContent :: Maybe Bool
- sendPollReplyToMessageId :: Maybe MessageId
- sendPollAllowSendingWithoutReply :: Maybe Bool
- sendPollReplyMarkup :: Maybe InlineKeyboardMarkup
- data SendDiceRequest = SendDiceRequest {}
- type SendChatAction = "sendChatAction" :> (RequiredQueryParam "chat_id" SomeChatId :> (RequiredQueryParam "action" Text :> Post '[JSON] (Response Bool)))
- sendChatAction :: SomeChatId -> Text -> ClientM (Response Bool)
- data GetUserProfilePhotosRequest = GetUserProfilePhotosRequest {}
- data BanChatMemberRequest = BanChatMemberRequest {}
- data UnbanChatMemberRequest = UnbanChatMemberRequest {}
- data RestrictChatMemberRequest = RestrictChatMemberRequest {}
- data PromoteChatMemberRequest = PromoteChatMemberRequest {
- promoteChatMemberChatId :: SomeChatId
- promoteChatMemberUserId :: UserId
- promoteChatMemberIsAnonymous :: Maybe Bool
- promoteChatMemberCanManageChat :: Maybe Bool
- promoteChatMemberCanPostMessages :: Maybe Bool
- promoteChatMemberCanEditMessages :: Maybe Bool
- promoteChatMemberCanDeleteMessages :: Maybe Bool
- promoteChatMemberCanManageVideoChats :: Maybe Bool
- promoteChatMemberCanRestrictMembers :: Maybe Bool
- promoteChatMemberCanPromoteMembers :: Maybe Bool
- promoteChatMemberCanChangeInfo :: Maybe Bool
- promoteChatMemberCanInviteUsers :: Maybe Bool
- promoteChatMemberCanPinMessages :: Maybe Bool
- data SetChatAdministratorCustomTitleRequest = SetChatAdministratorCustomTitleRequest {}
- type BanChatSenderChat = "banChatSenderChat" :> (RequiredQueryParam "chat_id" SomeChatId :> (RequiredQueryParam "sender_chat_id" ChatId :> Post '[JSON] (Response Bool)))
- banChatSenderChat :: SomeChatId -> ChatId -> ClientM (Response Bool)
- type UnbanChatSenderChat = "unbanChatSenderChat" :> (RequiredQueryParam "chat_id" SomeChatId :> (RequiredQueryParam "sender_chat_id" ChatId :> Post '[JSON] (Response Bool)))
- unbanChatSenderChat :: SomeChatId -> ChatId -> ClientM (Response Bool)
- data SetChatPermissionsRequest = SetChatPermissionsRequest {}
- type ExportChatInviteLink = "exportChatInviteLink" :> (RequiredQueryParam "chat_id" SomeChatId :> Post '[JSON] (Response Text))
- exportChatInviteLink :: SomeChatId -> ClientM (Response Text)
- data CreateChatInviteLinkRequest = CreateChatInviteLinkRequest {}
- data EditChatInviteLinkRequest = EditChatInviteLinkRequest {}
- type RevokeChatInviteLink = "revokeChatInviteLink" :> (RequiredQueryParam "chat_id" SomeChatId :> (RequiredQueryParam "invite_link" Text :> Post '[JSON] (Response ChatInviteLink)))
- revokeChatInviteLink :: SomeChatId -> Text -> ClientM (Response ChatInviteLink)
- type ApproveChatJoinRequest = "approveChatJoinRequest" :> (RequiredQueryParam "chat_id" SomeChatId :> (RequiredQueryParam "user_id" UserId :> Post '[JSON] (Response Bool)))
- approveChatJoinRequest :: SomeChatId -> UserId -> ClientM (Response Bool)
- type DeclineChatJoinRequest = "declineChatJoinRequest" :> (RequiredQueryParam "chat_id" SomeChatId :> (RequiredQueryParam "user_id" UserId :> Post '[JSON] (Response Bool)))
- declineChatJoinRequest :: SomeChatId -> UserId -> ClientM (Response Bool)
- data SetChatPhotoRequest = SetChatPhotoRequest {}
- type SetChatPhoto = "setChatPhoto" :> (MultipartForm Tmp SetChatPhotoRequest :> Post '[JSON] (Response Bool))
- setChatPhoto :: SetChatPhotoRequest -> ClientM (Response Bool)
- type DeleteChatPhoto = "deleteChatPhoto" :> (RequiredQueryParam "chat_id" SomeChatId :> Post '[JSON] (Response Bool))
- deleteChatPhoto :: SomeChatId -> ClientM (Response Bool)
- type SetChatTitle = "setChatTitle" :> (RequiredQueryParam "chat_id" SomeChatId :> (RequiredQueryParam "title" Text :> Post '[JSON] (Response Bool)))
- setChatTitle :: SomeChatId -> Text -> ClientM (Response Bool)
- type SetChatDescription = "setChatDescription" :> (RequiredQueryParam "chat_id" SomeChatId :> (QueryParam "description" Text :> Post '[JSON] (Response Bool)))
- setChatDescription :: SomeChatId -> Maybe Text -> ClientM (Response Bool)
- data PinChatMessageRequest = PinChatMessageRequest {}
- type UnpinChatMessage = "unpinChatMessage" :> (RequiredQueryParam "chat_id" SomeChatId :> (QueryParam "message_id" MessageId :> Post '[JSON] (Response Bool)))
- unpinChatMessage :: SomeChatId -> Maybe MessageId -> ClientM (Response Bool)
- type UnpinAllChatMessages = "unpinAllChatMessages" :> (RequiredQueryParam "chat_id" SomeChatId :> Post '[JSON] (Response Bool))
- unpinAllChatMessages :: SomeChatId -> ClientM (Response Bool)
- type LeaveChat = "leaveChat" :> (RequiredQueryParam "chat_id" SomeChatId :> Post '[JSON] (Response Bool))
- leaveChat :: SomeChatId -> ClientM (Response Bool)
- type GetChat = "getChat" :> (RequiredQueryParam "chat_id" SomeChatId :> Post '[JSON] (Response Chat))
- getChat :: SomeChatId -> ClientM (Response Chat)
- type GetChatAdministrators = "getChatAdministrators" :> (RequiredQueryParam "chat_id" SomeChatId :> Post '[JSON] (Response [ChatMember]))
- getChatAdministrators :: SomeChatId -> ClientM (Response [ChatMember])
- type GetChatMemberCount = "getChatMemberCount" :> (RequiredQueryParam "chat_id" SomeChatId :> Post '[JSON] (Response Integer))
- getChatMemberCount :: SomeChatId -> ClientM (Response Integer)
- type GetChatMember = "getChatMember" :> (RequiredQueryParam "chat_id" SomeChatId :> (RequiredQueryParam "user_id" UserId :> Post '[JSON] (Response ChatMember)))
- getChatMember :: SomeChatId -> UserId -> ClientM (Response ChatMember)
- type SetChatStickerSet = "setChatStickerSet" :> (RequiredQueryParam "chat_id" SomeChatId :> (RequiredQueryParam "sticker_set_name" Text :> Post '[JSON] (Response Bool)))
- setChatStickerSet :: SomeChatId -> Text -> ClientM (Response Bool)
- type DeleteChatStickerSet = "deleteChatStickerSet" :> (RequiredQueryParam "chat_id" SomeChatId :> Post '[JSON] (Response Bool))
- deleteChatStickerSet :: SomeChatId -> ClientM (Response Bool)
- data AnswerCallbackQueryRequest = AnswerCallbackQueryRequest {}
- data SetMyCommandsRequest = SetMyCommandsRequest {}
- data DeleteMyCommandsRequest = DeleteMyCommandsRequest {}
- data GetMyCommandsRequest = GetMyCommandsRequest {}
- data SetChatMenuButtonRequest = SetChatMenuButtonRequest {}
- data GetChatMenuButtonRequest = GetChatMenuButtonRequest {}
- data SetMyDefaultAdministratorRightsRequest = SetMyDefaultAdministratorRightsRequest {}
- data GetMyDefaultAdministratorRightsRequest = GetMyDefaultAdministratorRightsRequest {}
- type CopyMessage = "copyMessage" :> (ReqBody '[JSON] CopyMessageRequest :> Post '[JSON] (Response CopyMessageId))
- copyMessage :: CopyMessageRequest -> ClientM (Response CopyMessageId)
- type SendLocation = "sendLocation" :> (ReqBody '[JSON] SendLocationRequest :> Post '[JSON] (Response Message))
- sendLocation :: SendLocationRequest -> ClientM (Response Message)
- type EditMessageLiveLocation = "editMessageLiveLocation" :> (ReqBody '[JSON] EditMessageLiveLocationRequest :> Post '[JSON] (Response (Either Bool Message)))
- editMessageLiveLocation :: EditMessageLiveLocationRequest -> ClientM (Response (Either Bool Message))
- type StopMessageLiveLocation = "stopMessageLiveLocation" :> (ReqBody '[JSON] StopMessageLiveLocationRequest :> Post '[JSON] (Response (Either Bool Message)))
- stopMessageLiveLocation :: StopMessageLiveLocationRequest -> ClientM (Response (Either Bool Message))
- type SendVenue = "sendVenue" :> (ReqBody '[JSON] SendVenueRequest :> Post '[JSON] (Response Message))
- sendVenue :: SendVenueRequest -> ClientM (Response Message)
- type SendContact = "sendContact" :> (ReqBody '[JSON] SendContactRequest :> Post '[JSON] (Response Message))
- sendContact :: SendContactRequest -> ClientM (Response Message)
- type SendPoll = "sendPoll" :> (ReqBody '[JSON] SendPollRequest :> Post '[JSON] (Response Message))
- sendPoll :: SendPollRequest -> ClientM (Response Message)
- type SendDice = "sendDice" :> (ReqBody '[JSON] SendDiceRequest :> Post '[JSON] (Response Message))
- sendDice :: SendDiceRequest -> ClientM (Response Message)
- type GetUserProfilePhotos = "getUserProfilePhotos" :> (ReqBody '[JSON] GetUserProfilePhotosRequest :> Post '[JSON] (Response UserProfilePhotos))
- getUserProfilePhotos :: GetUserProfilePhotosRequest -> ClientM (Response UserProfilePhotos)
- type BanChatMember = "banChatMember" :> (ReqBody '[JSON] BanChatMemberRequest :> Post '[JSON] (Response Bool))
- banChatMember :: BanChatMemberRequest -> ClientM (Response Bool)
- type UnbanChatMember = "unbanChatMember" :> (ReqBody '[JSON] UnbanChatMemberRequest :> Post '[JSON] (Response Bool))
- unbanChatMember :: UnbanChatMemberRequest -> ClientM (Response Bool)
- type RestrictChatMember = "restrictChatMember" :> (ReqBody '[JSON] RestrictChatMemberRequest :> Post '[JSON] (Response Bool))
- restrictChatMember :: RestrictChatMemberRequest -> ClientM (Response Bool)
- type PromoteChatMember = "promoteChatMember" :> (ReqBody '[JSON] PromoteChatMemberRequest :> Post '[JSON] (Response Bool))
- promoteChatMember :: PromoteChatMemberRequest -> ClientM (Response Bool)
- type SetChatAdministratorCustomTitle = "setChatAdministratorCustomTitle" :> (ReqBody '[JSON] SetChatAdministratorCustomTitleRequest :> Post '[JSON] (Response Bool))
- setChatAdministratorCustomTitle :: SetChatAdministratorCustomTitleRequest -> ClientM (Response Bool)
- type SetChatPermissions = "setChatPermissions" :> (ReqBody '[JSON] SetChatPermissionsRequest :> Post '[JSON] (Response Bool))
- setChatPermissions :: SetChatPermissionsRequest -> ClientM (Response Bool)
- type CreateChatInviteLink = "createChatInviteLink" :> (ReqBody '[JSON] CreateChatInviteLinkRequest :> Post '[JSON] (Response ChatInviteLink))
- createChatInviteLink :: CreateChatInviteLinkRequest -> ClientM (Response ChatInviteLink)
- type EditChatInviteLink = "editChatInviteLink" :> (ReqBody '[JSON] EditChatInviteLinkRequest :> Post '[JSON] (Response ChatInviteLink))
- editChatInviteLink :: EditChatInviteLinkRequest -> ClientM (Response ChatInviteLink)
- type PinChatMessage = "pinChatMessage" :> (ReqBody '[JSON] PinChatMessageRequest :> Post '[JSON] (Response Bool))
- pinChatMessage :: PinChatMessageRequest -> ClientM (Response Bool)
- type AnswerCallbackQuery = "answerCallbackQuery" :> (ReqBody '[JSON] AnswerCallbackQueryRequest :> Post '[JSON] (Response Bool))
- answerCallbackQuery :: AnswerCallbackQueryRequest -> ClientM (Response Bool)
- type SetMyCommands = "setMyCommands" :> (ReqBody '[JSON] SetMyCommandsRequest :> Post '[JSON] (Response Bool))
- setMyCommands :: SetMyCommandsRequest -> ClientM (Response Bool)
- type DeleteMyCommands = "deleteMyCommands" :> (ReqBody '[JSON] DeleteMyCommandsRequest :> Post '[JSON] (Response Bool))
- deleteMyCommands :: DeleteMyCommandsRequest -> ClientM (Response Bool)
- type GetMyCommands = "getMyCommands" :> (ReqBody '[JSON] GetMyCommandsRequest :> Post '[JSON] (Response [BotCommand]))
- getMyCommands :: GetMyCommandsRequest -> ClientM (Response [BotCommand])
- type SetChatMenuButton = "setChatMenuButton" :> (ReqBody '[JSON] SetChatMenuButtonRequest :> Post '[JSON] (Response Bool))
- setChatMenuButton :: SetChatMenuButtonRequest -> ClientM (Response Bool)
- type GetChatMenuButton = "getChatMenuButton" :> (ReqBody '[JSON] GetChatMenuButtonRequest :> Post '[JSON] (Response MenuButton))
- getChatMenuButton :: GetChatMenuButtonRequest -> ClientM (Response MenuButton)
- type SetMyDefaultAdministratorRights = "setMyDefaultAdministratorRights" :> (ReqBody '[JSON] SetMyDefaultAdministratorRightsRequest :> Post '[JSON] (Response Bool))
- setMyDefaultAdministratorRights :: SetMyDefaultAdministratorRightsRequest -> ClientM (Response Bool)
- type GetMyDefaultAdministratorRights = "getMyDefaultAdministratorRights" :> (ReqBody '[JSON] GetMyDefaultAdministratorRightsRequest :> Post '[JSON] (Response ChatAdministratorRights))
- getMyDefaultAdministratorRights :: GetMyDefaultAdministratorRightsRequest -> ClientM (Response ChatAdministratorRights)
Available methods
getMe
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.
SomeInlineKeyboardMarkup InlineKeyboardMarkup | |
SomeReplyKeyboardMarkup ReplyKeyboardMarkup | |
SomeReplyKeyboardRemove ReplyKeyboardRemove | |
SomeForceReply ForceReply |
Instances
Instances
Generic ParseMode Source # | |
FromJSON ParseMode Source # | |
Defined in Telegram.Bot.API.Methods parseJSON :: Value -> Parser ParseMode parseJSONList :: Value -> Parser [ParseMode] | |
ToJSON ParseMode Source # | |
Defined in Telegram.Bot.API.Methods toEncoding :: ParseMode -> Encoding toJSONList :: [ParseMode] -> Value toEncodingList :: [ParseMode] -> Encoding | |
type Rep ParseMode Source # | |
Defined in Telegram.Bot.API.Methods type Rep ParseMode = D1 ('MetaData "ParseMode" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.5.2-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
.
SendMessageRequest | |
|
Instances
data ForwardMessageRequest Source #
Request parameters for forwardMessage
.
ForwardMessageRequest | |
|
Instances
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.
data SendDocumentRequest Source #
Request parameters for sendDocument
SendDocumentRequest | |
|
Instances
newtype DocumentFile Source #
Instances
ToJSON DocumentFile Source # | |
Defined in Telegram.Bot.API.Methods toJSON :: DocumentFile -> Value toEncoding :: DocumentFile -> Encoding toJSONList :: [DocumentFile] -> Value toEncodingList :: [DocumentFile] -> Encoding |
pattern DocumentFileId :: FileId -> DocumentFile Source #
pattern DocumentUrl :: Text -> DocumentFile Source #
pattern DocumentFile :: FilePath -> ContentType -> DocumentFile Source #
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 #
Instances
ToJSON PhotoFile Source # | |
Defined in Telegram.Bot.API.Methods toEncoding :: PhotoFile -> Encoding toJSONList :: [PhotoFile] -> Value toEncodingList :: [PhotoFile] -> Encoding |
pattern PhotoFileId :: FileId -> PhotoFile Source #
data SendPhotoRequest Source #
Request parameters for sendPhoto
SendPhotoRequest | |
|
Instances
sendPhoto :: SendPhotoRequest -> ClientM (Response Message) Source #
Use this method to send photos.
On success, the sent Message
is returned.
data CopyMessageRequest Source #
Request parameters for copyMessage
.
CopyMessageRequest | |
|
Instances
data SendAudioRequest Source #
Request parameters for sendAudio
.
SendAudioRequest | |
|
Instances
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
.
SendVideoRequest | |
|
Instances
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
.
SendAnimationRequest | |
|
Instances
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
.
SendVoiceRequest | |
|
Instances
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
.
SendVideoNoteRequest | |
|
Instances
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
.
SendMediaGroupRequest | |
|
Instances
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
.
SendLocationRequest | |
|
Instances
data EditMessageLiveLocationRequest Source #
Request parameters for editMessageLiveLocation
.
EditMessageLiveLocationRequest | |
|
Instances
data StopMessageLiveLocationRequest Source #
Request parameters for stopMessageLiveLocation
.
StopMessageLiveLocationRequest | |
|
Instances
data SendVenueRequest Source #
Request parameters for sendVenue
.
SendVenueRequest | |
|
Instances
data SendContactRequest Source #
Request parameters for sendContact
.
SendContactRequest | |
|
Instances
data SendPollRequest Source #
Request parameters for sendPoll
.
SendPollRequest | |
|
Instances
data SendDiceRequest Source #
Request parameters for sendDice
.
SendDiceRequest | |
|
Instances
type SendChatAction = "sendChatAction" :> (RequiredQueryParam "chat_id" SomeChatId :> (RequiredQueryParam "action" Text :> Post '[JSON] (Response Bool))) Source #
:: 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
.
GetUserProfilePhotosRequest | |
|
Instances
data BanChatMemberRequest Source #
Request parameters for banChatMember
.
BanChatMemberRequest | |
|
Instances
data UnbanChatMemberRequest Source #
Request parameters for unbanChatMember
.
UnbanChatMemberRequest | |
|
Instances
data RestrictChatMemberRequest Source #
Request parameters for restrictChatMember
.
RestrictChatMemberRequest | |
|
Instances
data PromoteChatMemberRequest Source #
Request parameters for promoteChatMember
.
PromoteChatMemberRequest | |
|
Instances
data SetChatAdministratorCustomTitleRequest Source #
Request parameters for setChatAdministratorCustomTitle
.
SetChatAdministratorCustomTitleRequest | |
|
Instances
type BanChatSenderChat = "banChatSenderChat" :> (RequiredQueryParam "chat_id" SomeChatId :> (RequiredQueryParam "sender_chat_id" ChatId :> Post '[JSON] (Response Bool))) Source #
:: 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 #
:: 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
.
SetChatPermissionsRequest | |
|
Instances
type ExportChatInviteLink = "exportChatInviteLink" :> (RequiredQueryParam "chat_id" SomeChatId :> Post '[JSON] (Response Text)) Source #
:: 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
.
CreateChatInviteLinkRequest | |
|
Instances
data EditChatInviteLinkRequest Source #
Request parameters for editChatInviteLink
.
EditChatInviteLinkRequest | |
|
Instances
type RevokeChatInviteLink = "revokeChatInviteLink" :> (RequiredQueryParam "chat_id" SomeChatId :> (RequiredQueryParam "invite_link" Text :> Post '[JSON] (Response ChatInviteLink))) Source #
:: 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 #
:: 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 #
:: 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
.
SetChatPhotoRequest | |
|
Instances
ToMultipart Tmp SetChatPhotoRequest Source # | |
Defined in Telegram.Bot.API.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.
- Note*: Only
InputFile
case might be used inSetChatPhotoRequest
. Rest cases will be rejected by Telegram.
type DeleteChatPhoto = "deleteChatPhoto" :> (RequiredQueryParam "chat_id" SomeChatId :> Post '[JSON] (Response Bool)) Source #
:: 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 #
:: 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 #
:: 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
.
PinChatMessageRequest | |
|
Instances
type UnpinChatMessage = "unpinChatMessage" :> (RequiredQueryParam "chat_id" SomeChatId :> (QueryParam "message_id" MessageId :> Post '[JSON] (Response Bool))) Source #
:: 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 #
:: 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 #
:: 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 #
:: 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 #
:: 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 #
:: 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 #
:: 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 #
:: 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 #
:: 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
.
AnswerCallbackQueryRequest | |
|
Instances
data SetMyCommandsRequest Source #
Request parameters for setMyCommands
.
SetMyCommandsRequest | |
|
Instances
data DeleteMyCommandsRequest Source #
Request parameters for deleteMyCommands
.
DeleteMyCommandsRequest | |
|
Instances
data GetMyCommandsRequest Source #
Request parameters for getMyCommands
.
GetMyCommandsRequest | |
|
Instances
data SetChatMenuButtonRequest Source #
Request parameters for setChatMenuButton
SetChatMenuButtonRequest | |
|
Instances
data GetChatMenuButtonRequest Source #
Request parameters for getChatMenuButton
GetChatMenuButtonRequest | |
|
Instances
data SetMyDefaultAdministratorRightsRequest Source #
Request parameters for setMyDefaultAdministratorRights
SetMyDefaultAdministratorRightsRequest | |
|
Instances
data GetMyDefaultAdministratorRightsRequest Source #
Request parameters for getMyDefaultAdministratorRights
GetMyDefaultAdministratorRightsRequest | |
|
Instances
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.