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

Telegram.Bot.API.Games

Synopsis

Types

SendGameRequest

data SendGameRequest Source #

Constructors

SendGameRequest 

Fields

Instances

Instances details
Show SendGameRequest Source # 
Instance details

Defined in Telegram.Bot.API.Games

Generic SendGameRequest Source # 
Instance details

Defined in Telegram.Bot.API.Games

Associated Types

type Rep SendGameRequest :: Type -> Type #

FromJSON SendGameRequest Source # 
Instance details

Defined in Telegram.Bot.API.Games

Methods

parseJSON :: Value -> Parser SendGameRequest

parseJSONList :: Value -> Parser [SendGameRequest]

ToJSON SendGameRequest Source # 
Instance details

Defined in Telegram.Bot.API.Games

Methods

toJSON :: SendGameRequest -> Value

toEncoding :: SendGameRequest -> Encoding

toJSONList :: [SendGameRequest] -> Value

toEncodingList :: [SendGameRequest] -> Encoding

type Rep SendGameRequest Source # 
Instance details

Defined in Telegram.Bot.API.Games

type Rep SendGameRequest = D1 ('MetaData "SendGameRequest" "Telegram.Bot.API.Games" "telegram-bot-simple-0.5-inplace" 'False) (C1 ('MetaCons "SendGameRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "sendGameRequestChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChatId) :*: (S1 ('MetaSel ('Just "sendGameRequestGameShortName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "sendGameRequestDisableNotification") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "sendGameProtectContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendGameRequestReplyToMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId))) :*: (S1 ('MetaSel ('Just "sendGameRequestAllowSendingWithoutReply") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "sendGameRequestReplyMarkup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe InlineKeyboardMarkup))))))

SetGameScoreRequest

data SetGameScoreRequest Source #

Constructors

SetGameScoreRequest 

Fields

Instances

Instances details
Show SetGameScoreRequest Source # 
Instance details

Defined in Telegram.Bot.API.Games

Generic SetGameScoreRequest Source # 
Instance details

Defined in Telegram.Bot.API.Games

Associated Types

type Rep SetGameScoreRequest :: Type -> Type #

FromJSON SetGameScoreRequest Source # 
Instance details

Defined in Telegram.Bot.API.Games

Methods

parseJSON :: Value -> Parser SetGameScoreRequest

parseJSONList :: Value -> Parser [SetGameScoreRequest]

ToJSON SetGameScoreRequest Source # 
Instance details

Defined in Telegram.Bot.API.Games

type Rep SetGameScoreRequest Source # 
Instance details

Defined in Telegram.Bot.API.Games

type Rep SetGameScoreRequest = D1 ('MetaData "SetGameScoreRequest" "Telegram.Bot.API.Games" "telegram-bot-simple-0.5-inplace" 'False) (C1 ('MetaCons "SetGameScoreRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "setGameScoreRequestUserId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UserId) :*: (S1 ('MetaSel ('Just "setGameScoreRequestScore") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "setGameScoreRequestForce") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)))) :*: ((S1 ('MetaSel ('Just "setGameScoreRequestDisableEditMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "setGameScoreRequestChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ChatId))) :*: (S1 ('MetaSel ('Just "setGameScoreRequestMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId)) :*: S1 ('MetaSel ('Just "setGameScoreRequestInlineMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId))))))

SetGameScoreResult

data SetGameScoreResult Source #

Instances

Instances details
Show SetGameScoreResult Source # 
Instance details

Defined in Telegram.Bot.API.Games

Generic SetGameScoreResult Source # 
Instance details

Defined in Telegram.Bot.API.Games

Associated Types

type Rep SetGameScoreResult :: Type -> Type #

FromJSON SetGameScoreResult Source # 
Instance details

Defined in Telegram.Bot.API.Games

Methods

parseJSON :: Value -> Parser SetGameScoreResult

parseJSONList :: Value -> Parser [SetGameScoreResult]

ToJSON SetGameScoreResult Source # 
Instance details

Defined in Telegram.Bot.API.Games

type Rep SetGameScoreResult Source # 
Instance details

Defined in Telegram.Bot.API.Games

type Rep SetGameScoreResult = D1 ('MetaData "SetGameScoreResult" "Telegram.Bot.API.Games" "telegram-bot-simple-0.5-inplace" 'False) (C1 ('MetaCons "SetGameScoreMessage" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Message)) :+: C1 ('MetaCons "SetGameScoreMessageBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

GetGameHighScoresRequest

data GetGameHighScoresRequest Source #

Constructors

GetGameHighScoresRequest 

Fields

Instances

Instances details
Show GetGameHighScoresRequest Source # 
Instance details

Defined in Telegram.Bot.API.Games

Generic GetGameHighScoresRequest Source # 
Instance details

Defined in Telegram.Bot.API.Games

Associated Types

type Rep GetGameHighScoresRequest :: Type -> Type #

type Rep GetGameHighScoresRequest Source # 
Instance details

Defined in Telegram.Bot.API.Games

type Rep GetGameHighScoresRequest = D1 ('MetaData "GetGameHighScoresRequest" "Telegram.Bot.API.Games" "telegram-bot-simple-0.5-inplace" 'False) (C1 ('MetaCons "GetGameHighScoresRequest" 'PrefixI 'True) ((S1 ('MetaSel ('Just "getGameHighScoresRequestUserId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UserId) :*: S1 ('MetaSel ('Just "getGameHighScoresRequestChatId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ChatId))) :*: (S1 ('MetaSel ('Just "getGameHighScoresRequestMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId)) :*: S1 ('MetaSel ('Just "getGameHighScoresRequestInlineMessageId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MessageId)))))

Methods

sendGame

type SendGame = "sendGame" :> (ReqBody '[JSON] SendGameRequest :> Post '[JSON] (Response Message)) Source #

sendGame :: SendGameRequest -> ClientM (Response Message) Source #

Use this method to send a game. On success, the sent Message is returned.

setGameScore

type SetGameScore = "setGameScore" :> (ReqBody '[JSON] SetGameScoreRequest :> Post '[JSON] (Response SetGameScoreResult)) Source #

setGameScore :: SetGameScoreRequest -> ClientM (Response SetGameScoreResult) Source #

Use this method to set the score of the specified user in a game message. On success, if the message is not an inline message, the Message is returned, otherwise True is returned. Returns an error, if the new score is not greater than the user's current score in the chat and force is False.

getGameHighScores

type GetGameHighScores = "getGameHighScores" :> (ReqBody '[JSON] GetGameHighScoresRequest :> Post '[JSON] (Response [GameHighScore])) Source #