{-# LANGUAGE DeriveGeneric #-}
module Telegram.Bot.API.Types.Game where
import Data.Aeson (FromJSON (..), ToJSON (..))
import Data.Text (Text)
import GHC.Generics (Generic)
import Telegram.Bot.API.Types.Animation
import Telegram.Bot.API.Types.MessageEntity
import Telegram.Bot.API.Types.PhotoSize
import Telegram.Bot.API.Internal.Utils
data Game = Game
{ Game -> Text
gameTitle :: Text
, Game -> Text
gameDescription :: Text
, Game -> [PhotoSize]
gamePhoto :: [PhotoSize]
, Game -> Maybe Text
gameText :: Maybe Text
, Game -> Maybe [MessageEntity]
gameTextEntities :: Maybe [MessageEntity]
, Game -> Maybe Animation
gameAnimation :: Maybe Animation
}
deriving (forall x. Rep Game x -> Game
forall x. Game -> Rep Game x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Game x -> Game
$cfrom :: forall x. Game -> Rep Game x
Generic, Int -> Game -> ShowS
[Game] -> ShowS
Game -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Game] -> ShowS
$cshowList :: [Game] -> ShowS
show :: Game -> String
$cshow :: Game -> String
showsPrec :: Int -> Game -> ShowS
$cshowsPrec :: Int -> Game -> ShowS
Show)
instance ToJSON Game where toJSON :: Game -> 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 Game where parseJSON :: Value -> Parser Game
parseJSON = forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON