{-# LANGUAGE DeriveGeneric #-}
module Telegram.Bot.API.Types.GameHighScore where

import Data.Aeson (FromJSON (..), ToJSON (..))
import GHC.Generics (Generic)

import Telegram.Bot.API.Types.User
import Telegram.Bot.API.Internal.Utils

-- ** 'GameHighScore'

-- | This object represents one row of the high scores table for a game.
data GameHighScore = GameHighScore
  { GameHighScore -> Int
gameHighScorePosition :: Int -- ^ Position in high score table for the game.
  , GameHighScore -> User
gameHighScoreUser     :: User  -- ^ User.
  , GameHighScore -> Int
gameHighScoreScore    :: Int -- ^ Score.
  }
  deriving (forall x. Rep GameHighScore x -> GameHighScore
forall x. GameHighScore -> Rep GameHighScore x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GameHighScore x -> GameHighScore
$cfrom :: forall x. GameHighScore -> Rep GameHighScore x
Generic, Int -> GameHighScore -> ShowS
[GameHighScore] -> ShowS
GameHighScore -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GameHighScore] -> ShowS
$cshowList :: [GameHighScore] -> ShowS
show :: GameHighScore -> String
$cshow :: GameHighScore -> String
showsPrec :: Int -> GameHighScore -> ShowS
$cshowsPrec :: Int -> GameHighScore -> ShowS
Show)

instance ToJSON   GameHighScore where toJSON :: GameHighScore -> Value
toJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance FromJSON GameHighScore where parseJSON :: Value -> Parser GameHighScore
parseJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON