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

Safe HaskellNone
LanguageHaskell2010

Web.Telegram.Types.Interaction

Contents

Description

User interactions: customized keyboards, clickable buttons, popups and inline displays

Synopsis

queries

data CallbackQuery Source #

Instances
Eq CallbackQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Show CallbackQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Generic CallbackQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Associated Types

type Rep CallbackQuery :: Type -> Type #

ToJSON CallbackQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

FromJSON CallbackQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

ToHttpApiData CallbackQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Default CallbackQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

type Rep CallbackQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

data ShippingQuery Source #

Instances
Eq ShippingQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Show ShippingQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Generic ShippingQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Associated Types

type Rep ShippingQuery :: Type -> Type #

ToJSON ShippingQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

FromJSON ShippingQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

ToHttpApiData ShippingQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Default ShippingQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

type Rep ShippingQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

type Rep ShippingQuery = D1 (MetaData "ShippingQuery" "Web.Telegram.Types.Internal.Common" "telegram-types-0.4.1-1P4e2IAcVvTIzPu4vV22Qd" False) (C1 (MetaCons "SQuery" PrefixI True) ((S1 (MetaSel (Just "queryId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "from") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 User)) :*: (S1 (MetaSel (Just "invoicePayload") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "shippingAddress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ShippingAddress))))

data PreCheckoutQuery Source #

Instances
Eq PreCheckoutQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Show PreCheckoutQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Generic PreCheckoutQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Associated Types

type Rep PreCheckoutQuery :: Type -> Type #

ToJSON PreCheckoutQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

FromJSON PreCheckoutQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

ToHttpApiData PreCheckoutQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

Default PreCheckoutQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

type Rep PreCheckoutQuery Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Common

replys

data ReplyKeyboardMarkup Source #

Instances
Eq ReplyKeyboardMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Show ReplyKeyboardMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Generic ReplyKeyboardMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Associated Types

type Rep ReplyKeyboardMarkup :: Type -> Type #

ToJSON ReplyKeyboardMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

ToJSON ReplyMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

ToHttpApiData ReplyKeyboardMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Default ReplyKeyboardMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

ToHttpApiData (Union (InlineKeyboardMarkup ': (ReplyKeyboardMarkup ': (ReplyKeyboardRemove ': (ForceReply ': ([] :: [Type])))))) Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

type Rep ReplyKeyboardMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

type Rep ReplyKeyboardMarkup = D1 (MetaData "ReplyKeyboardMarkup" "Web.Telegram.Types.Internal.Keyboard" "telegram-types-0.4.1-1P4e2IAcVvTIzPu4vV22Qd" False) (C1 (MetaCons "ReplyKeyboardMarkup" PrefixI True) ((S1 (MetaSel (Just "keyboard") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[KeyboardButton]]) :*: S1 (MetaSel (Just "resizeKeyboard") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 (MetaSel (Just "oneTimeKeyboard") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 (MetaSel (Just "selective") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)))))

data KeyboardButton Source #

Instances
Eq KeyboardButton Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Show KeyboardButton Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Generic KeyboardButton Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Associated Types

type Rep KeyboardButton :: Type -> Type #

ToJSON KeyboardButton Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

ToHttpApiData KeyboardButton Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Default KeyboardButton Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

type Rep KeyboardButton Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

type Rep KeyboardButton = D1 (MetaData "KeyboardButton" "Web.Telegram.Types.Internal.Keyboard" "telegram-types-0.4.1-1P4e2IAcVvTIzPu4vV22Qd" False) (C1 (MetaCons "KeyboardButton" PrefixI True) (S1 (MetaSel (Just "text") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "addon") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe KeyboardButtonAddon))))

data KeyboardButtonAddon Source #

Instances
Eq KeyboardButtonAddon Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Show KeyboardButtonAddon Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Generic KeyboardButtonAddon Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Associated Types

type Rep KeyboardButtonAddon :: Type -> Type #

ToJSON KeyboardButtonAddon Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

FromJSON KeyboardButtonAddon Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Default KeyboardButtonAddon Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

type Rep KeyboardButtonAddon Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

type Rep KeyboardButtonAddon = D1 (MetaData "KeyboardButtonAddon" "Web.Telegram.Types.Internal.Keyboard" "telegram-types-0.4.1-1P4e2IAcVvTIzPu4vV22Qd" False) (C1 (MetaCons "RequestContact" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :+: (C1 (MetaCons "RequestLocation" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :+: C1 (MetaCons "RequestPoll" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 KeyboardButtonPollType))))

newtype KeyboardButtonPollType Source #

Instances
Eq KeyboardButtonPollType Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Show KeyboardButtonPollType Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Generic KeyboardButtonPollType Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Associated Types

type Rep KeyboardButtonPollType :: Type -> Type #

ToJSON KeyboardButtonPollType Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

FromJSON KeyboardButtonPollType Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

ToHttpApiData KeyboardButtonPollType Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Default KeyboardButtonPollType Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

type Rep KeyboardButtonPollType Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

type Rep KeyboardButtonPollType = D1 (MetaData "KeyboardButtonPollType" "Web.Telegram.Types.Internal.Keyboard" "telegram-types-0.4.1-1P4e2IAcVvTIzPu4vV22Qd" True) (C1 (MetaCons "KeyboardButtonPollType" PrefixI True) (S1 (MetaSel (Just "pollType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PollType))))

data ReplyKeyboardRemove Source #

Instances
Eq ReplyKeyboardRemove Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Show ReplyKeyboardRemove Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Generic ReplyKeyboardRemove Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Associated Types

type Rep ReplyKeyboardRemove :: Type -> Type #

ToJSON ReplyKeyboardRemove Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

ToJSON ReplyMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

FromJSON ReplyKeyboardRemove Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

ToHttpApiData ReplyKeyboardRemove Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Default ReplyKeyboardRemove Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

ToHttpApiData (Union (InlineKeyboardMarkup ': (ReplyKeyboardMarkup ': (ReplyKeyboardRemove ': (ForceReply ': ([] :: [Type])))))) Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

type Rep ReplyKeyboardRemove Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

type Rep ReplyKeyboardRemove = D1 (MetaData "ReplyKeyboardRemove" "Web.Telegram.Types.Internal.Keyboard" "telegram-types-0.4.1-1P4e2IAcVvTIzPu4vV22Qd" False) (C1 (MetaCons "ReplyKeyboardRemove" PrefixI True) (S1 (MetaSel (Just "removeKeyboard") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "selective") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))))

newtype InlineKeyboardMarkup Source #

Instances
Eq InlineKeyboardMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Show InlineKeyboardMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Generic InlineKeyboardMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Associated Types

type Rep InlineKeyboardMarkup :: Type -> Type #

ToJSON InlineKeyboardMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

ToJSON ReplyMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

FromJSON InlineKeyboardMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

ToHttpApiData InlineKeyboardMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Default InlineKeyboardMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

ToHttpApiData (Union (InlineKeyboardMarkup ': (ReplyKeyboardMarkup ': (ReplyKeyboardRemove ': (ForceReply ': ([] :: [Type])))))) Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

type Rep InlineKeyboardMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

type Rep InlineKeyboardMarkup = D1 (MetaData "InlineKeyboardMarkup" "Web.Telegram.Types.Internal.Keyboard" "telegram-types-0.4.1-1P4e2IAcVvTIzPu4vV22Qd" True) (C1 (MetaCons "InlineKeyboardMarkup" PrefixI True) (S1 (MetaSel (Just "inlineKeyboard") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [[InlineKeyboardButton]])))

data InlineKeyboardButton Source #

Instances
Eq InlineKeyboardButton Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Show InlineKeyboardButton Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Generic InlineKeyboardButton Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Associated Types

type Rep InlineKeyboardButton :: Type -> Type #

ToJSON InlineKeyboardButton Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

FromJSON InlineKeyboardButton Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

ToHttpApiData InlineKeyboardButton Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Default InlineKeyboardButton Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

type Rep InlineKeyboardButton Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

data ForceReply Source #

Constructors

ForceReply 
Instances
Eq ForceReply Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Show ForceReply Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Generic ForceReply Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Associated Types

type Rep ForceReply :: Type -> Type #

ToJSON ForceReply Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

ToJSON ReplyMarkup Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

FromJSON ForceReply Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

ToHttpApiData ForceReply Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Default ForceReply Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

ToHttpApiData (Union (InlineKeyboardMarkup ': (ReplyKeyboardMarkup ': (ReplyKeyboardRemove ': (ForceReply ': ([] :: [Type])))))) Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

type Rep ForceReply Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

type Rep ForceReply = D1 (MetaData "ForceReply" "Web.Telegram.Types.Internal.Keyboard" "telegram-types-0.4.1-1P4e2IAcVvTIzPu4vV22Qd" False) (C1 (MetaCons "ForceReply" PrefixI True) (S1 (MetaSel (Just "forceReply") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "selective") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool))))

data LoginUrl Source #

Instances
Eq LoginUrl Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Show LoginUrl Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Generic LoginUrl Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Associated Types

type Rep LoginUrl :: Type -> Type #

Methods

from :: LoginUrl -> Rep LoginUrl x #

to :: Rep LoginUrl x -> LoginUrl #

ToJSON LoginUrl Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

FromJSON LoginUrl Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

ToHttpApiData LoginUrl Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Default LoginUrl Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

Methods

def :: LoginUrl Source #

type Rep LoginUrl Source # 
Instance details

Defined in Web.Telegram.Types.Internal.Keyboard

type Rep LoginUrl = D1 (MetaData "LoginUrl" "Web.Telegram.Types.Internal.Keyboard" "telegram-types-0.4.1-1P4e2IAcVvTIzPu4vV22Qd" False) (C1 (MetaCons "LoginUrl" PrefixI True) ((S1 (MetaSel (Just "url") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "forwardText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "botUsername") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "requestWriteAccess") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)))))

data Action Source #

Instances
Eq Action Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

Methods

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

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

Ord Action Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

Show Action Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

Generic Action Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

Associated Types

type Rep Action :: Type -> Type #

Methods

from :: Action -> Rep Action x #

to :: Rep Action x -> Action #

ToJSON Action Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

FromJSON Action Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

ToHttpApiData Action Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

Default Action Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

Methods

def :: Action Source #

type Rep Action Source # 
Instance details

Defined in Web.Telegram.Types.Interaction

type Rep Action = D1 (MetaData "Action" "Web.Telegram.Types.Interaction" "telegram-types-0.4.1-1P4e2IAcVvTIzPu4vV22Qd" False) (((C1 (MetaCons "Typing" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UploadPhoto" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "RecordVideo" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "UploadVideo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RecordAudio" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "UploadAudio" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UploadDocument" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "FindLocation" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "RecordVideoNote" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "UploadVideoNote" PrefixI False) (U1 :: Type -> Type)))))

Orphan instances