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

Telegram.Bot.API.Types

Synopsis

Documentation

type RequiredQueryParam = QueryParam' '[Required, Strict] Source #

newtype Seconds Source #

Constructors

Seconds Int32 

Instances

Instances details
Eq Seconds Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

(==) :: Seconds -> Seconds -> Bool #

(/=) :: Seconds -> Seconds -> Bool #

Num Seconds Source # 
Instance details

Defined in Telegram.Bot.API.Types

Show Seconds Source # 
Instance details

Defined in Telegram.Bot.API.Types

FromJSON Seconds Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser Seconds

parseJSONList :: Value -> Parser [Seconds]

ToJSON Seconds Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: Seconds -> Value

toEncoding :: Seconds -> Encoding

toJSONList :: [Seconds] -> Value

toEncodingList :: [Seconds] -> Encoding

Available types

User

data User Source #

This object represents a Telegram user or bot.

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

Constructors

User 

Fields

Instances

Instances details
Show User Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

showsPrec :: Int -> User -> ShowS #

show :: User -> String #

showList :: [User] -> ShowS #

Generic User Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep User :: Type -> Type #

Methods

from :: User -> Rep User x #

to :: Rep User x -> User #

FromJSON User Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser User

parseJSONList :: Value -> Parser [User]

ToJSON User Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: User -> Value

toEncoding :: User -> Encoding

toJSONList :: [User] -> Value

toEncodingList :: [User] -> Encoding

type Rep User Source # 
Instance details

Defined in Telegram.Bot.API.Types

newtype UserId Source #

Unique identifier for this user or bot.

Constructors

UserId Int32 

Instances

Instances details
Eq UserId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

(==) :: UserId -> UserId -> Bool #

(/=) :: UserId -> UserId -> Bool #

Show UserId Source # 
Instance details

Defined in Telegram.Bot.API.Types

FromJSON UserId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser UserId

parseJSONList :: Value -> Parser [UserId]

ToJSON UserId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: UserId -> Value

toEncoding :: UserId -> Encoding

toJSONList :: [UserId] -> Value

toEncodingList :: [UserId] -> Encoding

ToHttpApiData UserId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Chat

data Chat Source #

This object represents a chat.

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

Constructors

Chat 

Fields

Instances

Instances details
Show Chat Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

showsPrec :: Int -> Chat -> ShowS #

show :: Chat -> String #

showList :: [Chat] -> ShowS #

Generic Chat Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep Chat :: Type -> Type #

Methods

from :: Chat -> Rep Chat x #

to :: Rep Chat x -> Chat #

FromJSON Chat Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser Chat

parseJSONList :: Value -> Parser [Chat]

ToJSON Chat Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: Chat -> Value

toEncoding :: Chat -> Encoding

toJSONList :: [Chat] -> Value

toEncodingList :: [Chat] -> Encoding

type Rep Chat Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep Chat = D1 ('MetaData "Chat" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "Chat" 'PrefixI 'True) (((S1 ('MetaSel ('Just "chatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChatId) :*: (S1 ('MetaSel ('Just "chatType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChatType) :*: S1 ('MetaSel ('Just "chatTitle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))) :*: (S1 ('MetaSel ('Just "chatUsername") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "chatFirstName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "chatLastName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))) :*: ((S1 ('MetaSel ('Just "chatAllMembersAreAdministrators") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: (S1 ('MetaSel ('Just "chatPhoto") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ChatPhoto)) :*: S1 ('MetaSel ('Just "chatDescription") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))) :*: ((S1 ('MetaSel ('Just "chatInviteLink") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "chatPinnedMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Message))) :*: (S1 ('MetaSel ('Just "chatStickerSetName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "chatCanSetStickerSet") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))))))

newtype ChatId Source #

Unique identifier for this chat.

Constructors

ChatId Integer 

Instances

Instances details
Eq ChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

(==) :: ChatId -> ChatId -> Bool #

(/=) :: ChatId -> ChatId -> Bool #

Show ChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types

FromJSON ChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser ChatId

parseJSONList :: Value -> Parser [ChatId]

ToJSON ChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: ChatId -> Value

toEncoding :: ChatId -> Encoding

toJSONList :: [ChatId] -> Value

toEncodingList :: [ChatId] -> Encoding

Hashable ChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

hashWithSalt :: Int -> ChatId -> Int

hash :: ChatId -> Int

ToHttpApiData ChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types

data ChatType Source #

Type of chat.

Instances

Instances details
Show ChatType Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic ChatType Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep ChatType :: Type -> Type #

Methods

from :: ChatType -> Rep ChatType x #

to :: Rep ChatType x -> ChatType #

FromJSON ChatType Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser ChatType

parseJSONList :: Value -> Parser [ChatType]

ToJSON ChatType Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: ChatType -> Value

toEncoding :: ChatType -> Encoding

toJSONList :: [ChatType] -> Value

toEncodingList :: [ChatType] -> Encoding

type Rep ChatType Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep ChatType = D1 ('MetaData "ChatType" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) ((C1 ('MetaCons "ChatTypePrivate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ChatTypeGroup" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ChatTypeSupergroup" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ChatTypeChannel" 'PrefixI 'False) (U1 :: Type -> Type)))

Message

data Message Source #

This object represents a message.

Constructors

Message 

Fields

Instances

Instances details
Show Message Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic Message Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep Message :: Type -> Type #

Methods

from :: Message -> Rep Message x #

to :: Rep Message x -> Message #

FromJSON Message Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser Message

parseJSONList :: Value -> Parser [Message]

ToJSON Message Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: Message -> Value

toEncoding :: Message -> Encoding

toJSONList :: [Message] -> Value

toEncodingList :: [Message] -> Encoding

type Rep Message Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep Message = D1 ('MetaData "Message" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "Message" 'PrefixI 'True) (((((S1 ('MetaSel ('Just "messageMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MessageId) :*: S1 ('MetaSel ('Just "messageFrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe User))) :*: (S1 ('MetaSel ('Just "messageDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime) :*: S1 ('MetaSel ('Just "messageChat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Chat))) :*: ((S1 ('MetaSel ('Just "messageForwardFrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe User)) :*: S1 ('MetaSel ('Just "messageForwardFromChat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Chat))) :*: (S1 ('MetaSel ('Just "messageForwardFromMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId)) :*: (S1 ('MetaSel ('Just "messageForwardSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "messageForwardDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime)))))) :*: (((S1 ('MetaSel ('Just "messageReplyToMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Message)) :*: S1 ('MetaSel ('Just "messageEditDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime))) :*: (S1 ('MetaSel ('Just "messageMediaGroupId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MediaGroupId)) :*: S1 ('MetaSel ('Just "messageAuthorSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))) :*: ((S1 ('MetaSel ('Just "messageText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "messageEntities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [MessageEntity]))) :*: (S1 ('MetaSel ('Just "messageCaptionEntities") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [MessageEntity])) :*: (S1 ('MetaSel ('Just "messageAudio") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Audio)) :*: S1 ('MetaSel ('Just "messageDocument") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Document))))))) :*: ((((S1 ('MetaSel ('Just "messagePhoto") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PhotoSize])) :*: S1 ('MetaSel ('Just "messageVideo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Video))) :*: (S1 ('MetaSel ('Just "messageVoice") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Voice)) :*: S1 ('MetaSel ('Just "messageVideoNote") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe VideoNote)))) :*: ((S1 ('MetaSel ('Just "messageCaption") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "messageContact") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Contact))) :*: (S1 ('MetaSel ('Just "messageLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Location)) :*: (S1 ('MetaSel ('Just "messageVenue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Venue)) :*: S1 ('MetaSel ('Just "messageNewChatMembers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [User])))))) :*: (((S1 ('MetaSel ('Just "messageLeftChatMember") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe User)) :*: S1 ('MetaSel ('Just "messageNewChatTitle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "messageNewChatPhoto") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PhotoSize])) :*: (S1 ('MetaSel ('Just "messageDeleteChatPhoto") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "messageGroupChatCreated") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))) :*: ((S1 ('MetaSel ('Just "messageSupergroupChatCreated") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "messageChannelChatCreated") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "messageMigrateToChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ChatId)) :*: (S1 ('MetaSel ('Just "messageMigrateFromChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ChatId)) :*: S1 ('MetaSel ('Just "messagePinnedMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Message)))))))))

newtype MessageId Source #

Unique message identifier inside this chat.

Constructors

MessageId Int32 

Instances

Instances details
Eq MessageId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Show MessageId Source # 
Instance details

Defined in Telegram.Bot.API.Types

FromJSON MessageId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser MessageId

parseJSONList :: Value -> Parser [MessageId]

ToJSON MessageId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: MessageId -> Value

toEncoding :: MessageId -> Encoding

toJSONList :: [MessageId] -> Value

toEncodingList :: [MessageId] -> Encoding

ToHttpApiData MessageId Source # 
Instance details

Defined in Telegram.Bot.API.Types

newtype MediaGroupId Source #

The unique identifier of a media message group a message belongs to.

Constructors

MediaGroupId Text 

Instances

Instances details
Eq MediaGroupId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Show MediaGroupId Source # 
Instance details

Defined in Telegram.Bot.API.Types

FromJSON MediaGroupId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser MediaGroupId

parseJSONList :: Value -> Parser [MediaGroupId]

ToJSON MediaGroupId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: MediaGroupId -> Value

toEncoding :: MediaGroupId -> Encoding

toJSONList :: [MediaGroupId] -> Value

toEncodingList :: [MediaGroupId] -> Encoding

MessageEntity

data MessageEntity Source #

This object represents one special entity in a text message. For example, hashtags, usernames, URLs, etc.

Constructors

MessageEntity 

Fields

  • messageEntityType :: MessageEntityType

    Type of the entity. Can be mention (@username), hashtag, bot_command, url, email, bold (bold text), italic (italic text), underline (underlined text), strikethrough, code (monowidth string), pre (monowidth block), text_link (for clickable text URLs), text_mention (for users without usernames)

  • messageEntityOffset :: Int32

    Offset in UTF-16 code units to the start of the entity

  • messageEntityLength :: Int32

    Length of the entity in UTF-16 code units

  • messageEntityUrl :: Maybe Text

    For “text_link” only, url that will be opened after user taps on the text

  • messageEntityUser :: Maybe User

    For “text_mention” only, the mentioned user

Instances

Instances details
Show MessageEntity Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic MessageEntity Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep MessageEntity :: Type -> Type #

FromJSON MessageEntity Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser MessageEntity

parseJSONList :: Value -> Parser [MessageEntity]

ToJSON MessageEntity Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: MessageEntity -> Value

toEncoding :: MessageEntity -> Encoding

toJSONList :: [MessageEntity] -> Value

toEncodingList :: [MessageEntity] -> Encoding

type Rep MessageEntity Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep MessageEntity = D1 ('MetaData "MessageEntity" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "MessageEntity" 'PrefixI 'True) ((S1 ('MetaSel ('Just "messageEntityType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MessageEntityType) :*: S1 ('MetaSel ('Just "messageEntityOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32)) :*: (S1 ('MetaSel ('Just "messageEntityLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32) :*: (S1 ('MetaSel ('Just "messageEntityUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "messageEntityUser") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe User))))))

data MessageEntityType Source #

Type of the entity. Can be mention (@username), hashtag, bot_command, url, email, bold (bold text), italic (italic text), underline (underlined text), strikethrough, code (monowidth string), pre (monowidth block), text_link (for clickable text URLs), text_mention (for users without usernames), cashtag, phone_number

Instances

Instances details
Eq MessageEntityType Source # 
Instance details

Defined in Telegram.Bot.API.Types

Show MessageEntityType Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic MessageEntityType Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep MessageEntityType :: Type -> Type #

FromJSON MessageEntityType Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser MessageEntityType

parseJSONList :: Value -> Parser [MessageEntityType]

ToJSON MessageEntityType Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep MessageEntityType Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep MessageEntityType = D1 ('MetaData "MessageEntityType" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (((C1 ('MetaCons "MessageEntityMention" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MessageEntityHashtag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MessageEntityBotCommand" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MessageEntityUrl" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MessageEntityEmail" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MessageEntityBold" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MessageEntityItalic" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "MessageEntityUnderline" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MessageEntityStrikethrough" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MessageEntityCode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MessageEntityPre" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MessageEntityTextLink" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MessageEntityTextMention" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MessageEntityCashtag" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MessageEntityPhoneNumber" 'PrefixI 'False) (U1 :: Type -> Type)))))

PhotoSize

data PhotoSize Source #

This object represents one size of a photo or a file / sticker thumbnail.

Constructors

PhotoSize 

Fields

Instances

Instances details
Show PhotoSize Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic PhotoSize Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep PhotoSize :: Type -> Type #

FromJSON PhotoSize Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser PhotoSize

parseJSONList :: Value -> Parser [PhotoSize]

ToJSON PhotoSize Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: PhotoSize -> Value

toEncoding :: PhotoSize -> Encoding

toJSONList :: [PhotoSize] -> Value

toEncodingList :: [PhotoSize] -> Encoding

type Rep PhotoSize Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep PhotoSize = D1 ('MetaData "PhotoSize" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "PhotoSize" 'PrefixI 'True) ((S1 ('MetaSel ('Just "photoSizeFileId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FileId) :*: S1 ('MetaSel ('Just "photoSizeWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32)) :*: (S1 ('MetaSel ('Just "photoSizeHeight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32) :*: S1 ('MetaSel ('Just "photoSizeFileSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int32)))))

newtype FileId Source #

Unique identifier for this file.

Constructors

FileId Text 

Instances

Instances details
Eq FileId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

(==) :: FileId -> FileId -> Bool #

(/=) :: FileId -> FileId -> Bool #

Show FileId Source # 
Instance details

Defined in Telegram.Bot.API.Types

FromJSON FileId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser FileId

parseJSONList :: Value -> Parser [FileId]

ToJSON FileId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: FileId -> Value

toEncoding :: FileId -> Encoding

toJSONList :: [FileId] -> Value

toEncodingList :: [FileId] -> Encoding

Audio

data Audio Source #

This object represents an audio file to be treated as music by the Telegram clients.

Constructors

Audio 

Fields

Instances

Instances details
Show Audio Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

showsPrec :: Int -> Audio -> ShowS #

show :: Audio -> String #

showList :: [Audio] -> ShowS #

Generic Audio Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep Audio :: Type -> Type #

Methods

from :: Audio -> Rep Audio x #

to :: Rep Audio x -> Audio #

FromJSON Audio Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser Audio

parseJSONList :: Value -> Parser [Audio]

ToJSON Audio Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: Audio -> Value

toEncoding :: Audio -> Encoding

toJSONList :: [Audio] -> Value

toEncodingList :: [Audio] -> Encoding

type Rep Audio Source # 
Instance details

Defined in Telegram.Bot.API.Types

Document

data Document Source #

This object represents a general file (as opposed to photos, voice messages and audio files).

Constructors

Document 

Fields

Instances

Instances details
Show Document Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic Document Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep Document :: Type -> Type #

Methods

from :: Document -> Rep Document x #

to :: Rep Document x -> Document #

FromJSON Document Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser Document

parseJSONList :: Value -> Parser [Document]

ToJSON Document Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: Document -> Value

toEncoding :: Document -> Encoding

toJSONList :: [Document] -> Value

toEncodingList :: [Document] -> Encoding

type Rep Document Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep Document = D1 ('MetaData "Document" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "Document" 'PrefixI 'True) ((S1 ('MetaSel ('Just "documentFileId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FileId) :*: S1 ('MetaSel ('Just "documentThumb") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PhotoSize))) :*: (S1 ('MetaSel ('Just "documentFileName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "documentMimeType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "documentFileSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int32))))))

Video

data Video Source #

This object represents a video file.

Constructors

Video 

Fields

Instances

Instances details
Show Video Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

showsPrec :: Int -> Video -> ShowS #

show :: Video -> String #

showList :: [Video] -> ShowS #

Generic Video Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep Video :: Type -> Type #

Methods

from :: Video -> Rep Video x #

to :: Rep Video x -> Video #

FromJSON Video Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser Video

parseJSONList :: Value -> Parser [Video]

ToJSON Video Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: Video -> Value

toEncoding :: Video -> Encoding

toJSONList :: [Video] -> Value

toEncodingList :: [Video] -> Encoding

type Rep Video Source # 
Instance details

Defined in Telegram.Bot.API.Types

Voice

data Voice Source #

This object represents a voice note.

Constructors

Voice 

Fields

Instances

Instances details
Show Voice Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

showsPrec :: Int -> Voice -> ShowS #

show :: Voice -> String #

showList :: [Voice] -> ShowS #

Generic Voice Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep Voice :: Type -> Type #

Methods

from :: Voice -> Rep Voice x #

to :: Rep Voice x -> Voice #

FromJSON Voice Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser Voice

parseJSONList :: Value -> Parser [Voice]

ToJSON Voice Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: Voice -> Value

toEncoding :: Voice -> Encoding

toJSONList :: [Voice] -> Value

toEncodingList :: [Voice] -> Encoding

type Rep Voice Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep Voice = D1 ('MetaData "Voice" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "Voice" 'PrefixI 'True) ((S1 ('MetaSel ('Just "voiceFileId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FileId) :*: S1 ('MetaSel ('Just "voiceDuration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Seconds)) :*: (S1 ('MetaSel ('Just "voiceMimeType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "voiceFileSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int32)))))

VideoNote

data VideoNote Source #

This object represents a video message (available in Telegram apps as of v.4.0).

Constructors

VideoNote 

Fields

Instances

Instances details
Show VideoNote Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic VideoNote Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep VideoNote :: Type -> Type #

FromJSON VideoNote Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser VideoNote

parseJSONList :: Value -> Parser [VideoNote]

ToJSON VideoNote Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: VideoNote -> Value

toEncoding :: VideoNote -> Encoding

toJSONList :: [VideoNote] -> Value

toEncodingList :: [VideoNote] -> Encoding

type Rep VideoNote Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep VideoNote = D1 ('MetaData "VideoNote" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "VideoNote" 'PrefixI 'True) ((S1 ('MetaSel ('Just "videoNoteFileId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "videoNoteLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32)) :*: (S1 ('MetaSel ('Just "videoNoteDuration") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Seconds) :*: (S1 ('MetaSel ('Just "videoNoteThumb") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PhotoSize)) :*: S1 ('MetaSel ('Just "videoNoteFileSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int32))))))

Contact

data Contact Source #

This object represents a phone contact.

Constructors

Contact 

Fields

Instances

Instances details
Show Contact Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic Contact Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep Contact :: Type -> Type #

Methods

from :: Contact -> Rep Contact x #

to :: Rep Contact x -> Contact #

FromJSON Contact Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser Contact

parseJSONList :: Value -> Parser [Contact]

ToJSON Contact Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: Contact -> Value

toEncoding :: Contact -> Encoding

toJSONList :: [Contact] -> Value

toEncodingList :: [Contact] -> Encoding

type Rep Contact Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep Contact = D1 ('MetaData "Contact" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "Contact" 'PrefixI 'True) ((S1 ('MetaSel ('Just "contactPhoneNumber") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "contactFirstName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "contactLastName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "contactUserId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe UserId)))))

Location

data Location Source #

This object represents a point on the map.

Constructors

Location 

Fields

Instances

Instances details
Show Location Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic Location Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep Location :: Type -> Type #

Methods

from :: Location -> Rep Location x #

to :: Rep Location x -> Location #

FromJSON Location Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser Location

parseJSONList :: Value -> Parser [Location]

ToJSON Location Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: Location -> Value

toEncoding :: Location -> Encoding

toJSONList :: [Location] -> Value

toEncodingList :: [Location] -> Encoding

type Rep Location Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep Location = D1 ('MetaData "Location" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "Location" 'PrefixI 'True) (S1 ('MetaSel ('Just "locationLongitude") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float) :*: S1 ('MetaSel ('Just "locationLatitude") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)))

Venue

data Venue Source #

This object represents a venue.

Constructors

Venue 

Fields

Instances

Instances details
Show Venue Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

showsPrec :: Int -> Venue -> ShowS #

show :: Venue -> String #

showList :: [Venue] -> ShowS #

Generic Venue Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep Venue :: Type -> Type #

Methods

from :: Venue -> Rep Venue x #

to :: Rep Venue x -> Venue #

FromJSON Venue Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser Venue

parseJSONList :: Value -> Parser [Venue]

ToJSON Venue Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: Venue -> Value

toEncoding :: Venue -> Encoding

toJSONList :: [Venue] -> Value

toEncodingList :: [Venue] -> Encoding

type Rep Venue Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep Venue = D1 ('MetaData "Venue" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "Venue" 'PrefixI 'True) ((S1 ('MetaSel ('Just "venueLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Location) :*: S1 ('MetaSel ('Just "venueTitle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "venueAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "venueFoursquareId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))

UserProfilePhotos

data UserProfilePhotos Source #

This object represent a user's profile pictures.

Constructors

UserProfilePhotos 

Fields

Instances

Instances details
Show UserProfilePhotos Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic UserProfilePhotos Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep UserProfilePhotos :: Type -> Type #

FromJSON UserProfilePhotos Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser UserProfilePhotos

parseJSONList :: Value -> Parser [UserProfilePhotos]

ToJSON UserProfilePhotos Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep UserProfilePhotos Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep UserProfilePhotos = D1 ('MetaData "UserProfilePhotos" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "UserProfilePhotos" 'PrefixI 'True) (S1 ('MetaSel ('Just "userProfilePhotosTotalCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int32) :*: S1 ('MetaSel ('Just "userProfilePhotosPhotos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [[PhotoSize]])))

File

data File Source #

This object represents a file ready to be downloaded. The file can be downloaded via the link https://api.telegram.org/file/bot<token>/<file_path>. It is guaranteed that the link will be valid for at least 1 hour. When the link expires, a new one can be requested by calling getFile.

Constructors

File 

Fields

Instances

Instances details
Show File Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

showsPrec :: Int -> File -> ShowS #

show :: File -> String #

showList :: [File] -> ShowS #

Generic File Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep File :: Type -> Type #

Methods

from :: File -> Rep File x #

to :: Rep File x -> File #

FromJSON File Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser File

parseJSONList :: Value -> Parser [File]

ToJSON File Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: File -> Value

toEncoding :: File -> Encoding

toJSONList :: [File] -> Value

toEncodingList :: [File] -> Encoding

type Rep File Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep File = D1 ('MetaData "File" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "File" 'PrefixI 'True) (S1 ('MetaSel ('Just "fileFileId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FileId) :*: (S1 ('MetaSel ('Just "fileFileSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int32)) :*: S1 ('MetaSel ('Just "fileFilePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))))

ReplyKeyboardMarkup

data ReplyKeyboardMarkup Source #

This object represents a custom keyboard with reply options (see Introduction to bots for details and examples).

Constructors

ReplyKeyboardMarkup 

Fields

  • replyKeyboardMarkupKeyboard :: [[KeyboardButton]]

    Array of button rows, each represented by an Array of KeyboardButton objects

  • replyKeyboardMarkupResizeKeyboard :: Maybe Bool

    Requests clients to resize the keyboard vertically for optimal fit (e.g., make the keyboard smaller if there are just two rows of buttons). Defaults to false, in which case the custom keyboard is always of the same height as the app's standard keyboard.

  • replyKeyboardMarkupOneTimeKeyboard :: Maybe Bool

    Requests clients to hide the keyboard as soon as it's been used. The keyboard will still be available, but clients will automatically display the usual letter-keyboard in the chat – the user can press a special button in the input field to see the custom keyboard again. Defaults to false.

  • replyKeyboardMarkupSelective :: Maybe Bool

    Use this parameter if you want to show the keyboard to specific users only. Targets: 1) users that are @mentioned in the text of the Message object; 2) if the bot's message is a reply (has reply_to_message_id), sender of the original message.

Instances

Instances details
Show ReplyKeyboardMarkup Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic ReplyKeyboardMarkup Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep ReplyKeyboardMarkup :: Type -> Type #

FromJSON ReplyKeyboardMarkup Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser ReplyKeyboardMarkup

parseJSONList :: Value -> Parser [ReplyKeyboardMarkup]

ToJSON ReplyKeyboardMarkup Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep ReplyKeyboardMarkup Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep ReplyKeyboardMarkup = D1 ('MetaData "ReplyKeyboardMarkup" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "ReplyKeyboardMarkup" 'PrefixI 'True) ((S1 ('MetaSel ('Just "replyKeyboardMarkupKeyboard") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [[KeyboardButton]]) :*: S1 ('MetaSel ('Just "replyKeyboardMarkupResizeKeyboard") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "replyKeyboardMarkupOneTimeKeyboard") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "replyKeyboardMarkupSelective") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))))

KeyboardButton

data KeyboardButton Source #

This object represents one button of the reply keyboard. For simple text buttons String can be used instead of this object to specify text of the button. Optional fields are mutually exclusive.

Constructors

KeyboardButton 

Fields

Instances

Instances details
Show KeyboardButton Source # 
Instance details

Defined in Telegram.Bot.API.Types

IsString KeyboardButton Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic KeyboardButton Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep KeyboardButton :: Type -> Type #

FromJSON KeyboardButton Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser KeyboardButton

parseJSONList :: Value -> Parser [KeyboardButton]

ToJSON KeyboardButton Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: KeyboardButton -> Value

toEncoding :: KeyboardButton -> Encoding

toJSONList :: [KeyboardButton] -> Value

toEncodingList :: [KeyboardButton] -> Encoding

type Rep KeyboardButton Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep KeyboardButton = D1 ('MetaData "KeyboardButton" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "KeyboardButton" 'PrefixI 'True) (S1 ('MetaSel ('Just "keyboardButtonText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "keyboardButtonRequestContact") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "keyboardButtonRequestLocation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))))

ReplyKeyboardRemove

data ReplyKeyboardRemove Source #

Upon receiving a message with this object, Telegram clients will remove the current custom keyboard and display the default letter-keyboard.

By default, custom keyboards are displayed until a new keyboard is sent by a bot. An exception is made for one-time keyboards that are hidden immediately after the user presses a button (see ReplyKeyboardMarkup).

Constructors

ReplyKeyboardRemove 

Fields

  • replyKeyboardRemoveRemoveKeyboard :: Bool

    Requests clients to remove the custom keyboard (user will not be able to summon this keyboard; if you want to hide the keyboard from sight but keep it accessible, use one_time_keyboard in ReplyKeyboardMarkup)

  • replyKeyboardRemoveSelective :: Maybe Bool

    Use this parameter if you want to remove the keyboard for specific users only. Targets: 1) users that are @mentioned in the text of the Message object; 2) if the bot's message is a reply (has reply_to_message_id), sender of the original message.

Instances

Instances details
Show ReplyKeyboardRemove Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic ReplyKeyboardRemove Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep ReplyKeyboardRemove :: Type -> Type #

FromJSON ReplyKeyboardRemove Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser ReplyKeyboardRemove

parseJSONList :: Value -> Parser [ReplyKeyboardRemove]

ToJSON ReplyKeyboardRemove Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep ReplyKeyboardRemove Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep ReplyKeyboardRemove = D1 ('MetaData "ReplyKeyboardRemove" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "ReplyKeyboardRemove" 'PrefixI 'True) (S1 ('MetaSel ('Just "replyKeyboardRemoveRemoveKeyboard") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "replyKeyboardRemoveSelective") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))

InlineKeyboardMarkup

data InlineKeyboardMarkup Source #

This object represents an inline keyboard that appears right next to the message it belongs to.

Constructors

InlineKeyboardMarkup 

Fields

Instances

Instances details
Show InlineKeyboardMarkup Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic InlineKeyboardMarkup Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep InlineKeyboardMarkup :: Type -> Type #

FromJSON InlineKeyboardMarkup Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser InlineKeyboardMarkup

parseJSONList :: Value -> Parser [InlineKeyboardMarkup]

ToJSON InlineKeyboardMarkup Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep InlineKeyboardMarkup Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep InlineKeyboardMarkup = D1 ('MetaData "InlineKeyboardMarkup" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "InlineKeyboardMarkup" 'PrefixI 'True) (S1 ('MetaSel ('Just "inlineKeyboardMarkupInlineKeyboard") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [[InlineKeyboardButton]])))

InlineKeyboardButton

data InlineKeyboardButton Source #

This object represents one button of an inline keyboard. You must use exactly one of the optional fields.

Constructors

InlineKeyboardButton 

Fields

Instances

Instances details
Show InlineKeyboardButton Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic InlineKeyboardButton Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep InlineKeyboardButton :: Type -> Type #

FromJSON InlineKeyboardButton Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser InlineKeyboardButton

parseJSONList :: Value -> Parser [InlineKeyboardButton]

ToJSON InlineKeyboardButton Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep InlineKeyboardButton Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep InlineKeyboardButton = D1 ('MetaData "InlineKeyboardButton" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "InlineKeyboardButton" 'PrefixI 'True) ((S1 ('MetaSel ('Just "inlineKeyboardButtonText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "inlineKeyboardButtonUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "inlineKeyboardButtonCallbackData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)))) :*: (S1 ('MetaSel ('Just "inlineKeyboardButtonSwitchInlineQuery") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "inlineKeyboardButtonSwitchInlineQueryCurrentChat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "inlineKeyboardButtonPay") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))))

CallbackQuery

data CallbackQuery Source #

This object represents an incoming callback query from a callback button in an inline keyboard. If the button that originated the query was attached to a message sent by the bot, the field message will be present. If the button was attached to a message sent via the bot (in inline mode), the field inline_message_id will be present. Exactly one of the fields data or game_short_name will be present.

Constructors

CallbackQuery 

Fields

Instances

Instances details
Show CallbackQuery Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic CallbackQuery Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep CallbackQuery :: Type -> Type #

FromJSON CallbackQuery Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser CallbackQuery

parseJSONList :: Value -> Parser [CallbackQuery]

ToJSON CallbackQuery Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: CallbackQuery -> Value

toEncoding :: CallbackQuery -> Encoding

toJSONList :: [CallbackQuery] -> Value

toEncodingList :: [CallbackQuery] -> Encoding

type Rep CallbackQuery Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep CallbackQuery = D1 ('MetaData "CallbackQuery" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "CallbackQuery" 'PrefixI 'True) ((S1 ('MetaSel ('Just "callbackQueryId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CallbackQueryId) :*: (S1 ('MetaSel ('Just "callbackQueryFrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 User) :*: S1 ('MetaSel ('Just "callbackQueryMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Message)))) :*: ((S1 ('MetaSel ('Just "callbackQueryInlineMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId)) :*: S1 ('MetaSel ('Just "callbackQueryChatInstance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "callbackQueryData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "callbackQueryGameShortName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))))

newtype CallbackQueryId Source #

Constructors

CallbackQueryId Text 

Instances

Instances details
Eq CallbackQueryId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Show CallbackQueryId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic CallbackQueryId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep CallbackQueryId :: Type -> Type #

FromJSON CallbackQueryId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser CallbackQueryId

parseJSONList :: Value -> Parser [CallbackQueryId]

ToJSON CallbackQueryId Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: CallbackQueryId -> Value

toEncoding :: CallbackQueryId -> Encoding

toJSONList :: [CallbackQueryId] -> Value

toEncodingList :: [CallbackQueryId] -> Encoding

type Rep CallbackQueryId Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep CallbackQueryId = D1 ('MetaData "CallbackQueryId" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'True) (C1 ('MetaCons "CallbackQueryId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

ForceReply

data ForceReply Source #

Upon receiving a message with this object, Telegram clients will display a reply interface to the user (act as if the user has selected the bot‘s message and tapped ’Reply'). This can be extremely useful if you want to create user-friendly step-by-step interfaces without having to sacrifice privacy mode.

Constructors

ForceReply 

Fields

  • forceReplyForceReply :: Bool

    Shows reply interface to the user, as if they manually selected the bot‘s message and tapped ’Reply'

  • forceReplySelective :: Maybe Bool

    Use this parameter if you want to force reply from specific users only. Targets: 1) users that are @mentioned in the text of the Message object; 2) if the bot's message is a reply (has reply_to_message_id), sender of the original message.

Instances

Instances details
Show ForceReply Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic ForceReply Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep ForceReply :: Type -> Type #

FromJSON ForceReply Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser ForceReply

parseJSONList :: Value -> Parser [ForceReply]

ToJSON ForceReply Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: ForceReply -> Value

toEncoding :: ForceReply -> Encoding

toJSONList :: [ForceReply] -> Value

toEncodingList :: [ForceReply] -> Encoding

type Rep ForceReply Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep ForceReply = D1 ('MetaData "ForceReply" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "ForceReply" 'PrefixI 'True) (S1 ('MetaSel ('Just "forceReplyForceReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "forceReplySelective") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))

Chat photo

data ChatPhoto Source #

Chat photo. Returned only in getChat.

Constructors

ChatPhoto 

Fields

  • chatPhotoSmallFileId :: FileId

    Unique file identifier of small (160x160) chat photo. This file_id can be used only for photo download.

  • chatPhotoBigFileId :: FileId

    Unique file identifier of big (640x640) chat photo. This file_id can be used only for photo download.

Instances

Instances details
Show ChatPhoto Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic ChatPhoto Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep ChatPhoto :: Type -> Type #

FromJSON ChatPhoto Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser ChatPhoto

parseJSONList :: Value -> Parser [ChatPhoto]

ToJSON ChatPhoto Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: ChatPhoto -> Value

toEncoding :: ChatPhoto -> Encoding

toJSONList :: [ChatPhoto] -> Value

toEncodingList :: [ChatPhoto] -> Encoding

type Rep ChatPhoto Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep ChatPhoto = D1 ('MetaData "ChatPhoto" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "ChatPhoto" 'PrefixI 'True) (S1 ('MetaSel ('Just "chatPhotoSmallFileId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FileId) :*: S1 ('MetaSel ('Just "chatPhotoBigFileId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FileId)))

ChatMember

data ChatMember Source #

This object contains information about one member of a chat.

Constructors

ChatMember 

Fields

Instances

Instances details
Show ChatMember Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic ChatMember Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep ChatMember :: Type -> Type #

FromJSON ChatMember Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser ChatMember

parseJSONList :: Value -> Parser [ChatMember]

ToJSON ChatMember Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

toJSON :: ChatMember -> Value

toEncoding :: ChatMember -> Encoding

toJSONList :: [ChatMember] -> Value

toEncodingList :: [ChatMember] -> Encoding

type Rep ChatMember Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep ChatMember = D1 ('MetaData "ChatMember" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "ChatMember" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "chatMemberUser") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 User) :*: S1 ('MetaSel ('Just "chatMemberStatus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "chatMemberUntilDate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe POSIXTime)) :*: S1 ('MetaSel ('Just "chatMemberCanBeEdited") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "chatMemberCanChangeInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "chatMemberCanPostMessages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "chatMemberCanEditMessages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "chatMemberCanDeleteMessages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))))) :*: (((S1 ('MetaSel ('Just "chatMemberCanInviteUsers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "chatMemberCanRestrictMembers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "chatMemberCanPinMessages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "chatMemberCanPromoteMembers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "chatMemberCanSendMessages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "chatMemberCanSendMediaMessages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "chatMemberCanSendOtherMessages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "chatMemberCanAddWebPagePreviews") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))))))

ResponseParameters

data ResponseParameters Source #

Contains information about why a request was unsuccessful.

Constructors

ResponseParameters 

Fields

  • responseParametersMigrateToChatId :: Maybe ChatId

    The group has been migrated to a supergroup with the specified identifier. This number may be greater than 32 bits and some programming languages may have difficulty/silent defects in interpreting it. But it is smaller than 52 bits, so a signed 64 bit integer or double-precision float type are safe for storing this identifier.

  • responseParametersRetryAfter :: Maybe Seconds

    In case of exceeding flood control, the number of seconds left to wait before the request can be repeated

Instances

Instances details
Show ResponseParameters Source # 
Instance details

Defined in Telegram.Bot.API.Types

Generic ResponseParameters Source # 
Instance details

Defined in Telegram.Bot.API.Types

Associated Types

type Rep ResponseParameters :: Type -> Type #

FromJSON ResponseParameters Source # 
Instance details

Defined in Telegram.Bot.API.Types

Methods

parseJSON :: Value -> Parser ResponseParameters

parseJSONList :: Value -> Parser [ResponseParameters]

ToJSON ResponseParameters Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep ResponseParameters Source # 
Instance details

Defined in Telegram.Bot.API.Types

type Rep ResponseParameters = D1 ('MetaData "ResponseParameters" "Telegram.Bot.API.Types" "telegram-bot-simple-0.3.1-inplace" 'False) (C1 ('MetaCons "ResponseParameters" 'PrefixI 'True) (S1 ('MetaSel ('Just "responseParametersMigrateToChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ChatId)) :*: S1 ('MetaSel ('Just "responseParametersRetryAfter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Seconds))))