{-# LANGUAGE MultiWayIf #-}
-- CHANGE WITH CAUTION: This is a generated code file generated by https://github.com/Haskell-OpenAPI-Code-Generator/Haskell-OpenAPI-Client-Code-Generator.
{-# LANGUAGE OverloadedStrings #-}

-- | Contains the types generated from the schema GiftCardCreate
module RecurlyClient.Types.GiftCardCreate where

import qualified Control.Monad.Fail
import qualified Data.Aeson
import qualified Data.Aeson as Data.Aeson.Encoding.Internal
import qualified Data.Aeson as Data.Aeson.Types
import qualified Data.Aeson as Data.Aeson.Types.FromJSON
import qualified Data.Aeson as Data.Aeson.Types.Internal
import qualified Data.Aeson as Data.Aeson.Types.ToJSON
import qualified Data.ByteString
import qualified Data.ByteString as Data.ByteString.Internal
import qualified Data.Foldable
import qualified Data.Functor
import qualified Data.Maybe
import qualified Data.Scientific
import qualified Data.Text
import qualified Data.Text as Data.Text.Internal
import qualified Data.Time.Calendar as Data.Time.Calendar.Days
import qualified Data.Time.LocalTime as Data.Time.LocalTime.Internal.ZonedTime
import qualified GHC.Base
import qualified GHC.Classes
import qualified GHC.Int
import qualified GHC.Show
import qualified GHC.Types
import qualified RecurlyClient.Common
import RecurlyClient.TypeAlias
import {-# SOURCE #-} RecurlyClient.Types.AccountPurchase
import {-# SOURCE #-} RecurlyClient.Types.GiftCardDeliveryCreate
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe

{- | Defines the object schema located at @components.schemas.GiftCardCreate@ in the specification.

Gift card details
-}
data GiftCardCreate = GiftCardCreate
    { GiftCardCreate -> Text
giftCardCreateCurrency :: Data.Text.Internal.Text
    -- ^ currency: 3-letter ISO 4217 currency code.
    --
    -- Constraints:
    --
    -- * Maximum length of 3
    , GiftCardCreate -> GiftCardDeliveryCreate
giftCardCreateDelivery :: GiftCardDeliveryCreate
    -- ^ delivery: Gift card delivery details
    , GiftCardCreate -> AccountPurchase
giftCardCreateGifter_account :: AccountPurchase
    -- ^ gifter_account
    , GiftCardCreate -> Text
giftCardCreateProduct_code :: Data.Text.Internal.Text
    -- ^ product_code: The product code or SKU of the gift card product.
    , GiftCardCreate -> Float
giftCardCreateUnit_amount :: GHC.Types.Float
    -- ^ unit_amount: The amount of the gift card, which is the amount of the charge to the gifter account and the amount of credit that is applied to the recipient account upon successful redemption.
    }
    deriving
        ( Int -> GiftCardCreate -> ShowS
[GiftCardCreate] -> ShowS
GiftCardCreate -> String
(Int -> GiftCardCreate -> ShowS)
-> (GiftCardCreate -> String)
-> ([GiftCardCreate] -> ShowS)
-> Show GiftCardCreate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GiftCardCreate -> ShowS
showsPrec :: Int -> GiftCardCreate -> ShowS
$cshow :: GiftCardCreate -> String
show :: GiftCardCreate -> String
$cshowList :: [GiftCardCreate] -> ShowS
showList :: [GiftCardCreate] -> ShowS
GHC.Show.Show
        , GiftCardCreate -> GiftCardCreate -> Bool
(GiftCardCreate -> GiftCardCreate -> Bool)
-> (GiftCardCreate -> GiftCardCreate -> Bool) -> Eq GiftCardCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GiftCardCreate -> GiftCardCreate -> Bool
== :: GiftCardCreate -> GiftCardCreate -> Bool
$c/= :: GiftCardCreate -> GiftCardCreate -> Bool
/= :: GiftCardCreate -> GiftCardCreate -> Bool
GHC.Classes.Eq
        )

instance Data.Aeson.Types.ToJSON.ToJSON GiftCardCreate where
    toJSON :: GiftCardCreate -> Value
toJSON GiftCardCreate
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object ([[Pair]] -> [Pair]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Key
"currency" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..= GiftCardCreate -> Text
giftCardCreateCurrency GiftCardCreate
obj] [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Key
"delivery" Key -> GiftCardDeliveryCreate -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..= GiftCardCreate -> GiftCardDeliveryCreate
giftCardCreateDelivery GiftCardCreate
obj] [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Key
"gifter_account" Key -> AccountPurchase -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..= GiftCardCreate -> AccountPurchase
giftCardCreateGifter_account GiftCardCreate
obj] [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Key
"product_code" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..= GiftCardCreate -> Text
giftCardCreateProduct_code GiftCardCreate
obj] [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Key
"unit_amount" Key -> Float -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..= GiftCardCreate -> Float
giftCardCreateUnit_amount GiftCardCreate
obj] [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [[Pair]]
forall a. Monoid a => a
GHC.Base.mempty))
    toEncoding :: GiftCardCreate -> Encoding
toEncoding GiftCardCreate
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ([Series] -> Series
forall a. Monoid a => [a] -> a
GHC.Base.mconcat ([[Series]] -> [Series]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Key
"currency" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..= GiftCardCreate -> Text
giftCardCreateCurrency GiftCardCreate
obj] [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Key
"delivery" Key -> GiftCardDeliveryCreate -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..= GiftCardCreate -> GiftCardDeliveryCreate
giftCardCreateDelivery GiftCardCreate
obj] [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Key
"gifter_account" Key -> AccountPurchase -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..= GiftCardCreate -> AccountPurchase
giftCardCreateGifter_account GiftCardCreate
obj] [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Key
"product_code" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..= GiftCardCreate -> Text
giftCardCreateProduct_code GiftCardCreate
obj] [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Key
"unit_amount" Key -> Float -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..= GiftCardCreate -> Float
giftCardCreateUnit_amount GiftCardCreate
obj] [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [[Series]]
forall a. Monoid a => a
GHC.Base.mempty)))
instance Data.Aeson.Types.FromJSON.FromJSON GiftCardCreate where
    parseJSON :: Value -> Parser GiftCardCreate
parseJSON = String
-> (Object -> Parser GiftCardCreate)
-> Value
-> Parser GiftCardCreate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"GiftCardCreate" (\Object
obj -> (((((Text
 -> GiftCardDeliveryCreate
 -> AccountPurchase
 -> Text
 -> Float
 -> GiftCardCreate)
-> Parser
     (Text
      -> GiftCardDeliveryCreate
      -> AccountPurchase
      -> Text
      -> Float
      -> GiftCardCreate)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Text
-> GiftCardDeliveryCreate
-> AccountPurchase
-> Text
-> Float
-> GiftCardCreate
GiftCardCreate Parser
  (Text
   -> GiftCardDeliveryCreate
   -> AccountPurchase
   -> Text
   -> Float
   -> GiftCardCreate)
-> Parser Text
-> Parser
     (GiftCardDeliveryCreate
      -> AccountPurchase -> Text -> Float -> GiftCardCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
Data.Aeson.Types.FromJSON..: Key
"currency")) Parser
  (GiftCardDeliveryCreate
   -> AccountPurchase -> Text -> Float -> GiftCardCreate)
-> Parser GiftCardDeliveryCreate
-> Parser (AccountPurchase -> Text -> Float -> GiftCardCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser GiftCardDeliveryCreate
forall a. FromJSON a => Object -> Key -> Parser a
Data.Aeson.Types.FromJSON..: Key
"delivery")) Parser (AccountPurchase -> Text -> Float -> GiftCardCreate)
-> Parser AccountPurchase
-> Parser (Text -> Float -> GiftCardCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser AccountPurchase
forall a. FromJSON a => Object -> Key -> Parser a
Data.Aeson.Types.FromJSON..: Key
"gifter_account")) Parser (Text -> Float -> GiftCardCreate)
-> Parser Text -> Parser (Float -> GiftCardCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
Data.Aeson.Types.FromJSON..: Key
"product_code")) Parser (Float -> GiftCardCreate)
-> Parser Float -> Parser GiftCardCreate
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser Float
forall a. FromJSON a => Object -> Key -> Parser a
Data.Aeson.Types.FromJSON..: Key
"unit_amount"))

-- | Create a new 'GiftCardCreate' with all required fields.
mkGiftCardCreate ::
    -- | 'giftCardCreateCurrency'
    Data.Text.Internal.Text ->
    -- | 'giftCardCreateDelivery'
    GiftCardDeliveryCreate ->
    -- | 'giftCardCreateGifter_account'
    AccountPurchase ->
    -- | 'giftCardCreateProduct_code'
    Data.Text.Internal.Text ->
    -- | 'giftCardCreateUnit_amount'
    GHC.Types.Float ->
    GiftCardCreate
mkGiftCardCreate :: Text
-> GiftCardDeliveryCreate
-> AccountPurchase
-> Text
-> Float
-> GiftCardCreate
mkGiftCardCreate Text
giftCardCreateCurrency GiftCardDeliveryCreate
giftCardCreateDelivery AccountPurchase
giftCardCreateGifter_account Text
giftCardCreateProduct_code Float
giftCardCreateUnit_amount =
    GiftCardCreate
        { giftCardCreateCurrency :: Text
giftCardCreateCurrency = Text
giftCardCreateCurrency
        , giftCardCreateDelivery :: GiftCardDeliveryCreate
giftCardCreateDelivery = GiftCardDeliveryCreate
giftCardCreateDelivery
        , giftCardCreateGifter_account :: AccountPurchase
giftCardCreateGifter_account = AccountPurchase
giftCardCreateGifter_account
        , giftCardCreateProduct_code :: Text
giftCardCreateProduct_code = Text
giftCardCreateProduct_code
        , giftCardCreateUnit_amount :: Float
giftCardCreateUnit_amount = Float
giftCardCreateUnit_amount
        }