telegram-bot-simple-0.3.0: Easy to use library for building Telegram bots.

Safe HaskellNone
LanguageHaskell2010

Telegram.Bot.API.Methods

Contents

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.

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 # 
Instance details

Defined in Telegram.Bot.API.Methods

Associated Types

type Rep SomeChatId :: Type -> Type #

FromJSON SomeChatId Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

parseJSON :: Value -> Parser SomeChatId

parseJSONList :: Value -> Parser [SomeChatId]

ToJSON SomeChatId Source # 
Instance details

Defined in Telegram.Bot.API.Methods

Methods

toJSON :: SomeChatId -> Value

toEncoding :: SomeChatId -> Encoding

toJSONList :: [SomeChatId] -> Value

toEncodingList :: [SomeChatId] -> Encoding

type Rep SomeChatId Source # 
Instance details

Defined in Telegram.Bot.API.Methods

type Rep SomeChatId = D1 (MetaData "SomeChatId" "Telegram.Bot.API.Methods" "telegram-bot-simple-0.3.0-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.

Instances
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 
Instances
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.3.0-inplace" False) (C1 (MetaCons "Markdown" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HTML" PrefixI False) (U1 :: Type -> Type))

data SendMessageRequest Source #

Request parameters for sendMessage.

Constructors

SendMessageRequest 

Fields

Instances
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.3.0-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 "sendMessageDisableWebPagePreview") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "sendMessageDisableNotification") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 (MetaSel (Just "sendMessageReplyToMessageId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe MessageId)) :*: S1 (MetaSel (Just "sendMessageReplyMarkup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SomeReplyMarkup))))))