telegram-types-0.4.1: Types used in Telegram bot API

Safe HaskellNone
LanguageHaskell2010

Web.Telegram.Types.Update

Contents

Synopsis

Documentation

data Update Source #

An incoming update

Constructors

Message

New incoming message of any kind — text, photo, sticker, etc.

Fields

EditedMessage

New version of a message that is known to the bot and was edited

Fields

ChannelPost

New incoming channel post of any kind — text, photo, sticker, etc.

Fields

EditedChannelPost

New version of a channel post that is known to the bot and was edited

Fields

InlineQuery

New incoming inline query

ChosenInlineResult

The result of an inline query that was chosen by a user and sent to their chat partner. Please see our documentation on the feedback collecting for details on how to enable these updates for your bot

CallbackQuery

New incoming callback query

ShippingQuery

New incoming shipping query. Only for invoices with flexible price

PreCheckoutQuery

New incoming pre-checkout query. Contains full information about checkout

PollUpdate

New poll state. Bots receive only updates about stopped polls and polls, which are sent by the bot

Fields

PollAnswer

A user changed their answer in a non-anonymous poll. Bots receive new votes only in polls that were sent by the bot itself.

Fields

Instances
Eq Update Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Update

Methods

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

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

Show Update Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Update

Generic Update Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Update

Associated Types

type Rep Update :: Type -> Type #

Methods

from :: Update -> Rep Update x #

to :: Rep Update x -> Update #

FromJSON Update Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Update

Default Update Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Update

Methods

def :: Update Source #

type Rep Update Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Update

type Rep Update = D1 (MetaData "Update" "Web.Telegram.Types.Internal.Update" "telegram-types-0.4.1-1P4e2IAcVvTIzPu4vV22Qd" False) (((C1 (MetaCons "Message" PrefixI True) (S1 (MetaSel (Just "updateId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "message") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Message)) :+: C1 (MetaCons "EditedMessage" PrefixI True) (S1 (MetaSel (Just "updateId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "message") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Message))) :+: (C1 (MetaCons "ChannelPost" PrefixI True) (S1 (MetaSel (Just "updateId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "message") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Message)) :+: (C1 (MetaCons "EditedChannelPost" PrefixI True) (S1 (MetaSel (Just "updateId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "message") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Message)) :+: C1 (MetaCons "InlineQuery" PrefixI True) (S1 (MetaSel (Just "updateId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "iquery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 InlineQuery))))) :+: ((C1 (MetaCons "ChosenInlineResult" PrefixI True) (S1 (MetaSel (Just "updateId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "result") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ChosenInlineResult)) :+: (C1 (MetaCons "CallbackQuery" PrefixI True) (S1 (MetaSel (Just "updateId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "cbquery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CallbackQuery)) :+: C1 (MetaCons "ShippingQuery" PrefixI True) (S1 (MetaSel (Just "updateId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "squery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ShippingQuery)))) :+: (C1 (MetaCons "PreCheckoutQuery" PrefixI True) (S1 (MetaSel (Just "updateId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "pcquery") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PreCheckoutQuery)) :+: (C1 (MetaCons "PollUpdate" PrefixI True) (S1 (MetaSel (Just "updateId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "poll") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Poll)) :+: C1 (MetaCons "PollAnswer" PrefixI True) (S1 (MetaSel (Just "updateId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "answer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PollAnswer))))))

data WebhookInfo Source #

Contains information about the current status of a webhook.

Constructors

WebhookInfo 

Fields

Instances
Eq WebhookInfo Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Update

Show WebhookInfo Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Update

Generic WebhookInfo Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Update

Associated Types

type Rep WebhookInfo :: Type -> Type #

ToJSON WebhookInfo Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Update

FromJSON WebhookInfo Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Update

Default WebhookInfo Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Update

type Rep WebhookInfo Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Update

Response

data ResponseParameters Source #

Instances
Eq ResponseParameters Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Show ResponseParameters Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Generic ResponseParameters Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Associated Types

type Rep ResponseParameters :: Type -> Type #

ToJSON ResponseParameters Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

FromJSON ResponseParameters Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

ToHttpApiData ResponseParameters Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Default ResponseParameters Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

type Rep ResponseParameters Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

type Rep ResponseParameters = D1 (MetaData "ResponseParameters" "Web.Telegram.Types.Internal.Common" "telegram-types-0.4.1-1P4e2IAcVvTIzPu4vV22Qd" False) (C1 (MetaCons "ResponseParameters" PrefixI True) (S1 (MetaSel (Just "migrateToChatId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int64)) :*: S1 (MetaSel (Just "retryAfter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int))))

newtype ReqResult a Source #

Constructors

Ok a 
Instances
Eq a => Eq (ReqResult a) Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Methods

(==) :: ReqResult a -> ReqResult a -> Bool #

(/=) :: ReqResult a -> ReqResult a -> Bool #

Show a => Show (ReqResult a) Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Generic (ReqResult a) Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Associated Types

type Rep (ReqResult a) :: Type -> Type #

Methods

from :: ReqResult a -> Rep (ReqResult a) x #

to :: Rep (ReqResult a) x -> ReqResult a #

FromJSON a => FromJSON (ReqResult a) Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

type Rep (ReqResult a) Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

type Rep (ReqResult a) = D1 (MetaData "ReqResult" "Web.Telegram.Types.Internal.Common" "telegram-types-0.4.1-1P4e2IAcVvTIzPu4vV22Qd" True) (C1 (MetaCons "Ok" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

data ReqEither a b Source #

Constructors

LLL a 
RRR b 
Instances
(Eq a, Eq b) => Eq (ReqEither a b) Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Methods

(==) :: ReqEither a b -> ReqEither a b -> Bool #

(/=) :: ReqEither a b -> ReqEither a b -> Bool #

(Show a, Show b) => Show (ReqEither a b) Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Methods

showsPrec :: Int -> ReqEither a b -> ShowS #

show :: ReqEither a b -> String #

showList :: [ReqEither a b] -> ShowS #

Generic (ReqEither a b) Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Associated Types

type Rep (ReqEither a b) :: Type -> Type #

Methods

from :: ReqEither a b -> Rep (ReqEither a b) x #

to :: Rep (ReqEither a b) x -> ReqEither a b #

(FromJSON a, FromJSON b) => FromJSON (ReqEither a b) Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

type Rep (ReqEither a b) Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

type Rep (ReqEither a b) = D1 (MetaData "ReqEither" "Web.Telegram.Types.Internal.Common" "telegram-types-0.4.1-1P4e2IAcVvTIzPu4vV22Qd" False) (C1 (MetaCons "LLL" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "RRR" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b)))

data BotCommand Source #

Constructors

BC 

Fields

Instances
Eq BotCommand Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Show BotCommand Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Generic BotCommand Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Associated Types

type Rep BotCommand :: Type -> Type #

ToJSON BotCommand Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

FromJSON BotCommand Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

ToHttpApiData BotCommand Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Default BotCommand Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

type Rep BotCommand Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

type Rep BotCommand = D1 (MetaData "BotCommand" "Web.Telegram.Types.Internal.Common" "telegram-types-0.4.1-1P4e2IAcVvTIzPu4vV22Qd" False) (C1 (MetaCons "BC" PrefixI True) (S1 (MetaSel (Just "command") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "description") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))