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

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

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

-- ** 'PreCheckoutQuery'

-- | This object contains information about an incoming pre-checkout query.
data PreCheckoutQuery = PreCheckoutQuery
  { PreCheckoutQuery -> Text
preCheckoutQueryId               :: Text                   -- ^ Unique query identifier.
  , PreCheckoutQuery -> User
preCheckoutQueryFrom             :: User                   -- ^ User who sent the query.
  , PreCheckoutQuery -> Text
preCheckoutQueryCurrency         :: Text                   -- ^ Three-letter ISO 4217 currency code
  , PreCheckoutQuery -> Int
preCheckoutQueryTotalAmount      :: Int                  -- ^ Total price in the smallest units of the currency (integer, not float/double). For example, for a price of US$ 1.45 pass amount = 145. See the exp parameter in currencies.json, it shows the number of digits past the decimal point for each currency (2 for the majority of currencies).
  , PreCheckoutQuery -> Text
preCheckoutQueryInvoicePayload   :: Text                   -- ^ Bot specified invoice payload
  , PreCheckoutQuery -> Maybe ShippingOptionId
preCheckoutQueryShippingOptionId :: Maybe ShippingOptionId -- ^ Identifier of the shipping option chosen by the user.
  , PreCheckoutQuery -> Maybe OrderInfo
preCheckoutQueryOrderInfo        :: Maybe OrderInfo        -- ^ Order info provided by the user.
  }
  deriving ((forall x. PreCheckoutQuery -> Rep PreCheckoutQuery x)
-> (forall x. Rep PreCheckoutQuery x -> PreCheckoutQuery)
-> Generic PreCheckoutQuery
forall x. Rep PreCheckoutQuery x -> PreCheckoutQuery
forall x. PreCheckoutQuery -> Rep PreCheckoutQuery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PreCheckoutQuery x -> PreCheckoutQuery
$cfrom :: forall x. PreCheckoutQuery -> Rep PreCheckoutQuery x
Generic, Int -> PreCheckoutQuery -> ShowS
[PreCheckoutQuery] -> ShowS
PreCheckoutQuery -> String
(Int -> PreCheckoutQuery -> ShowS)
-> (PreCheckoutQuery -> String)
-> ([PreCheckoutQuery] -> ShowS)
-> Show PreCheckoutQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PreCheckoutQuery] -> ShowS
$cshowList :: [PreCheckoutQuery] -> ShowS
show :: PreCheckoutQuery -> String
$cshow :: PreCheckoutQuery -> String
showsPrec :: Int -> PreCheckoutQuery -> ShowS
$cshowsPrec :: Int -> PreCheckoutQuery -> ShowS
Show)

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