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

import Data.Aeson (FromJSON (..), ToJSON (..))
import Data.Text
import Data.Time.Clock.POSIX (POSIXTime)
import GHC.Generics (Generic)

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

-- ** 'GiveawayWinners'

-- | This object represents a message about the completion of a giveaway with public winners.
data GiveawayWinners = GiveawayWinners
  { GiveawayWinners -> Chat
giveawayWinnersChat :: Chat -- ^ The chat that created the giveaway.
  , GiveawayWinners -> MessageId
giveawayWinnersGiveawayMessageId :: MessageId -- ^ Identifier of the messsage with the giveaway in the chat.
  , GiveawayWinners -> POSIXTime
giveawayWinnersWinnersSelectionDate :: POSIXTime -- ^ Point in time (Unix timestamp) when winners of the giveaway were selected.
  , GiveawayWinners -> Int
giveawayWinnersWinnerCount :: Int -- ^ Total number of winners in the giveaway.
  , GiveawayWinners -> [User]
giveawayWinnersWinners :: [User] -- ^ List of up to 100 winners of the giveaway.
  , GiveawayWinners -> Maybe Int
giveawayWinnersAdditionalChatCount :: Maybe Int -- ^ The number of other chats the user had to join in order to be eligible for the giveaway.
  , GiveawayWinners -> Maybe Int
giveawayWinnersPremiumSubscriptionMonthCount :: Maybe Int -- ^ The number of months the Telegram Premium subscription won from the giveaway will be active for.
  , GiveawayWinners -> Maybe Int
giveawayWinnersUnclaimedPrizeCount :: Maybe Int -- ^ Number of undistributed prizes.
  , GiveawayWinners -> Maybe Bool
giveawayWinnersOnlyNewMembers :: Maybe Bool -- ^ 'True', if only users who had joined the chats after the giveaway started were eligible to win.
  , GiveawayWinners -> Maybe Bool
giveawayWinnersWasRefunded :: Maybe Bool -- ^ 'True', if the giveaway was canceled because the payment for it was refunded.
  , GiveawayWinners -> Maybe Text
giveawayWinnersPrizeDescription :: Maybe Text -- ^ Description of additional giveaway prize.
  }
  deriving ((forall x. GiveawayWinners -> Rep GiveawayWinners x)
-> (forall x. Rep GiveawayWinners x -> GiveawayWinners)
-> Generic GiveawayWinners
forall x. Rep GiveawayWinners x -> GiveawayWinners
forall x. GiveawayWinners -> Rep GiveawayWinners x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GiveawayWinners -> Rep GiveawayWinners x
from :: forall x. GiveawayWinners -> Rep GiveawayWinners x
$cto :: forall x. Rep GiveawayWinners x -> GiveawayWinners
to :: forall x. Rep GiveawayWinners x -> GiveawayWinners
Generic, Int -> GiveawayWinners -> ShowS
[GiveawayWinners] -> ShowS
GiveawayWinners -> String
(Int -> GiveawayWinners -> ShowS)
-> (GiveawayWinners -> String)
-> ([GiveawayWinners] -> ShowS)
-> Show GiveawayWinners
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GiveawayWinners -> ShowS
showsPrec :: Int -> GiveawayWinners -> ShowS
$cshow :: GiveawayWinners -> String
show :: GiveawayWinners -> String
$cshowList :: [GiveawayWinners] -> ShowS
showList :: [GiveawayWinners] -> ShowS
Show)

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