{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Telegram.Bot.API.Games where
import Data.Text (Text)
import Data.Proxy
import GHC.Generics (Generic)
import Servant.API
import Servant.Client hiding (Response)
import Telegram.Bot.API.Internal.Utils (deriveJSON')
import Telegram.Bot.API.MakingRequests (Response)
import Telegram.Bot.API.Types (ChatId, GameHighScore, InlineKeyboardMarkup, Message, MessageId, UserId)
data SendGameRequest = SendGameRequest
{ SendGameRequest -> ChatId
sendGameRequestChatId :: ChatId
, SendGameRequest -> Text
sendGameRequestGameShortName :: Text
, SendGameRequest -> Maybe Bool
sendGameRequestDisableNotification :: Maybe Bool
, SendGameRequest -> Maybe Bool
sendGameProtectContent :: Maybe Bool
, SendGameRequest -> Maybe MessageId
sendGameRequestReplyToMessageId :: Maybe MessageId
, SendGameRequest -> Maybe Bool
sendGameRequestAllowSendingWithoutReply :: Maybe Bool
, SendGameRequest -> Maybe InlineKeyboardMarkup
sendGameRequestReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving (forall x. Rep SendGameRequest x -> SendGameRequest
forall x. SendGameRequest -> Rep SendGameRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendGameRequest x -> SendGameRequest
$cfrom :: forall x. SendGameRequest -> Rep SendGameRequest x
Generic, Int -> SendGameRequest -> ShowS
[SendGameRequest] -> ShowS
SendGameRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendGameRequest] -> ShowS
$cshowList :: [SendGameRequest] -> ShowS
show :: SendGameRequest -> String
$cshow :: SendGameRequest -> String
showsPrec :: Int -> SendGameRequest -> ShowS
$cshowsPrec :: Int -> SendGameRequest -> ShowS
Show)
data SetGameScoreRequest = SetGameScoreRequest
{ SetGameScoreRequest -> UserId
setGameScoreRequestUserId :: UserId
, SetGameScoreRequest -> Integer
setGameScoreRequestScore :: Integer
, SetGameScoreRequest -> Maybe Bool
setGameScoreRequestForce :: Maybe Bool
, SetGameScoreRequest -> Maybe Bool
setGameScoreRequestDisableEditMessage :: Maybe Bool
, SetGameScoreRequest -> Maybe ChatId
setGameScoreRequestChatId :: Maybe ChatId
, SetGameScoreRequest -> Maybe MessageId
setGameScoreRequestMessageId :: Maybe MessageId
, SetGameScoreRequest -> Maybe MessageId
setGameScoreRequestInlineMessageId :: Maybe MessageId
}
deriving (forall x. Rep SetGameScoreRequest x -> SetGameScoreRequest
forall x. SetGameScoreRequest -> Rep SetGameScoreRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetGameScoreRequest x -> SetGameScoreRequest
$cfrom :: forall x. SetGameScoreRequest -> Rep SetGameScoreRequest x
Generic, Int -> SetGameScoreRequest -> ShowS
[SetGameScoreRequest] -> ShowS
SetGameScoreRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetGameScoreRequest] -> ShowS
$cshowList :: [SetGameScoreRequest] -> ShowS
show :: SetGameScoreRequest -> String
$cshow :: SetGameScoreRequest -> String
showsPrec :: Int -> SetGameScoreRequest -> ShowS
$cshowsPrec :: Int -> SetGameScoreRequest -> ShowS
Show)
data SetGameScoreResult = SetGameScoreMessage Message | SetGameScoreMessageBool Bool
deriving (forall x. Rep SetGameScoreResult x -> SetGameScoreResult
forall x. SetGameScoreResult -> Rep SetGameScoreResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetGameScoreResult x -> SetGameScoreResult
$cfrom :: forall x. SetGameScoreResult -> Rep SetGameScoreResult x
Generic, Int -> SetGameScoreResult -> ShowS
[SetGameScoreResult] -> ShowS
SetGameScoreResult -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetGameScoreResult] -> ShowS
$cshowList :: [SetGameScoreResult] -> ShowS
show :: SetGameScoreResult -> String
$cshow :: SetGameScoreResult -> String
showsPrec :: Int -> SetGameScoreResult -> ShowS
$cshowsPrec :: Int -> SetGameScoreResult -> ShowS
Show)
data GetGameHighScoresRequest = GetGameHighScoresRequest
{ GetGameHighScoresRequest -> UserId
getGameHighScoresRequestUserId :: UserId
, GetGameHighScoresRequest -> Maybe ChatId
getGameHighScoresRequestChatId :: Maybe ChatId
, GetGameHighScoresRequest -> Maybe MessageId
getGameHighScoresRequestMessageId :: Maybe MessageId
, GetGameHighScoresRequest -> Maybe MessageId
getGameHighScoresRequestInlineMessageId :: Maybe MessageId
}
deriving (forall x.
Rep GetGameHighScoresRequest x -> GetGameHighScoresRequest
forall x.
GetGameHighScoresRequest -> Rep GetGameHighScoresRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetGameHighScoresRequest x -> GetGameHighScoresRequest
$cfrom :: forall x.
GetGameHighScoresRequest -> Rep GetGameHighScoresRequest x
Generic, Int -> GetGameHighScoresRequest -> ShowS
[GetGameHighScoresRequest] -> ShowS
GetGameHighScoresRequest -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetGameHighScoresRequest] -> ShowS
$cshowList :: [GetGameHighScoresRequest] -> ShowS
show :: GetGameHighScoresRequest -> String
$cshow :: GetGameHighScoresRequest -> String
showsPrec :: Int -> GetGameHighScoresRequest -> ShowS
$cshowsPrec :: Int -> GetGameHighScoresRequest -> ShowS
Show)
foldMap deriveJSON'
[ ''SendGameRequest
, ''SetGameScoreRequest
, ''SetGameScoreResult
]
type SendGame
= "sendGame" :> ReqBody '[JSON] SendGameRequest :> Post '[JSON] (Response Message)
sendGame :: SendGameRequest -> ClientM (Response Message)
sendGame :: SendGameRequest -> ClientM (Response Message)
sendGame = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SendGame)
type SetGameScore
= "setGameScore" :> ReqBody '[JSON] SetGameScoreRequest :> Post '[JSON] (Response SetGameScoreResult)
setGameScore :: SetGameScoreRequest -> ClientM (Response SetGameScoreResult)
setGameScore :: SetGameScoreRequest -> ClientM (Response SetGameScoreResult)
setGameScore = forall api.
HasClient ClientM api =>
Proxy api -> Client ClientM api
client (forall {k} (t :: k). Proxy t
Proxy @SetGameScore)
type GetGameHighScores
= "getGameHighScores" :> ReqBody '[JSON] GetGameHighScoresRequest :> Post '[JSON] (Response [GameHighScore])