telegram-bot-api-6.5: Easy to use library for building Telegram bots. Exports Telegram Bot API.
Safe HaskellNone
LanguageHaskell2010

Telegram.Bot.API.Types.Common

Synopsis

Documentation

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.Common

Methods

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

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

Show FileId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

FromJSON FileId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

parseJSON :: Value -> Parser FileId

parseJSONList :: Value -> Parser [FileId]

ToJSON FileId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

toJSON :: FileId -> Value

toEncoding :: FileId -> Encoding

toJSONList :: [FileId] -> Value

toEncodingList :: [FileId] -> Encoding

ToHttpApiData FileId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

newtype Seconds Source #

Constructors

Seconds Int 

Instances

Instances details
Eq Seconds Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

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

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

Num Seconds Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Show Seconds Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

FromJSON Seconds Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

parseJSON :: Value -> Parser Seconds

parseJSONList :: Value -> Parser [Seconds]

ToJSON Seconds Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

toJSON :: Seconds -> Value

toEncoding :: Seconds -> Encoding

toJSONList :: [Seconds] -> Value

toEncodingList :: [Seconds] -> Encoding

newtype UserId Source #

Unique identifier for this user or bot.

Constructors

UserId Integer 

Instances

Instances details
Eq UserId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

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

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

Show UserId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

FromJSON UserId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

parseJSON :: Value -> Parser UserId

parseJSONList :: Value -> Parser [UserId]

ToJSON UserId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

toJSON :: UserId -> Value

toEncoding :: UserId -> Encoding

toJSONList :: [UserId] -> Value

toEncodingList :: [UserId] -> Encoding

ToHttpApiData UserId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

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.Common

Methods

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

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

Show ChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

FromJSON ChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

parseJSON :: Value -> Parser ChatId

parseJSONList :: Value -> Parser [ChatId]

ToJSON ChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

toJSON :: ChatId -> Value

toEncoding :: ChatId -> Encoding

toJSONList :: [ChatId] -> Value

toEncodingList :: [ChatId] -> Encoding

Hashable ChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

hashWithSalt :: Int -> ChatId -> Int

hash :: ChatId -> Int

ToHttpApiData ChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

newtype MessageId Source #

Unique message identifier inside this chat.

Constructors

MessageId Integer 

Instances

Instances details
Eq MessageId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Show MessageId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

FromJSON MessageId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

parseJSON :: Value -> Parser MessageId

parseJSONList :: Value -> Parser [MessageId]

ToJSON MessageId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

toJSON :: MessageId -> Value

toEncoding :: MessageId -> Encoding

toJSONList :: [MessageId] -> Value

toEncodingList :: [MessageId] -> Encoding

Hashable MessageId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

ToHttpApiData MessageId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

newtype MessageThreadId Source #

Unique identifier of a message thread to which the message belongs; for supergroups only.

Constructors

MessageThreadId Integer 

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.Common

Show MediaGroupId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

FromJSON MediaGroupId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

parseJSON :: Value -> Parser MediaGroupId

parseJSONList :: Value -> Parser [MediaGroupId]

ToJSON MediaGroupId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

toJSON :: MediaGroupId -> Value

toEncoding :: MediaGroupId -> Encoding

toJSONList :: [MediaGroupId] -> Value

toEncodingList :: [MediaGroupId] -> Encoding

newtype RequestId Source #

Signed 32-bit identifier of the request, which will be received back in the UserShared or ChatShared object. Must be unique within the message.

Constructors

RequestId Integer 

Instances

Instances details
Eq RequestId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Show RequestId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

FromJSON RequestId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

parseJSON :: Value -> Parser RequestId

parseJSONList :: Value -> Parser [RequestId]

ToJSON RequestId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

toJSON :: RequestId -> Value

toEncoding :: RequestId -> Encoding

toJSONList :: [RequestId] -> Value

toEncodingList :: [RequestId] -> Encoding

newtype PollId Source #

Unique poll identifier.

Constructors

PollId Text 

Instances

Instances details
Eq PollId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

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

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

Show PollId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

FromJSON PollId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

parseJSON :: Value -> Parser PollId

parseJSONList :: Value -> Parser [PollId]

ToJSON PollId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

toJSON :: PollId -> Value

toEncoding :: PollId -> Encoding

toJSONList :: [PollId] -> Value

toEncodingList :: [PollId] -> Encoding

newtype ShippingOptionId Source #

Constructors

ShippingOptionId Text 

Instances

Instances details
Eq ShippingOptionId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Show ShippingOptionId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Generic ShippingOptionId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Associated Types

type Rep ShippingOptionId :: Type -> Type #

FromJSON ShippingOptionId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

parseJSON :: Value -> Parser ShippingOptionId

parseJSONList :: Value -> Parser [ShippingOptionId]

ToJSON ShippingOptionId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

type Rep ShippingOptionId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

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

newtype WebAppInfo Source #

Constructors

WebAppInfo 

Fields

Instances

Instances details
Show WebAppInfo Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Generic WebAppInfo Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Associated Types

type Rep WebAppInfo :: Type -> Type #

FromJSON WebAppInfo Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

parseJSON :: Value -> Parser WebAppInfo

parseJSONList :: Value -> Parser [WebAppInfo]

ToJSON WebAppInfo Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

toJSON :: WebAppInfo -> Value

toEncoding :: WebAppInfo -> Encoding

toJSONList :: [WebAppInfo] -> Value

toEncodingList :: [WebAppInfo] -> Encoding

type Rep WebAppInfo Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

type Rep WebAppInfo = D1 ('MetaData "WebAppInfo" "Telegram.Bot.API.Types.Common" "telegram-bot-api-6.5-inplace" 'True) (C1 ('MetaCons "WebAppInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "webAppInfoUrl") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype CallbackQueryId Source #

Constructors

CallbackQueryId Text 

Instances

Instances details
Eq CallbackQueryId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Show CallbackQueryId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Generic CallbackQueryId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Associated Types

type Rep CallbackQueryId :: Type -> Type #

FromJSON CallbackQueryId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

parseJSON :: Value -> Parser CallbackQueryId

parseJSONList :: Value -> Parser [CallbackQueryId]

ToJSON CallbackQueryId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

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.Common

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

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

Instances details
Generic SomeChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Associated Types

type Rep SomeChatId :: Type -> Type #

FromJSON SomeChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

parseJSON :: Value -> Parser SomeChatId

parseJSONList :: Value -> Parser [SomeChatId]

ToJSON SomeChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

Methods

toJSON :: SomeChatId -> Value

toEncoding :: SomeChatId -> Encoding

toJSONList :: [SomeChatId] -> Value

toEncodingList :: [SomeChatId] -> Encoding

ToHttpApiData SomeChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

type Rep SomeChatId Source # 
Instance details

Defined in Telegram.Bot.API.Types.Common

type Rep SomeChatId = D1 ('MetaData "SomeChatId" "Telegram.Bot.API.Types.Common" "telegram-bot-api-6.5-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)))

addType :: Text -> [Pair] -> [Pair] Source #