Safe Haskell | None |
---|---|
Language | Haskell2010 |
Telegram.Bot.API.Methods
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 SomeChatId
- data SomeReplyMarkup
- data ParseMode
- = Markdown
- | HTML
- | MarkdownV2
- data SendMessageRequest = SendMessageRequest {}
- 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
- sendDocumentDisableNotification :: Maybe Bool
- sendDocumentReplyToMessageId :: Maybe MessageId
- sendDocumentReplyMarkup :: Maybe SomeReplyMarkup
- data DocumentFile
- type ContentType = Text
- toSendDocument :: SomeChatId -> DocumentFile -> SendDocumentRequest
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 SomeChatId Source #
Unique identifier for the target chat
or username of the target channel (in the format @channelusername
).
Constructors
SomeChatId ChatId | Unique chat ID. |
SomeChatUsername Text | Username of the target channel. |
Instances
Generic SomeChatId Source # | |
Defined in Telegram.Bot.API.Methods Associated Types type Rep SomeChatId :: Type -> Type # | |
FromJSON SomeChatId Source # | |
Defined in Telegram.Bot.API.Methods | |
ToJSON SomeChatId Source # | |
Defined in Telegram.Bot.API.Methods Methods toJSON :: SomeChatId -> Value toEncoding :: SomeChatId -> Encoding toJSONList :: [SomeChatId] -> Value toEncodingList :: [SomeChatId] -> Encoding | |
type Rep SomeChatId Source # | |
Defined in Telegram.Bot.API.Methods type Rep SomeChatId = D1 ('MetaData "SomeChatId" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.3.3-inplace" 'False) (C1 ('MetaCons "SomeChatId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChatId)) :+: C1 ('MetaCons "SomeChatUsername" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
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.
Constructors
SomeInlineKeyboardMarkup InlineKeyboardMarkup | |
SomeReplyKeyboardMarkup ReplyKeyboardMarkup | |
SomeReplyKeyboardRemove ReplyKeyboardRemove | |
SomeForceReply ForceReply |
Instances
Constructors
Markdown | |
HTML | |
MarkdownV2 |
Instances
Generic ParseMode Source # | |
FromJSON ParseMode Source # | |
Defined in Telegram.Bot.API.Methods | |
ToJSON ParseMode Source # | |
Defined in Telegram.Bot.API.Methods 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.3.3-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
data ForwardMessageRequest Source #
Request parameters for forwardMessage
.
Constructors
ForwardMessageRequest | |
Fields
|
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
Constructors
SendDocumentRequest | |
Fields
|
Instances
data DocumentFile Source #
Constructors
DocumentFileId Int | |
DocumentUrl Text | |
DocumentFile FilePath ContentType |
Instances
ToJSON DocumentFile Source # | |
Defined in Telegram.Bot.API.Methods Methods toJSON :: DocumentFile -> Value toEncoding :: DocumentFile -> Encoding toJSONList :: [DocumentFile] -> Value toEncodingList :: [DocumentFile] -> Encoding |
type ContentType = Text Source #
toSendDocument :: SomeChatId -> DocumentFile -> SendDocumentRequest Source #
Generate send document structure.