{-# LANGUAGE ExplicitForAll #-}
{-# 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 different functions to run the operation postCheckoutSessions
module StripeAPI.Operations.PostCheckoutSessions where

import qualified Control.Monad.Fail
import qualified Control.Monad.Trans.Reader
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.Char8
import qualified Data.ByteString.Char8 as Data.ByteString.Internal
import qualified Data.Either
import qualified Data.Functor
import qualified Data.Scientific
import qualified Data.Text
import qualified 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 Data.Vector
import qualified GHC.Base
import qualified GHC.Classes
import qualified GHC.Int
import qualified GHC.Show
import qualified GHC.Types
import qualified Network.HTTP.Client
import qualified Network.HTTP.Client as Network.HTTP.Client.Request
import qualified Network.HTTP.Client as Network.HTTP.Client.Types
import qualified Network.HTTP.Simple
import qualified Network.HTTP.Types
import qualified Network.HTTP.Types as Network.HTTP.Types.Status
import qualified Network.HTTP.Types as Network.HTTP.Types.URI
import qualified StripeAPI.Common
import StripeAPI.Types
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe

-- | > POST /v1/checkout/sessions
--
-- \<p>Creates a Session object.\<\/p>
postCheckoutSessions ::
  forall m.
  StripeAPI.Common.MonadHTTP m =>
  -- | The request body to send
  PostCheckoutSessionsRequestBody ->
  -- | Monadic computation which returns the result of the operation
  StripeAPI.Common.ClientT m (Network.HTTP.Client.Types.Response PostCheckoutSessionsResponse)
postCheckoutSessions :: PostCheckoutSessionsRequestBody
-> ClientT m (Response PostCheckoutSessionsResponse)
postCheckoutSessions PostCheckoutSessionsRequestBody
body =
  (Response ByteString -> Response PostCheckoutSessionsResponse)
-> ClientT m (Response ByteString)
-> ClientT m (Response PostCheckoutSessionsResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
    ( \Response ByteString
response_0 ->
        (ByteString -> PostCheckoutSessionsResponse)
-> Response ByteString -> Response PostCheckoutSessionsResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
          ( (String -> PostCheckoutSessionsResponse)
-> (PostCheckoutSessionsResponse -> PostCheckoutSessionsResponse)
-> Either String PostCheckoutSessionsResponse
-> PostCheckoutSessionsResponse
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
Data.Either.either String -> PostCheckoutSessionsResponse
PostCheckoutSessionsResponseError PostCheckoutSessionsResponse -> PostCheckoutSessionsResponse
forall a. a -> a
GHC.Base.id
              (Either String PostCheckoutSessionsResponse
 -> PostCheckoutSessionsResponse)
-> (ByteString -> Either String PostCheckoutSessionsResponse)
-> ByteString
-> PostCheckoutSessionsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. ( \Response ByteString
response ByteString
body ->
                             if
                                 | (\Status
status_1 -> Status -> Int
Network.HTTP.Types.Status.statusCode Status
status_1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Int
200) (Response ByteString -> Status
forall body. Response body -> Status
Network.HTTP.Client.Types.responseStatus Response ByteString
response) ->
                                   Checkout'session -> PostCheckoutSessionsResponse
PostCheckoutSessionsResponse200
                                     (Checkout'session -> PostCheckoutSessionsResponse)
-> Either String Checkout'session
-> Either String PostCheckoutSessionsResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String Checkout'session
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                          Data.Either.Either
                                                            GHC.Base.String
                                                            Checkout'session
                                                      )
                                 | Bool -> Status -> Bool
forall a b. a -> b -> a
GHC.Base.const Bool
GHC.Types.True (Response ByteString -> Status
forall body. Response body -> Status
Network.HTTP.Client.Types.responseStatus Response ByteString
response) ->
                                   Error -> PostCheckoutSessionsResponse
PostCheckoutSessionsResponseDefault
                                     (Error -> PostCheckoutSessionsResponse)
-> Either String Error
-> Either String PostCheckoutSessionsResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String Error
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                          Data.Either.Either
                                                            GHC.Base.String
                                                            Error
                                                      )
                                 | Bool
GHC.Base.otherwise -> String -> Either String PostCheckoutSessionsResponse
forall a b. a -> Either a b
Data.Either.Left String
"Missing default response type"
                         )
                Response ByteString
response_0
          )
          Response ByteString
response_0
    )
    (Text
-> Text
-> [QueryParameter]
-> Maybe PostCheckoutSessionsRequestBody
-> RequestBodyEncoding
-> ClientT m (Response ByteString)
forall (m :: * -> *) body.
(MonadHTTP m, ToJSON body) =>
Text
-> Text
-> [QueryParameter]
-> Maybe body
-> RequestBodyEncoding
-> ClientT m (Response ByteString)
StripeAPI.Common.doBodyCallWithConfigurationM (Text -> Text
Data.Text.toUpper (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
GHC.Base.$ String -> Text
Data.Text.pack String
"POST") (String -> Text
Data.Text.pack String
"/v1/checkout/sessions") [QueryParameter]
forall a. Monoid a => a
GHC.Base.mempty (PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBody
forall a. a -> Maybe a
GHC.Maybe.Just PostCheckoutSessionsRequestBody
body) RequestBodyEncoding
StripeAPI.Common.RequestBodyEncodingFormData)

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema@ in the specification.
data PostCheckoutSessionsRequestBody = PostCheckoutSessionsRequestBody
  { -- | allow_promotion_codes: Enables user redeemable promotion codes.
    PostCheckoutSessionsRequestBody -> Maybe Bool
postCheckoutSessionsRequestBodyAllowPromotionCodes :: (GHC.Maybe.Maybe GHC.Types.Bool),
    -- | automatic_tax
    PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyAutomaticTax'
postCheckoutSessionsRequestBodyAutomaticTax :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyAutomaticTax'),
    -- | billing_address_collection: Specify whether Checkout should collect the customer\'s billing address.
    PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
postCheckoutSessionsRequestBodyBillingAddressCollection :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'),
    -- | cancel_url: The URL the customer will be directed to if they decide to cancel payment and return to your website.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBody -> Text
postCheckoutSessionsRequestBodyCancelUrl :: Data.Text.Internal.Text,
    -- | client_reference_id: A unique string to reference the Checkout Session. This can be a
    -- customer ID, a cart ID, or similar, and can be used to reconcile the
    -- session with your internal systems.
    --
    -- Constraints:
    --
    -- * Maximum length of 200
    PostCheckoutSessionsRequestBody -> Maybe Text
postCheckoutSessionsRequestBodyClientReferenceId :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | customer: ID of an existing Customer, if one exists. In \`payment\` mode, the customer’s most recent card
    -- payment method will be used to prefill the email, name, card details, and billing address
    -- on the Checkout page. In \`subscription\` mode, the customer’s [default payment method](https:\/\/stripe.com\/docs\/api\/customers\/update\#update_customer-invoice_settings-default_payment_method)
    -- will be used if it’s a card, and otherwise the most recent card will be used. A valid billing address is required for Checkout to prefill the customer\'s card details.
    --
    -- If the customer changes their email on the Checkout page, the Customer object will be updated with the new email.
    --
    -- If blank for Checkout Sessions in \`payment\` or \`subscription\` mode, Checkout will create a new Customer object based on information provided during the payment flow.
    --
    -- You can set [\`payment_intent_data.setup_future_usage\`](https:\/\/stripe.com\/docs\/api\/checkout\/sessions\/create\#create_checkout_session-payment_intent_data-setup_future_usage) to have Checkout automatically attach the payment method to the Customer you pass in for future reuse.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBody -> Maybe Text
postCheckoutSessionsRequestBodyCustomer :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | customer_email: If provided, this value will be used when the Customer object is created.
    -- If not provided, customers will be asked to enter their email address.
    -- Use this parameter to prefill customer data if you already have an email
    -- on file. To access information about the customer once a session is
    -- complete, use the \`customer\` field.
    PostCheckoutSessionsRequestBody -> Maybe Text
postCheckoutSessionsRequestBodyCustomerEmail :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | customer_update: Controls what fields on Customer can be updated by the Checkout Session. Can only be provided when \`customer\` is provided.
    PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
postCheckoutSessionsRequestBodyCustomerUpdate :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'),
    -- | discounts: The coupon or promotion code to apply to this Session. Currently, only up to one may be specified.
    PostCheckoutSessionsRequestBody
-> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
postCheckoutSessionsRequestBodyDiscounts :: (GHC.Maybe.Maybe ([PostCheckoutSessionsRequestBodyDiscounts'])),
    -- | expand: Specifies which fields in the response should be expanded.
    PostCheckoutSessionsRequestBody -> Maybe [Text]
postCheckoutSessionsRequestBodyExpand :: (GHC.Maybe.Maybe ([Data.Text.Internal.Text])),
    -- | line_items: A list of items the customer is purchasing. Use this parameter to pass one-time or recurring [Prices](https:\/\/stripe.com\/docs\/api\/prices).
    --
    -- For \`payment\` mode, there is a maximum of 100 line items, however it is recommended to consolidate line items if there are more than a few dozen.
    --
    -- For \`subscription\` mode, there is a maximum of 20 line items with recurring Prices and 20 line items with one-time Prices. Line items with one-time Prices in will be on the initial invoice only.
    PostCheckoutSessionsRequestBody
-> Maybe [PostCheckoutSessionsRequestBodyLineItems']
postCheckoutSessionsRequestBodyLineItems :: (GHC.Maybe.Maybe ([PostCheckoutSessionsRequestBodyLineItems'])),
    -- | locale: The IETF language tag of the locale Checkout is displayed in. If blank or \`auto\`, the browser\'s locale is used.
    PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyLocale'
postCheckoutSessionsRequestBodyLocale :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyLocale'),
    -- | metadata: Set of [key-value pairs](https:\/\/stripe.com\/docs\/api\/metadata) that you can attach to an object. This can be useful for storing additional information about the object in a structured format. Individual keys can be unset by posting an empty value to them. All keys can be unset by posting an empty value to \`metadata\`.
    PostCheckoutSessionsRequestBody -> Maybe Object
postCheckoutSessionsRequestBodyMetadata :: (GHC.Maybe.Maybe Data.Aeson.Types.Internal.Object),
    -- | mode: The mode of the Checkout Session. Required when using prices or \`setup\` mode. Pass \`subscription\` if the Checkout Session includes at least one recurring item.
    PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyMode'
postCheckoutSessionsRequestBodyMode :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyMode'),
    -- | payment_intent_data: A subset of parameters to be passed to PaymentIntent creation for Checkout Sessions in \`payment\` mode.
    PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
postCheckoutSessionsRequestBodyPaymentIntentData :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'),
    -- | payment_method_options: Payment-method-specific configuration.
    PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
postCheckoutSessionsRequestBodyPaymentMethodOptions :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'),
    -- | payment_method_types: A list of the types of payment methods (e.g., \`card\`) this Checkout Session can accept.
    --
    -- Read more about the supported payment methods and their requirements in our [payment
    -- method details guide](\/docs\/payments\/checkout\/payment-methods).
    --
    -- If multiple payment methods are passed, Checkout will dynamically reorder them to
    -- prioritize the most relevant payment methods based on the customer\'s location and
    -- other characteristics.
    PostCheckoutSessionsRequestBody
-> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
postCheckoutSessionsRequestBodyPaymentMethodTypes :: (GHC.Maybe.Maybe ([PostCheckoutSessionsRequestBodyPaymentMethodTypes'])),
    -- | setup_intent_data: A subset of parameters to be passed to SetupIntent creation for Checkout Sessions in \`setup\` mode.
    PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
postCheckoutSessionsRequestBodySetupIntentData :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodySetupIntentData'),
    -- | shipping_address_collection: When set, provides configuration for Checkout to collect a shipping address from a customer.
    PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
postCheckoutSessionsRequestBodyShippingAddressCollection :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'),
    -- | shipping_rates: The shipping rate to apply to this Session. Currently, only up to one may be specified
    PostCheckoutSessionsRequestBody -> Maybe [Text]
postCheckoutSessionsRequestBodyShippingRates :: (GHC.Maybe.Maybe ([Data.Text.Internal.Text])),
    -- | submit_type: Describes the type of transaction being performed by Checkout in order to customize
    -- relevant text on the page, such as the submit button. \`submit_type\` can only be
    -- specified on Checkout Sessions in \`payment\` mode, but not Checkout Sessions
    -- in \`subscription\` or \`setup\` mode.
    PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodySubmitType'
postCheckoutSessionsRequestBodySubmitType :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodySubmitType'),
    -- | subscription_data: A subset of parameters to be passed to subscription creation for Checkout Sessions in \`subscription\` mode.
    PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
postCheckoutSessionsRequestBodySubscriptionData :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodySubscriptionData'),
    -- | success_url: The URL to which Stripe should send customers when payment or setup
    -- is complete.
    -- If you’d like access to the Checkout Session for the successful
    -- payment, read more about it in the guide on [fulfilling orders](https:\/\/stripe.com\/docs\/payments\/checkout\/fulfill-orders).
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBody -> Text
postCheckoutSessionsRequestBodySuccessUrl :: Data.Text.Internal.Text,
    -- | tax_id_collection: Controls tax ID collection settings for the session.
    PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
postCheckoutSessionsRequestBodyTaxIdCollection :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyTaxIdCollection')
  }
  deriving
    ( Int -> PostCheckoutSessionsRequestBody -> ShowS
[PostCheckoutSessionsRequestBody] -> ShowS
PostCheckoutSessionsRequestBody -> String
(Int -> PostCheckoutSessionsRequestBody -> ShowS)
-> (PostCheckoutSessionsRequestBody -> String)
-> ([PostCheckoutSessionsRequestBody] -> ShowS)
-> Show PostCheckoutSessionsRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBody] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBody] -> ShowS
show :: PostCheckoutSessionsRequestBody -> String
$cshow :: PostCheckoutSessionsRequestBody -> String
showsPrec :: Int -> PostCheckoutSessionsRequestBody -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsRequestBody -> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBody
-> PostCheckoutSessionsRequestBody -> Bool
(PostCheckoutSessionsRequestBody
 -> PostCheckoutSessionsRequestBody -> Bool)
-> (PostCheckoutSessionsRequestBody
    -> PostCheckoutSessionsRequestBody -> Bool)
-> Eq PostCheckoutSessionsRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBody
-> PostCheckoutSessionsRequestBody -> Bool
$c/= :: PostCheckoutSessionsRequestBody
-> PostCheckoutSessionsRequestBody -> Bool
== :: PostCheckoutSessionsRequestBody
-> PostCheckoutSessionsRequestBody -> Bool
$c== :: PostCheckoutSessionsRequestBody
-> PostCheckoutSessionsRequestBody -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBody where
  toJSON :: PostCheckoutSessionsRequestBody -> Value
toJSON PostCheckoutSessionsRequestBody
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"allow_promotion_codes" Text -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Maybe Bool
postCheckoutSessionsRequestBodyAllowPromotionCodes PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"automatic_tax" Text -> Maybe PostCheckoutSessionsRequestBodyAutomaticTax' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyAutomaticTax'
postCheckoutSessionsRequestBodyAutomaticTax PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"billing_address_collection" Text
-> Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
postCheckoutSessionsRequestBodyBillingAddressCollection PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"cancel_url" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Text
postCheckoutSessionsRequestBodyCancelUrl PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"client_reference_id" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Maybe Text
postCheckoutSessionsRequestBodyClientReferenceId PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"customer" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Maybe Text
postCheckoutSessionsRequestBodyCustomer PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"customer_email" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Maybe Text
postCheckoutSessionsRequestBodyCustomerEmail PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"customer_update" Text
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
postCheckoutSessionsRequestBodyCustomerUpdate PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"discounts" Text -> Maybe [PostCheckoutSessionsRequestBodyDiscounts'] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
postCheckoutSessionsRequestBodyDiscounts PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"expand" Text -> Maybe [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Maybe [Text]
postCheckoutSessionsRequestBodyExpand PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"line_items" Text -> Maybe [PostCheckoutSessionsRequestBodyLineItems'] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe [PostCheckoutSessionsRequestBodyLineItems']
postCheckoutSessionsRequestBodyLineItems PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"locale" Text -> Maybe PostCheckoutSessionsRequestBodyLocale' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyLocale'
postCheckoutSessionsRequestBodyLocale PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text -> Maybe Object -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Maybe Object
postCheckoutSessionsRequestBodyMetadata PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"mode" Text -> Maybe PostCheckoutSessionsRequestBodyMode' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyMode'
postCheckoutSessionsRequestBodyMode PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"payment_intent_data" Text
-> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
postCheckoutSessionsRequestBodyPaymentIntentData PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"payment_method_options" Text
-> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
postCheckoutSessionsRequestBodyPaymentMethodOptions PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"payment_method_types" Text
-> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
postCheckoutSessionsRequestBodyPaymentMethodTypes PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"setup_intent_data" Text
-> Maybe PostCheckoutSessionsRequestBodySetupIntentData' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
postCheckoutSessionsRequestBodySetupIntentData PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"shipping_address_collection" Text
-> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
postCheckoutSessionsRequestBodyShippingAddressCollection PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"shipping_rates" Text -> Maybe [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Maybe [Text]
postCheckoutSessionsRequestBodyShippingRates PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"submit_type" Text -> Maybe PostCheckoutSessionsRequestBodySubmitType' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodySubmitType'
postCheckoutSessionsRequestBodySubmitType PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"subscription_data" Text
-> Maybe PostCheckoutSessionsRequestBodySubscriptionData' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
postCheckoutSessionsRequestBodySubscriptionData PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"success_url" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Text
postCheckoutSessionsRequestBodySuccessUrl PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"tax_id_collection" Text
-> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
postCheckoutSessionsRequestBodyTaxIdCollection PostCheckoutSessionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBody -> Encoding
toEncoding PostCheckoutSessionsRequestBody
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"allow_promotion_codes" Text -> Maybe Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Maybe Bool
postCheckoutSessionsRequestBodyAllowPromotionCodes PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"automatic_tax" Text
-> Maybe PostCheckoutSessionsRequestBodyAutomaticTax' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyAutomaticTax'
postCheckoutSessionsRequestBodyAutomaticTax PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"billing_address_collection" Text
-> Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
postCheckoutSessionsRequestBodyBillingAddressCollection PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"cancel_url" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Text
postCheckoutSessionsRequestBodyCancelUrl PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"client_reference_id" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Maybe Text
postCheckoutSessionsRequestBodyClientReferenceId PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"customer" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Maybe Text
postCheckoutSessionsRequestBodyCustomer PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"customer_email" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Maybe Text
postCheckoutSessionsRequestBodyCustomerEmail PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"customer_update" Text
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
postCheckoutSessionsRequestBodyCustomerUpdate PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"discounts" Text -> Maybe [PostCheckoutSessionsRequestBodyDiscounts'] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
postCheckoutSessionsRequestBodyDiscounts PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"expand" Text -> Maybe [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Maybe [Text]
postCheckoutSessionsRequestBodyExpand PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"line_items" Text -> Maybe [PostCheckoutSessionsRequestBodyLineItems'] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe [PostCheckoutSessionsRequestBodyLineItems']
postCheckoutSessionsRequestBodyLineItems PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"locale" Text -> Maybe PostCheckoutSessionsRequestBodyLocale' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyLocale'
postCheckoutSessionsRequestBodyLocale PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"metadata" Text -> Maybe Object -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Maybe Object
postCheckoutSessionsRequestBodyMetadata PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"mode" Text -> Maybe PostCheckoutSessionsRequestBodyMode' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyMode'
postCheckoutSessionsRequestBodyMode PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"payment_intent_data" Text
-> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
postCheckoutSessionsRequestBodyPaymentIntentData PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"payment_method_options" Text
-> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
postCheckoutSessionsRequestBodyPaymentMethodOptions PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"payment_method_types" Text
-> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
postCheckoutSessionsRequestBodyPaymentMethodTypes PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"setup_intent_data" Text
-> Maybe PostCheckoutSessionsRequestBodySetupIntentData' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
postCheckoutSessionsRequestBodySetupIntentData PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"shipping_address_collection" Text
-> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
postCheckoutSessionsRequestBodyShippingAddressCollection PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"shipping_rates" Text -> Maybe [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Maybe [Text]
postCheckoutSessionsRequestBodyShippingRates PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"submit_type" Text -> Maybe PostCheckoutSessionsRequestBodySubmitType' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodySubmitType'
postCheckoutSessionsRequestBodySubmitType PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"subscription_data" Text
-> Maybe PostCheckoutSessionsRequestBodySubscriptionData' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
postCheckoutSessionsRequestBodySubscriptionData PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"success_url" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody -> Text
postCheckoutSessionsRequestBodySuccessUrl PostCheckoutSessionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"tax_id_collection" Text
-> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBody
-> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
postCheckoutSessionsRequestBodyTaxIdCollection PostCheckoutSessionsRequestBody
obj))))))))))))))))))))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBody where
  parseJSON :: Value -> Parser PostCheckoutSessionsRequestBody
parseJSON = String
-> (Object -> Parser PostCheckoutSessionsRequestBody)
-> Value
-> Parser PostCheckoutSessionsRequestBody
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBody" (\Object
obj -> ((((((((((((((((((((((((Maybe Bool
 -> Maybe PostCheckoutSessionsRequestBodyAutomaticTax'
 -> Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
 -> Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
 -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
 -> Maybe [Text]
 -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
 -> Maybe PostCheckoutSessionsRequestBodyLocale'
 -> Maybe Object
 -> Maybe PostCheckoutSessionsRequestBodyMode'
 -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
 -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
 -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
 -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
 -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
 -> Maybe [Text]
 -> Maybe PostCheckoutSessionsRequestBodySubmitType'
 -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
 -> Text
 -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
 -> PostCheckoutSessionsRequestBody)
-> Parser
     (Maybe Bool
      -> Maybe PostCheckoutSessionsRequestBodyAutomaticTax'
      -> Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
      -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
      -> Maybe [Text]
      -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
      -> Maybe PostCheckoutSessionsRequestBodyLocale'
      -> Maybe Object
      -> Maybe PostCheckoutSessionsRequestBodyMode'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Bool
-> Maybe PostCheckoutSessionsRequestBodyAutomaticTax'
-> Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
-> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
-> Maybe [Text]
-> Maybe [PostCheckoutSessionsRequestBodyLineItems']
-> Maybe PostCheckoutSessionsRequestBodyLocale'
-> Maybe Object
-> Maybe PostCheckoutSessionsRequestBodyMode'
-> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
-> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
-> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
-> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
-> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> Maybe [Text]
-> Maybe PostCheckoutSessionsRequestBodySubmitType'
-> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
-> Text
-> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
-> PostCheckoutSessionsRequestBody
PostCheckoutSessionsRequestBody Parser
  (Maybe Bool
   -> Maybe PostCheckoutSessionsRequestBodyAutomaticTax'
   -> Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
   -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
   -> Maybe [Text]
   -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
   -> Maybe PostCheckoutSessionsRequestBodyLocale'
   -> Maybe Object
   -> Maybe PostCheckoutSessionsRequestBodyMode'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe Bool)
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyAutomaticTax'
      -> Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
      -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
      -> Maybe [Text]
      -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
      -> Maybe PostCheckoutSessionsRequestBodyLocale'
      -> Maybe Object
      -> Maybe PostCheckoutSessionsRequestBodyMode'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"allow_promotion_codes")) Parser
  (Maybe PostCheckoutSessionsRequestBodyAutomaticTax'
   -> Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
   -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
   -> Maybe [Text]
   -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
   -> Maybe PostCheckoutSessionsRequestBodyLocale'
   -> Maybe Object
   -> Maybe PostCheckoutSessionsRequestBodyMode'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe PostCheckoutSessionsRequestBodyAutomaticTax')
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
      -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
      -> Maybe [Text]
      -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
      -> Maybe PostCheckoutSessionsRequestBodyLocale'
      -> Maybe Object
      -> Maybe PostCheckoutSessionsRequestBodyMode'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe PostCheckoutSessionsRequestBodyAutomaticTax')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"automatic_tax")) Parser
  (Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
   -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
   -> Maybe [Text]
   -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
   -> Maybe PostCheckoutSessionsRequestBodyLocale'
   -> Maybe Object
   -> Maybe PostCheckoutSessionsRequestBodyMode'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection')
-> Parser
     (Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
      -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
      -> Maybe [Text]
      -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
      -> Maybe PostCheckoutSessionsRequestBodyLocale'
      -> Maybe Object
      -> Maybe PostCheckoutSessionsRequestBodyMode'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"billing_address_collection")) Parser
  (Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
   -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
   -> Maybe [Text]
   -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
   -> Maybe PostCheckoutSessionsRequestBodyLocale'
   -> Maybe Object
   -> Maybe PostCheckoutSessionsRequestBodyMode'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser Text
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
      -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
      -> Maybe [Text]
      -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
      -> Maybe PostCheckoutSessionsRequestBodyLocale'
      -> Maybe Object
      -> Maybe PostCheckoutSessionsRequestBodyMode'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"cancel_url")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
   -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
   -> Maybe [Text]
   -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
   -> Maybe PostCheckoutSessionsRequestBodyLocale'
   -> Maybe Object
   -> Maybe PostCheckoutSessionsRequestBodyMode'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
      -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
      -> Maybe [Text]
      -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
      -> Maybe PostCheckoutSessionsRequestBodyLocale'
      -> Maybe Object
      -> Maybe PostCheckoutSessionsRequestBodyMode'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"client_reference_id")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
   -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
   -> Maybe [Text]
   -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
   -> Maybe PostCheckoutSessionsRequestBodyLocale'
   -> Maybe Object
   -> Maybe PostCheckoutSessionsRequestBodyMode'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
      -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
      -> Maybe [Text]
      -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
      -> Maybe PostCheckoutSessionsRequestBodyLocale'
      -> Maybe Object
      -> Maybe PostCheckoutSessionsRequestBodyMode'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"customer")) Parser
  (Maybe Text
   -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
   -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
   -> Maybe [Text]
   -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
   -> Maybe PostCheckoutSessionsRequestBodyLocale'
   -> Maybe Object
   -> Maybe PostCheckoutSessionsRequestBodyMode'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe Text)
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
      -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
      -> Maybe [Text]
      -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
      -> Maybe PostCheckoutSessionsRequestBodyLocale'
      -> Maybe Object
      -> Maybe PostCheckoutSessionsRequestBodyMode'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"customer_email")) Parser
  (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
   -> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
   -> Maybe [Text]
   -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
   -> Maybe PostCheckoutSessionsRequestBodyLocale'
   -> Maybe Object
   -> Maybe PostCheckoutSessionsRequestBodyMode'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate')
-> Parser
     (Maybe [PostCheckoutSessionsRequestBodyDiscounts']
      -> Maybe [Text]
      -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
      -> Maybe PostCheckoutSessionsRequestBodyLocale'
      -> Maybe Object
      -> Maybe PostCheckoutSessionsRequestBodyMode'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"customer_update")) Parser
  (Maybe [PostCheckoutSessionsRequestBodyDiscounts']
   -> Maybe [Text]
   -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
   -> Maybe PostCheckoutSessionsRequestBodyLocale'
   -> Maybe Object
   -> Maybe PostCheckoutSessionsRequestBodyMode'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe [PostCheckoutSessionsRequestBodyDiscounts'])
-> Parser
     (Maybe [Text]
      -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
      -> Maybe PostCheckoutSessionsRequestBodyLocale'
      -> Maybe Object
      -> Maybe PostCheckoutSessionsRequestBodyMode'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe [PostCheckoutSessionsRequestBodyDiscounts'])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"discounts")) Parser
  (Maybe [Text]
   -> Maybe [PostCheckoutSessionsRequestBodyLineItems']
   -> Maybe PostCheckoutSessionsRequestBodyLocale'
   -> Maybe Object
   -> Maybe PostCheckoutSessionsRequestBodyMode'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe [Text])
-> Parser
     (Maybe [PostCheckoutSessionsRequestBodyLineItems']
      -> Maybe PostCheckoutSessionsRequestBodyLocale'
      -> Maybe Object
      -> Maybe PostCheckoutSessionsRequestBodyMode'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"expand")) Parser
  (Maybe [PostCheckoutSessionsRequestBodyLineItems']
   -> Maybe PostCheckoutSessionsRequestBodyLocale'
   -> Maybe Object
   -> Maybe PostCheckoutSessionsRequestBodyMode'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe [PostCheckoutSessionsRequestBodyLineItems'])
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyLocale'
      -> Maybe Object
      -> Maybe PostCheckoutSessionsRequestBodyMode'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe [PostCheckoutSessionsRequestBodyLineItems'])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"line_items")) Parser
  (Maybe PostCheckoutSessionsRequestBodyLocale'
   -> Maybe Object
   -> Maybe PostCheckoutSessionsRequestBodyMode'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe PostCheckoutSessionsRequestBodyLocale')
-> Parser
     (Maybe Object
      -> Maybe PostCheckoutSessionsRequestBodyMode'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text -> Parser (Maybe PostCheckoutSessionsRequestBodyLocale')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"locale")) Parser
  (Maybe Object
   -> Maybe PostCheckoutSessionsRequestBodyMode'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe Object)
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyMode'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"metadata")) Parser
  (Maybe PostCheckoutSessionsRequestBodyMode'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe PostCheckoutSessionsRequestBodyMode')
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text -> Parser (Maybe PostCheckoutSessionsRequestBodyMode')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"mode")) Parser
  (Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe PostCheckoutSessionsRequestBodyPaymentIntentData')
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
      -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe PostCheckoutSessionsRequestBodyPaymentIntentData')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"payment_intent_data")) Parser
  (Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
   -> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions')
-> Parser
     (Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
      -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"payment_method_options")) Parser
  (Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
   -> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser
     (Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes'])
-> Parser
     (Maybe PostCheckoutSessionsRequestBodySetupIntentData'
      -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes'])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"payment_method_types")) Parser
  (Maybe PostCheckoutSessionsRequestBodySetupIntentData'
   -> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe PostCheckoutSessionsRequestBodySetupIntentData')
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
      -> Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe PostCheckoutSessionsRequestBodySetupIntentData')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"setup_intent_data")) Parser
  (Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
   -> Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection')
-> Parser
     (Maybe [Text]
      -> Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"shipping_address_collection")) Parser
  (Maybe [Text]
   -> Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe [Text])
-> Parser
     (Maybe PostCheckoutSessionsRequestBodySubmitType'
      -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"shipping_rates")) Parser
  (Maybe PostCheckoutSessionsRequestBodySubmitType'
   -> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe PostCheckoutSessionsRequestBodySubmitType')
-> Parser
     (Maybe PostCheckoutSessionsRequestBodySubscriptionData'
      -> Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe PostCheckoutSessionsRequestBodySubmitType')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"submit_type")) Parser
  (Maybe PostCheckoutSessionsRequestBodySubscriptionData'
   -> Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe PostCheckoutSessionsRequestBodySubscriptionData')
-> Parser
     (Text
      -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe PostCheckoutSessionsRequestBodySubscriptionData')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"subscription_data")) Parser
  (Text
   -> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser Text
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
      -> PostCheckoutSessionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"success_url")) Parser
  (Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
   -> PostCheckoutSessionsRequestBody)
-> Parser (Maybe PostCheckoutSessionsRequestBodyTaxIdCollection')
-> Parser PostCheckoutSessionsRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe PostCheckoutSessionsRequestBodyTaxIdCollection')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"tax_id_collection"))

-- | Create a new 'PostCheckoutSessionsRequestBody' with all required fields.
mkPostCheckoutSessionsRequestBody ::
  -- | 'postCheckoutSessionsRequestBodyCancelUrl'
  Data.Text.Internal.Text ->
  -- | 'postCheckoutSessionsRequestBodySuccessUrl'
  Data.Text.Internal.Text ->
  PostCheckoutSessionsRequestBody
mkPostCheckoutSessionsRequestBody :: Text -> Text -> PostCheckoutSessionsRequestBody
mkPostCheckoutSessionsRequestBody Text
postCheckoutSessionsRequestBodyCancelUrl Text
postCheckoutSessionsRequestBodySuccessUrl =
  PostCheckoutSessionsRequestBody :: Maybe Bool
-> Maybe PostCheckoutSessionsRequestBodyAutomaticTax'
-> Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
-> Maybe [PostCheckoutSessionsRequestBodyDiscounts']
-> Maybe [Text]
-> Maybe [PostCheckoutSessionsRequestBodyLineItems']
-> Maybe PostCheckoutSessionsRequestBodyLocale'
-> Maybe Object
-> Maybe PostCheckoutSessionsRequestBodyMode'
-> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
-> Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
-> Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
-> Maybe PostCheckoutSessionsRequestBodySetupIntentData'
-> Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> Maybe [Text]
-> Maybe PostCheckoutSessionsRequestBodySubmitType'
-> Maybe PostCheckoutSessionsRequestBodySubscriptionData'
-> Text
-> Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
-> PostCheckoutSessionsRequestBody
PostCheckoutSessionsRequestBody
    { postCheckoutSessionsRequestBodyAllowPromotionCodes :: Maybe Bool
postCheckoutSessionsRequestBodyAllowPromotionCodes = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyAutomaticTax :: Maybe PostCheckoutSessionsRequestBodyAutomaticTax'
postCheckoutSessionsRequestBodyAutomaticTax = Maybe PostCheckoutSessionsRequestBodyAutomaticTax'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyBillingAddressCollection :: Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
postCheckoutSessionsRequestBodyBillingAddressCollection = Maybe PostCheckoutSessionsRequestBodyBillingAddressCollection'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyCancelUrl :: Text
postCheckoutSessionsRequestBodyCancelUrl = Text
postCheckoutSessionsRequestBodyCancelUrl,
      postCheckoutSessionsRequestBodyClientReferenceId :: Maybe Text
postCheckoutSessionsRequestBodyClientReferenceId = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyCustomer :: Maybe Text
postCheckoutSessionsRequestBodyCustomer = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyCustomerEmail :: Maybe Text
postCheckoutSessionsRequestBodyCustomerEmail = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyCustomerUpdate :: Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
postCheckoutSessionsRequestBodyCustomerUpdate = Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyDiscounts :: Maybe [PostCheckoutSessionsRequestBodyDiscounts']
postCheckoutSessionsRequestBodyDiscounts = Maybe [PostCheckoutSessionsRequestBodyDiscounts']
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyExpand :: Maybe [Text]
postCheckoutSessionsRequestBodyExpand = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems :: Maybe [PostCheckoutSessionsRequestBodyLineItems']
postCheckoutSessionsRequestBodyLineItems = Maybe [PostCheckoutSessionsRequestBodyLineItems']
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLocale :: Maybe PostCheckoutSessionsRequestBodyLocale'
postCheckoutSessionsRequestBodyLocale = Maybe PostCheckoutSessionsRequestBodyLocale'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyMetadata :: Maybe Object
postCheckoutSessionsRequestBodyMetadata = Maybe Object
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyMode :: Maybe PostCheckoutSessionsRequestBodyMode'
postCheckoutSessionsRequestBodyMode = Maybe PostCheckoutSessionsRequestBodyMode'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData :: Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
postCheckoutSessionsRequestBodyPaymentIntentData = Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentMethodOptions :: Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
postCheckoutSessionsRequestBodyPaymentMethodOptions = Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentMethodTypes :: Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
postCheckoutSessionsRequestBodyPaymentMethodTypes = Maybe [PostCheckoutSessionsRequestBodyPaymentMethodTypes']
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodySetupIntentData :: Maybe PostCheckoutSessionsRequestBodySetupIntentData'
postCheckoutSessionsRequestBodySetupIntentData = Maybe PostCheckoutSessionsRequestBodySetupIntentData'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyShippingAddressCollection :: Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
postCheckoutSessionsRequestBodyShippingAddressCollection = Maybe PostCheckoutSessionsRequestBodyShippingAddressCollection'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyShippingRates :: Maybe [Text]
postCheckoutSessionsRequestBodyShippingRates = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodySubmitType :: Maybe PostCheckoutSessionsRequestBodySubmitType'
postCheckoutSessionsRequestBodySubmitType = Maybe PostCheckoutSessionsRequestBodySubmitType'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodySubscriptionData :: Maybe PostCheckoutSessionsRequestBodySubscriptionData'
postCheckoutSessionsRequestBodySubscriptionData = Maybe PostCheckoutSessionsRequestBodySubscriptionData'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodySuccessUrl :: Text
postCheckoutSessionsRequestBodySuccessUrl = Text
postCheckoutSessionsRequestBodySuccessUrl,
      postCheckoutSessionsRequestBodyTaxIdCollection :: Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
postCheckoutSessionsRequestBodyTaxIdCollection = Maybe PostCheckoutSessionsRequestBodyTaxIdCollection'
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.automatic_tax@ in the specification.
data PostCheckoutSessionsRequestBodyAutomaticTax' = PostCheckoutSessionsRequestBodyAutomaticTax'
  { -- | enabled
    PostCheckoutSessionsRequestBodyAutomaticTax' -> Bool
postCheckoutSessionsRequestBodyAutomaticTax'Enabled :: GHC.Types.Bool
  }
  deriving
    ( Int -> PostCheckoutSessionsRequestBodyAutomaticTax' -> ShowS
[PostCheckoutSessionsRequestBodyAutomaticTax'] -> ShowS
PostCheckoutSessionsRequestBodyAutomaticTax' -> String
(Int -> PostCheckoutSessionsRequestBodyAutomaticTax' -> ShowS)
-> (PostCheckoutSessionsRequestBodyAutomaticTax' -> String)
-> ([PostCheckoutSessionsRequestBodyAutomaticTax'] -> ShowS)
-> Show PostCheckoutSessionsRequestBodyAutomaticTax'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyAutomaticTax'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyAutomaticTax'] -> ShowS
show :: PostCheckoutSessionsRequestBodyAutomaticTax' -> String
$cshow :: PostCheckoutSessionsRequestBodyAutomaticTax' -> String
showsPrec :: Int -> PostCheckoutSessionsRequestBodyAutomaticTax' -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsRequestBodyAutomaticTax' -> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyAutomaticTax'
-> PostCheckoutSessionsRequestBodyAutomaticTax' -> Bool
(PostCheckoutSessionsRequestBodyAutomaticTax'
 -> PostCheckoutSessionsRequestBodyAutomaticTax' -> Bool)
-> (PostCheckoutSessionsRequestBodyAutomaticTax'
    -> PostCheckoutSessionsRequestBodyAutomaticTax' -> Bool)
-> Eq PostCheckoutSessionsRequestBodyAutomaticTax'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyAutomaticTax'
-> PostCheckoutSessionsRequestBodyAutomaticTax' -> Bool
$c/= :: PostCheckoutSessionsRequestBodyAutomaticTax'
-> PostCheckoutSessionsRequestBodyAutomaticTax' -> Bool
== :: PostCheckoutSessionsRequestBodyAutomaticTax'
-> PostCheckoutSessionsRequestBodyAutomaticTax' -> Bool
$c== :: PostCheckoutSessionsRequestBodyAutomaticTax'
-> PostCheckoutSessionsRequestBodyAutomaticTax' -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyAutomaticTax' where
  toJSON :: PostCheckoutSessionsRequestBodyAutomaticTax' -> Value
toJSON PostCheckoutSessionsRequestBodyAutomaticTax'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"enabled" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyAutomaticTax' -> Bool
postCheckoutSessionsRequestBodyAutomaticTax'Enabled PostCheckoutSessionsRequestBodyAutomaticTax'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyAutomaticTax' -> Encoding
toEncoding PostCheckoutSessionsRequestBodyAutomaticTax'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs (Text
"enabled" Text -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyAutomaticTax' -> Bool
postCheckoutSessionsRequestBodyAutomaticTax'Enabled PostCheckoutSessionsRequestBodyAutomaticTax'
obj)

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyAutomaticTax' where
  parseJSON :: Value -> Parser PostCheckoutSessionsRequestBodyAutomaticTax'
parseJSON = String
-> (Object -> Parser PostCheckoutSessionsRequestBodyAutomaticTax')
-> Value
-> Parser PostCheckoutSessionsRequestBodyAutomaticTax'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyAutomaticTax'" (\Object
obj -> (Bool -> PostCheckoutSessionsRequestBodyAutomaticTax')
-> Parser (Bool -> PostCheckoutSessionsRequestBodyAutomaticTax')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Bool -> PostCheckoutSessionsRequestBodyAutomaticTax'
PostCheckoutSessionsRequestBodyAutomaticTax' Parser (Bool -> PostCheckoutSessionsRequestBodyAutomaticTax')
-> Parser Bool
-> Parser PostCheckoutSessionsRequestBodyAutomaticTax'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"enabled"))

-- | Create a new 'PostCheckoutSessionsRequestBodyAutomaticTax'' with all required fields.
mkPostCheckoutSessionsRequestBodyAutomaticTax' ::
  -- | 'postCheckoutSessionsRequestBodyAutomaticTax'Enabled'
  GHC.Types.Bool ->
  PostCheckoutSessionsRequestBodyAutomaticTax'
mkPostCheckoutSessionsRequestBodyAutomaticTax' :: Bool -> PostCheckoutSessionsRequestBodyAutomaticTax'
mkPostCheckoutSessionsRequestBodyAutomaticTax' Bool
postCheckoutSessionsRequestBodyAutomaticTax'Enabled = PostCheckoutSessionsRequestBodyAutomaticTax' :: Bool -> PostCheckoutSessionsRequestBodyAutomaticTax'
PostCheckoutSessionsRequestBodyAutomaticTax' {postCheckoutSessionsRequestBodyAutomaticTax'Enabled :: Bool
postCheckoutSessionsRequestBodyAutomaticTax'Enabled = Bool
postCheckoutSessionsRequestBodyAutomaticTax'Enabled}

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.billing_address_collection@ in the specification.
--
-- Specify whether Checkout should collect the customer\'s billing address.
data PostCheckoutSessionsRequestBodyBillingAddressCollection'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyBillingAddressCollection'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyBillingAddressCollection'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"auto"@
    PostCheckoutSessionsRequestBodyBillingAddressCollection'EnumAuto
  | -- | Represents the JSON value @"required"@
    PostCheckoutSessionsRequestBodyBillingAddressCollection'EnumRequired
  deriving (Int
-> PostCheckoutSessionsRequestBodyBillingAddressCollection'
-> ShowS
[PostCheckoutSessionsRequestBodyBillingAddressCollection'] -> ShowS
PostCheckoutSessionsRequestBodyBillingAddressCollection' -> String
(Int
 -> PostCheckoutSessionsRequestBodyBillingAddressCollection'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyBillingAddressCollection'
    -> String)
-> ([PostCheckoutSessionsRequestBodyBillingAddressCollection']
    -> ShowS)
-> Show PostCheckoutSessionsRequestBodyBillingAddressCollection'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyBillingAddressCollection'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyBillingAddressCollection'] -> ShowS
show :: PostCheckoutSessionsRequestBodyBillingAddressCollection' -> String
$cshow :: PostCheckoutSessionsRequestBodyBillingAddressCollection' -> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyBillingAddressCollection'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyBillingAddressCollection'
-> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyBillingAddressCollection'
-> PostCheckoutSessionsRequestBodyBillingAddressCollection' -> Bool
(PostCheckoutSessionsRequestBodyBillingAddressCollection'
 -> PostCheckoutSessionsRequestBodyBillingAddressCollection'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyBillingAddressCollection'
    -> PostCheckoutSessionsRequestBodyBillingAddressCollection'
    -> Bool)
-> Eq PostCheckoutSessionsRequestBodyBillingAddressCollection'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyBillingAddressCollection'
-> PostCheckoutSessionsRequestBodyBillingAddressCollection' -> Bool
$c/= :: PostCheckoutSessionsRequestBodyBillingAddressCollection'
-> PostCheckoutSessionsRequestBodyBillingAddressCollection' -> Bool
== :: PostCheckoutSessionsRequestBodyBillingAddressCollection'
-> PostCheckoutSessionsRequestBodyBillingAddressCollection' -> Bool
$c== :: PostCheckoutSessionsRequestBodyBillingAddressCollection'
-> PostCheckoutSessionsRequestBodyBillingAddressCollection' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyBillingAddressCollection' where
  toJSON :: PostCheckoutSessionsRequestBodyBillingAddressCollection' -> Value
toJSON (PostCheckoutSessionsRequestBodyBillingAddressCollection'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyBillingAddressCollection'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyBillingAddressCollection'
PostCheckoutSessionsRequestBodyBillingAddressCollection'EnumAuto) = Value
"auto"
  toJSON (PostCheckoutSessionsRequestBodyBillingAddressCollection'
PostCheckoutSessionsRequestBodyBillingAddressCollection'EnumRequired) = Value
"required"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyBillingAddressCollection' where
  parseJSON :: Value
-> Parser PostCheckoutSessionsRequestBodyBillingAddressCollection'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyBillingAddressCollection'
-> Parser PostCheckoutSessionsRequestBodyBillingAddressCollection'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"auto" -> PostCheckoutSessionsRequestBodyBillingAddressCollection'
PostCheckoutSessionsRequestBodyBillingAddressCollection'EnumAuto
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"required" -> PostCheckoutSessionsRequestBodyBillingAddressCollection'
PostCheckoutSessionsRequestBodyBillingAddressCollection'EnumRequired
            | Bool
GHC.Base.otherwise -> Value -> PostCheckoutSessionsRequestBodyBillingAddressCollection'
PostCheckoutSessionsRequestBodyBillingAddressCollection'Other Value
val
      )

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.customer_update@ in the specification.
--
-- Controls what fields on Customer can be updated by the Checkout Session. Can only be provided when \`customer\` is provided.
data PostCheckoutSessionsRequestBodyCustomerUpdate' = PostCheckoutSessionsRequestBodyCustomerUpdate'
  { -- | address
    PostCheckoutSessionsRequestBodyCustomerUpdate'
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
postCheckoutSessionsRequestBodyCustomerUpdate'Address :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Address'),
    -- | name
    PostCheckoutSessionsRequestBodyCustomerUpdate'
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
postCheckoutSessionsRequestBodyCustomerUpdate'Name :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name'),
    -- | shipping
    PostCheckoutSessionsRequestBodyCustomerUpdate'
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
postCheckoutSessionsRequestBodyCustomerUpdate'Shipping :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping')
  }
  deriving
    ( Int -> PostCheckoutSessionsRequestBodyCustomerUpdate' -> ShowS
[PostCheckoutSessionsRequestBodyCustomerUpdate'] -> ShowS
PostCheckoutSessionsRequestBodyCustomerUpdate' -> String
(Int -> PostCheckoutSessionsRequestBodyCustomerUpdate' -> ShowS)
-> (PostCheckoutSessionsRequestBodyCustomerUpdate' -> String)
-> ([PostCheckoutSessionsRequestBodyCustomerUpdate'] -> ShowS)
-> Show PostCheckoutSessionsRequestBodyCustomerUpdate'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyCustomerUpdate'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyCustomerUpdate'] -> ShowS
show :: PostCheckoutSessionsRequestBodyCustomerUpdate' -> String
$cshow :: PostCheckoutSessionsRequestBodyCustomerUpdate' -> String
showsPrec :: Int -> PostCheckoutSessionsRequestBodyCustomerUpdate' -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsRequestBodyCustomerUpdate' -> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyCustomerUpdate'
-> PostCheckoutSessionsRequestBodyCustomerUpdate' -> Bool
(PostCheckoutSessionsRequestBodyCustomerUpdate'
 -> PostCheckoutSessionsRequestBodyCustomerUpdate' -> Bool)
-> (PostCheckoutSessionsRequestBodyCustomerUpdate'
    -> PostCheckoutSessionsRequestBodyCustomerUpdate' -> Bool)
-> Eq PostCheckoutSessionsRequestBodyCustomerUpdate'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyCustomerUpdate'
-> PostCheckoutSessionsRequestBodyCustomerUpdate' -> Bool
$c/= :: PostCheckoutSessionsRequestBodyCustomerUpdate'
-> PostCheckoutSessionsRequestBodyCustomerUpdate' -> Bool
== :: PostCheckoutSessionsRequestBodyCustomerUpdate'
-> PostCheckoutSessionsRequestBodyCustomerUpdate' -> Bool
$c== :: PostCheckoutSessionsRequestBodyCustomerUpdate'
-> PostCheckoutSessionsRequestBodyCustomerUpdate' -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyCustomerUpdate' where
  toJSON :: PostCheckoutSessionsRequestBodyCustomerUpdate' -> Value
toJSON PostCheckoutSessionsRequestBodyCustomerUpdate'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"address" Text
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyCustomerUpdate'
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
postCheckoutSessionsRequestBodyCustomerUpdate'Address PostCheckoutSessionsRequestBodyCustomerUpdate'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"name" Text
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyCustomerUpdate'
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
postCheckoutSessionsRequestBodyCustomerUpdate'Name PostCheckoutSessionsRequestBodyCustomerUpdate'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"shipping" Text
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyCustomerUpdate'
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
postCheckoutSessionsRequestBodyCustomerUpdate'Shipping PostCheckoutSessionsRequestBodyCustomerUpdate'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyCustomerUpdate' -> Encoding
toEncoding PostCheckoutSessionsRequestBodyCustomerUpdate'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"address" Text
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyCustomerUpdate'
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
postCheckoutSessionsRequestBodyCustomerUpdate'Address PostCheckoutSessionsRequestBodyCustomerUpdate'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"name" Text
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyCustomerUpdate'
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
postCheckoutSessionsRequestBodyCustomerUpdate'Name PostCheckoutSessionsRequestBodyCustomerUpdate'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"shipping" Text
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyCustomerUpdate'
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
postCheckoutSessionsRequestBodyCustomerUpdate'Shipping PostCheckoutSessionsRequestBodyCustomerUpdate'
obj)))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyCustomerUpdate' where
  parseJSON :: Value -> Parser PostCheckoutSessionsRequestBodyCustomerUpdate'
parseJSON = String
-> (Object
    -> Parser PostCheckoutSessionsRequestBodyCustomerUpdate')
-> Value
-> Parser PostCheckoutSessionsRequestBodyCustomerUpdate'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyCustomerUpdate'" (\Object
obj -> (((Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
 -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
 -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
 -> PostCheckoutSessionsRequestBodyCustomerUpdate')
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
      -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
      -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
      -> PostCheckoutSessionsRequestBodyCustomerUpdate')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'
PostCheckoutSessionsRequestBodyCustomerUpdate' Parser
  (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
   -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
   -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
   -> PostCheckoutSessionsRequestBodyCustomerUpdate')
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Address')
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
      -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
      -> PostCheckoutSessionsRequestBodyCustomerUpdate')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Address')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"address")) Parser
  (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
   -> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
   -> PostCheckoutSessionsRequestBodyCustomerUpdate')
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name')
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
      -> PostCheckoutSessionsRequestBodyCustomerUpdate')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"name")) Parser
  (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
   -> PostCheckoutSessionsRequestBodyCustomerUpdate')
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping')
-> Parser PostCheckoutSessionsRequestBodyCustomerUpdate'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"shipping"))

-- | Create a new 'PostCheckoutSessionsRequestBodyCustomerUpdate'' with all required fields.
mkPostCheckoutSessionsRequestBodyCustomerUpdate' :: PostCheckoutSessionsRequestBodyCustomerUpdate'
mkPostCheckoutSessionsRequestBodyCustomerUpdate' :: PostCheckoutSessionsRequestBodyCustomerUpdate'
mkPostCheckoutSessionsRequestBodyCustomerUpdate' =
  PostCheckoutSessionsRequestBodyCustomerUpdate' :: Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
-> Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'
PostCheckoutSessionsRequestBodyCustomerUpdate'
    { postCheckoutSessionsRequestBodyCustomerUpdate'Address :: Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
postCheckoutSessionsRequestBodyCustomerUpdate'Address = Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyCustomerUpdate'Name :: Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
postCheckoutSessionsRequestBodyCustomerUpdate'Name = Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyCustomerUpdate'Shipping :: Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
postCheckoutSessionsRequestBodyCustomerUpdate'Shipping = Maybe PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.customer_update.properties.address@ in the specification.
data PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyCustomerUpdate'Address'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyCustomerUpdate'Address'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"auto"@
    PostCheckoutSessionsRequestBodyCustomerUpdate'Address'EnumAuto
  | -- | Represents the JSON value @"never"@
    PostCheckoutSessionsRequestBodyCustomerUpdate'Address'EnumNever
  deriving (Int
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Address' -> ShowS
[PostCheckoutSessionsRequestBodyCustomerUpdate'Address'] -> ShowS
PostCheckoutSessionsRequestBodyCustomerUpdate'Address' -> String
(Int
 -> PostCheckoutSessionsRequestBodyCustomerUpdate'Address' -> ShowS)
-> (PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
    -> String)
-> ([PostCheckoutSessionsRequestBodyCustomerUpdate'Address']
    -> ShowS)
-> Show PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyCustomerUpdate'Address'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyCustomerUpdate'Address'] -> ShowS
show :: PostCheckoutSessionsRequestBodyCustomerUpdate'Address' -> String
$cshow :: PostCheckoutSessionsRequestBodyCustomerUpdate'Address' -> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Address' -> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Address' -> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Address' -> Bool
(PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
 -> PostCheckoutSessionsRequestBodyCustomerUpdate'Address' -> Bool)
-> (PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
    -> PostCheckoutSessionsRequestBodyCustomerUpdate'Address' -> Bool)
-> Eq PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Address' -> Bool
$c/= :: PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Address' -> Bool
== :: PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Address' -> Bool
$c== :: PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Address' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyCustomerUpdate'Address' where
  toJSON :: PostCheckoutSessionsRequestBodyCustomerUpdate'Address' -> Value
toJSON (PostCheckoutSessionsRequestBodyCustomerUpdate'Address'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyCustomerUpdate'Address'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
PostCheckoutSessionsRequestBodyCustomerUpdate'Address'EnumAuto) = Value
"auto"
  toJSON (PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
PostCheckoutSessionsRequestBodyCustomerUpdate'Address'EnumNever) = Value
"never"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyCustomerUpdate'Address' where
  parseJSON :: Value
-> Parser PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
-> Parser PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"auto" -> PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
PostCheckoutSessionsRequestBodyCustomerUpdate'Address'EnumAuto
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"never" -> PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
PostCheckoutSessionsRequestBodyCustomerUpdate'Address'EnumNever
            | Bool
GHC.Base.otherwise -> Value -> PostCheckoutSessionsRequestBodyCustomerUpdate'Address'
PostCheckoutSessionsRequestBodyCustomerUpdate'Address'Other Value
val
      )

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.customer_update.properties.name@ in the specification.
data PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyCustomerUpdate'Name'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyCustomerUpdate'Name'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"auto"@
    PostCheckoutSessionsRequestBodyCustomerUpdate'Name'EnumAuto
  | -- | Represents the JSON value @"never"@
    PostCheckoutSessionsRequestBodyCustomerUpdate'Name'EnumNever
  deriving (Int -> PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> ShowS
[PostCheckoutSessionsRequestBodyCustomerUpdate'Name'] -> ShowS
PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> String
(Int
 -> PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> ShowS)
-> (PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> String)
-> ([PostCheckoutSessionsRequestBodyCustomerUpdate'Name'] -> ShowS)
-> Show PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyCustomerUpdate'Name'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyCustomerUpdate'Name'] -> ShowS
show :: PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> String
$cshow :: PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> String
showsPrec :: Int -> PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> Bool
(PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
 -> PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> Bool)
-> (PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
    -> PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> Bool)
-> Eq PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> Bool
$c/= :: PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> Bool
== :: PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> Bool
$c== :: PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyCustomerUpdate'Name' where
  toJSON :: PostCheckoutSessionsRequestBodyCustomerUpdate'Name' -> Value
toJSON (PostCheckoutSessionsRequestBodyCustomerUpdate'Name'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyCustomerUpdate'Name'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
PostCheckoutSessionsRequestBodyCustomerUpdate'Name'EnumAuto) = Value
"auto"
  toJSON (PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
PostCheckoutSessionsRequestBodyCustomerUpdate'Name'EnumNever) = Value
"never"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyCustomerUpdate'Name' where
  parseJSON :: Value -> Parser PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
-> Parser PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"auto" -> PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
PostCheckoutSessionsRequestBodyCustomerUpdate'Name'EnumAuto
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"never" -> PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
PostCheckoutSessionsRequestBodyCustomerUpdate'Name'EnumNever
            | Bool
GHC.Base.otherwise -> Value -> PostCheckoutSessionsRequestBodyCustomerUpdate'Name'
PostCheckoutSessionsRequestBodyCustomerUpdate'Name'Other Value
val
      )

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.customer_update.properties.shipping@ in the specification.
data PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"auto"@
    PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'EnumAuto
  | -- | Represents the JSON value @"never"@
    PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'EnumNever
  deriving (Int
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' -> ShowS
[PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'] -> ShowS
PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' -> String
(Int
 -> PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
    -> String)
-> ([PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping']
    -> ShowS)
-> Show PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'] -> ShowS
show :: PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' -> String
$cshow :: PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' -> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' -> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' -> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' -> Bool
(PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
 -> PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' -> Bool)
-> (PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
    -> PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' -> Bool)
-> Eq PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' -> Bool
$c/= :: PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' -> Bool
== :: PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' -> Bool
$c== :: PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
-> PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' where
  toJSON :: PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' -> Value
toJSON (PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'EnumAuto) = Value
"auto"
  toJSON (PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'EnumNever) = Value
"never"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping' where
  parseJSON :: Value
-> Parser PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
-> Parser PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"auto" -> PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'EnumAuto
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"never" -> PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'EnumNever
            | Bool
GHC.Base.otherwise -> Value -> PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'
PostCheckoutSessionsRequestBodyCustomerUpdate'Shipping'Other Value
val
      )

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.discounts.items@ in the specification.
data PostCheckoutSessionsRequestBodyDiscounts' = PostCheckoutSessionsRequestBodyDiscounts'
  { -- | coupon
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyDiscounts' -> Maybe Text
postCheckoutSessionsRequestBodyDiscounts'Coupon :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | promotion_code
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyDiscounts' -> Maybe Text
postCheckoutSessionsRequestBodyDiscounts'PromotionCode :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int -> PostCheckoutSessionsRequestBodyDiscounts' -> ShowS
[PostCheckoutSessionsRequestBodyDiscounts'] -> ShowS
PostCheckoutSessionsRequestBodyDiscounts' -> String
(Int -> PostCheckoutSessionsRequestBodyDiscounts' -> ShowS)
-> (PostCheckoutSessionsRequestBodyDiscounts' -> String)
-> ([PostCheckoutSessionsRequestBodyDiscounts'] -> ShowS)
-> Show PostCheckoutSessionsRequestBodyDiscounts'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyDiscounts'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyDiscounts'] -> ShowS
show :: PostCheckoutSessionsRequestBodyDiscounts' -> String
$cshow :: PostCheckoutSessionsRequestBodyDiscounts' -> String
showsPrec :: Int -> PostCheckoutSessionsRequestBodyDiscounts' -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsRequestBodyDiscounts' -> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyDiscounts'
-> PostCheckoutSessionsRequestBodyDiscounts' -> Bool
(PostCheckoutSessionsRequestBodyDiscounts'
 -> PostCheckoutSessionsRequestBodyDiscounts' -> Bool)
-> (PostCheckoutSessionsRequestBodyDiscounts'
    -> PostCheckoutSessionsRequestBodyDiscounts' -> Bool)
-> Eq PostCheckoutSessionsRequestBodyDiscounts'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyDiscounts'
-> PostCheckoutSessionsRequestBodyDiscounts' -> Bool
$c/= :: PostCheckoutSessionsRequestBodyDiscounts'
-> PostCheckoutSessionsRequestBodyDiscounts' -> Bool
== :: PostCheckoutSessionsRequestBodyDiscounts'
-> PostCheckoutSessionsRequestBodyDiscounts' -> Bool
$c== :: PostCheckoutSessionsRequestBodyDiscounts'
-> PostCheckoutSessionsRequestBodyDiscounts' -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyDiscounts' where
  toJSON :: PostCheckoutSessionsRequestBodyDiscounts' -> Value
toJSON PostCheckoutSessionsRequestBodyDiscounts'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"coupon" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyDiscounts' -> Maybe Text
postCheckoutSessionsRequestBodyDiscounts'Coupon PostCheckoutSessionsRequestBodyDiscounts'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"promotion_code" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyDiscounts' -> Maybe Text
postCheckoutSessionsRequestBodyDiscounts'PromotionCode PostCheckoutSessionsRequestBodyDiscounts'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyDiscounts' -> Encoding
toEncoding PostCheckoutSessionsRequestBodyDiscounts'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"coupon" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyDiscounts' -> Maybe Text
postCheckoutSessionsRequestBodyDiscounts'Coupon PostCheckoutSessionsRequestBodyDiscounts'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"promotion_code" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyDiscounts' -> Maybe Text
postCheckoutSessionsRequestBodyDiscounts'PromotionCode PostCheckoutSessionsRequestBodyDiscounts'
obj))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyDiscounts' where
  parseJSON :: Value -> Parser PostCheckoutSessionsRequestBodyDiscounts'
parseJSON = String
-> (Object -> Parser PostCheckoutSessionsRequestBodyDiscounts')
-> Value
-> Parser PostCheckoutSessionsRequestBodyDiscounts'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyDiscounts'" (\Object
obj -> ((Maybe Text
 -> Maybe Text -> PostCheckoutSessionsRequestBodyDiscounts')
-> Parser
     (Maybe Text
      -> Maybe Text -> PostCheckoutSessionsRequestBodyDiscounts')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe Text -> PostCheckoutSessionsRequestBodyDiscounts'
PostCheckoutSessionsRequestBodyDiscounts' Parser
  (Maybe Text
   -> Maybe Text -> PostCheckoutSessionsRequestBodyDiscounts')
-> Parser (Maybe Text)
-> Parser (Maybe Text -> PostCheckoutSessionsRequestBodyDiscounts')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"coupon")) Parser (Maybe Text -> PostCheckoutSessionsRequestBodyDiscounts')
-> Parser (Maybe Text)
-> Parser PostCheckoutSessionsRequestBodyDiscounts'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"promotion_code"))

-- | Create a new 'PostCheckoutSessionsRequestBodyDiscounts'' with all required fields.
mkPostCheckoutSessionsRequestBodyDiscounts' :: PostCheckoutSessionsRequestBodyDiscounts'
mkPostCheckoutSessionsRequestBodyDiscounts' :: PostCheckoutSessionsRequestBodyDiscounts'
mkPostCheckoutSessionsRequestBodyDiscounts' =
  PostCheckoutSessionsRequestBodyDiscounts' :: Maybe Text
-> Maybe Text -> PostCheckoutSessionsRequestBodyDiscounts'
PostCheckoutSessionsRequestBodyDiscounts'
    { postCheckoutSessionsRequestBodyDiscounts'Coupon :: Maybe Text
postCheckoutSessionsRequestBodyDiscounts'Coupon = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyDiscounts'PromotionCode :: Maybe Text
postCheckoutSessionsRequestBodyDiscounts'PromotionCode = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.line_items.items@ in the specification.
data PostCheckoutSessionsRequestBodyLineItems' = PostCheckoutSessionsRequestBodyLineItems'
  { -- | adjustable_quantity
    PostCheckoutSessionsRequestBodyLineItems'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'),
    -- | amount
    PostCheckoutSessionsRequestBodyLineItems' -> Maybe Int
postCheckoutSessionsRequestBodyLineItems'Amount :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | currency
    PostCheckoutSessionsRequestBodyLineItems' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'Currency :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | description
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyLineItems' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'Description :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | dynamic_tax_rates
    PostCheckoutSessionsRequestBodyLineItems' -> Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'DynamicTaxRates :: (GHC.Maybe.Maybe ([Data.Text.Internal.Text])),
    -- | images
    PostCheckoutSessionsRequestBodyLineItems' -> Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'Images :: (GHC.Maybe.Maybe ([Data.Text.Internal.Text])),
    -- | name
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyLineItems' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'Name :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | price
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyLineItems' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'Price :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | price_data
    PostCheckoutSessionsRequestBodyLineItems'
-> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
postCheckoutSessionsRequestBodyLineItems'PriceData :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'),
    -- | quantity
    PostCheckoutSessionsRequestBodyLineItems' -> Maybe Int
postCheckoutSessionsRequestBodyLineItems'Quantity :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | tax_rates
    PostCheckoutSessionsRequestBodyLineItems' -> Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'TaxRates :: (GHC.Maybe.Maybe ([Data.Text.Internal.Text]))
  }
  deriving
    ( Int -> PostCheckoutSessionsRequestBodyLineItems' -> ShowS
[PostCheckoutSessionsRequestBodyLineItems'] -> ShowS
PostCheckoutSessionsRequestBodyLineItems' -> String
(Int -> PostCheckoutSessionsRequestBodyLineItems' -> ShowS)
-> (PostCheckoutSessionsRequestBodyLineItems' -> String)
-> ([PostCheckoutSessionsRequestBodyLineItems'] -> ShowS)
-> Show PostCheckoutSessionsRequestBodyLineItems'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyLineItems'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyLineItems'] -> ShowS
show :: PostCheckoutSessionsRequestBodyLineItems' -> String
$cshow :: PostCheckoutSessionsRequestBodyLineItems' -> String
showsPrec :: Int -> PostCheckoutSessionsRequestBodyLineItems' -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsRequestBodyLineItems' -> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyLineItems'
-> PostCheckoutSessionsRequestBodyLineItems' -> Bool
(PostCheckoutSessionsRequestBodyLineItems'
 -> PostCheckoutSessionsRequestBodyLineItems' -> Bool)
-> (PostCheckoutSessionsRequestBodyLineItems'
    -> PostCheckoutSessionsRequestBodyLineItems' -> Bool)
-> Eq PostCheckoutSessionsRequestBodyLineItems'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyLineItems'
-> PostCheckoutSessionsRequestBodyLineItems' -> Bool
$c/= :: PostCheckoutSessionsRequestBodyLineItems'
-> PostCheckoutSessionsRequestBodyLineItems' -> Bool
== :: PostCheckoutSessionsRequestBodyLineItems'
-> PostCheckoutSessionsRequestBodyLineItems' -> Bool
$c== :: PostCheckoutSessionsRequestBodyLineItems'
-> PostCheckoutSessionsRequestBodyLineItems' -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyLineItems' where
  toJSON :: PostCheckoutSessionsRequestBodyLineItems' -> Value
toJSON PostCheckoutSessionsRequestBodyLineItems'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"adjustable_quantity" Text
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity PostCheckoutSessionsRequestBodyLineItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"amount" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe Int
postCheckoutSessionsRequestBodyLineItems'Amount PostCheckoutSessionsRequestBodyLineItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"currency" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'Currency PostCheckoutSessionsRequestBodyLineItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"description" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'Description PostCheckoutSessionsRequestBodyLineItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"dynamic_tax_rates" Text -> Maybe [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'DynamicTaxRates PostCheckoutSessionsRequestBodyLineItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"images" Text -> Maybe [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'Images PostCheckoutSessionsRequestBodyLineItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"name" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'Name PostCheckoutSessionsRequestBodyLineItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"price" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'Price PostCheckoutSessionsRequestBodyLineItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"price_data" Text
-> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'
-> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
postCheckoutSessionsRequestBodyLineItems'PriceData PostCheckoutSessionsRequestBodyLineItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"quantity" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe Int
postCheckoutSessionsRequestBodyLineItems'Quantity PostCheckoutSessionsRequestBodyLineItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"tax_rates" Text -> Maybe [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'TaxRates PostCheckoutSessionsRequestBodyLineItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyLineItems' -> Encoding
toEncoding PostCheckoutSessionsRequestBodyLineItems'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"adjustable_quantity" Text
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity PostCheckoutSessionsRequestBodyLineItems'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"amount" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe Int
postCheckoutSessionsRequestBodyLineItems'Amount PostCheckoutSessionsRequestBodyLineItems'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"currency" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'Currency PostCheckoutSessionsRequestBodyLineItems'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"description" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'Description PostCheckoutSessionsRequestBodyLineItems'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"dynamic_tax_rates" Text -> Maybe [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'DynamicTaxRates PostCheckoutSessionsRequestBodyLineItems'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"images" Text -> Maybe [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'Images PostCheckoutSessionsRequestBodyLineItems'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"name" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'Name PostCheckoutSessionsRequestBodyLineItems'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"price" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'Price PostCheckoutSessionsRequestBodyLineItems'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"price_data" Text
-> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'
-> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
postCheckoutSessionsRequestBodyLineItems'PriceData PostCheckoutSessionsRequestBodyLineItems'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"quantity" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe Int
postCheckoutSessionsRequestBodyLineItems'Quantity PostCheckoutSessionsRequestBodyLineItems'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"tax_rates" Text -> Maybe [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems' -> Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'TaxRates PostCheckoutSessionsRequestBodyLineItems'
obj)))))))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyLineItems' where
  parseJSON :: Value -> Parser PostCheckoutSessionsRequestBodyLineItems'
parseJSON = String
-> (Object -> Parser PostCheckoutSessionsRequestBodyLineItems')
-> Value
-> Parser PostCheckoutSessionsRequestBodyLineItems'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyLineItems'" (\Object
obj -> (((((((((((Maybe PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
 -> Maybe Int
 -> Maybe Text
 -> Maybe Text
 -> Maybe [Text]
 -> Maybe [Text]
 -> Maybe Text
 -> Maybe Text
 -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
 -> Maybe Int
 -> Maybe [Text]
 -> PostCheckoutSessionsRequestBodyLineItems')
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe [Text]
      -> Maybe [Text]
      -> Maybe Text
      -> Maybe Text
      -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
      -> Maybe Int
      -> Maybe [Text]
      -> PostCheckoutSessionsRequestBodyLineItems')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Text
-> Maybe Text
-> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> Maybe Int
-> Maybe [Text]
-> PostCheckoutSessionsRequestBodyLineItems'
PostCheckoutSessionsRequestBodyLineItems' Parser
  (Maybe PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe [Text]
   -> Maybe [Text]
   -> Maybe Text
   -> Maybe Text
   -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
   -> Maybe Int
   -> Maybe [Text]
   -> PostCheckoutSessionsRequestBodyLineItems')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity')
-> Parser
     (Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe [Text]
      -> Maybe [Text]
      -> Maybe Text
      -> Maybe Text
      -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
      -> Maybe Int
      -> Maybe [Text]
      -> PostCheckoutSessionsRequestBodyLineItems')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"adjustable_quantity")) Parser
  (Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe [Text]
   -> Maybe [Text]
   -> Maybe Text
   -> Maybe Text
   -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
   -> Maybe Int
   -> Maybe [Text]
   -> PostCheckoutSessionsRequestBodyLineItems')
-> Parser (Maybe Int)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe [Text]
      -> Maybe [Text]
      -> Maybe Text
      -> Maybe Text
      -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
      -> Maybe Int
      -> Maybe [Text]
      -> PostCheckoutSessionsRequestBodyLineItems')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"amount")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe [Text]
   -> Maybe [Text]
   -> Maybe Text
   -> Maybe Text
   -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
   -> Maybe Int
   -> Maybe [Text]
   -> PostCheckoutSessionsRequestBodyLineItems')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe [Text]
      -> Maybe [Text]
      -> Maybe Text
      -> Maybe Text
      -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
      -> Maybe Int
      -> Maybe [Text]
      -> PostCheckoutSessionsRequestBodyLineItems')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"currency")) Parser
  (Maybe Text
   -> Maybe [Text]
   -> Maybe [Text]
   -> Maybe Text
   -> Maybe Text
   -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
   -> Maybe Int
   -> Maybe [Text]
   -> PostCheckoutSessionsRequestBodyLineItems')
-> Parser (Maybe Text)
-> Parser
     (Maybe [Text]
      -> Maybe [Text]
      -> Maybe Text
      -> Maybe Text
      -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
      -> Maybe Int
      -> Maybe [Text]
      -> PostCheckoutSessionsRequestBodyLineItems')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"description")) Parser
  (Maybe [Text]
   -> Maybe [Text]
   -> Maybe Text
   -> Maybe Text
   -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
   -> Maybe Int
   -> Maybe [Text]
   -> PostCheckoutSessionsRequestBodyLineItems')
-> Parser (Maybe [Text])
-> Parser
     (Maybe [Text]
      -> Maybe Text
      -> Maybe Text
      -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
      -> Maybe Int
      -> Maybe [Text]
      -> PostCheckoutSessionsRequestBodyLineItems')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"dynamic_tax_rates")) Parser
  (Maybe [Text]
   -> Maybe Text
   -> Maybe Text
   -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
   -> Maybe Int
   -> Maybe [Text]
   -> PostCheckoutSessionsRequestBodyLineItems')
-> Parser (Maybe [Text])
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
      -> Maybe Int
      -> Maybe [Text]
      -> PostCheckoutSessionsRequestBodyLineItems')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"images")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
   -> Maybe Int
   -> Maybe [Text]
   -> PostCheckoutSessionsRequestBodyLineItems')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
      -> Maybe Int
      -> Maybe [Text]
      -> PostCheckoutSessionsRequestBodyLineItems')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"name")) Parser
  (Maybe Text
   -> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
   -> Maybe Int
   -> Maybe [Text]
   -> PostCheckoutSessionsRequestBodyLineItems')
-> Parser (Maybe Text)
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
      -> Maybe Int
      -> Maybe [Text]
      -> PostCheckoutSessionsRequestBodyLineItems')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"price")) Parser
  (Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
   -> Maybe Int
   -> Maybe [Text]
   -> PostCheckoutSessionsRequestBodyLineItems')
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData')
-> Parser
     (Maybe Int
      -> Maybe [Text] -> PostCheckoutSessionsRequestBodyLineItems')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"price_data")) Parser
  (Maybe Int
   -> Maybe [Text] -> PostCheckoutSessionsRequestBodyLineItems')
-> Parser (Maybe Int)
-> Parser
     (Maybe [Text] -> PostCheckoutSessionsRequestBodyLineItems')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"quantity")) Parser (Maybe [Text] -> PostCheckoutSessionsRequestBodyLineItems')
-> Parser (Maybe [Text])
-> Parser PostCheckoutSessionsRequestBodyLineItems'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"tax_rates"))

-- | Create a new 'PostCheckoutSessionsRequestBodyLineItems'' with all required fields.
mkPostCheckoutSessionsRequestBodyLineItems' :: PostCheckoutSessionsRequestBodyLineItems'
mkPostCheckoutSessionsRequestBodyLineItems' :: PostCheckoutSessionsRequestBodyLineItems'
mkPostCheckoutSessionsRequestBodyLineItems' =
  PostCheckoutSessionsRequestBodyLineItems' :: Maybe PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Text
-> Maybe Text
-> Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> Maybe Int
-> Maybe [Text]
-> PostCheckoutSessionsRequestBodyLineItems'
PostCheckoutSessionsRequestBodyLineItems'
    { postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity :: Maybe PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity = Maybe PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'Amount :: Maybe Int
postCheckoutSessionsRequestBodyLineItems'Amount = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'Currency :: Maybe Text
postCheckoutSessionsRequestBodyLineItems'Currency = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'Description :: Maybe Text
postCheckoutSessionsRequestBodyLineItems'Description = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'DynamicTaxRates :: Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'DynamicTaxRates = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'Images :: Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'Images = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'Name :: Maybe Text
postCheckoutSessionsRequestBodyLineItems'Name = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'Price :: Maybe Text
postCheckoutSessionsRequestBodyLineItems'Price = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'PriceData :: Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
postCheckoutSessionsRequestBodyLineItems'PriceData = Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'Quantity :: Maybe Int
postCheckoutSessionsRequestBodyLineItems'Quantity = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'TaxRates :: Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'TaxRates = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.line_items.items.properties.adjustable_quantity@ in the specification.
data PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity' = PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
  { -- | enabled
    PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Bool
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Enabled :: GHC.Types.Bool,
    -- | maximum
    PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Maybe Int
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Maximum :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | minimum
    PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Maybe Int
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Minimum :: (GHC.Maybe.Maybe GHC.Types.Int)
  }
  deriving
    ( Int
-> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> ShowS
[PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity']
-> ShowS
PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
    -> String)
-> ([PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity']
-> ShowS
show :: PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> String
$cshow :: PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Bool
(PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
 -> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
    -> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
    -> Bool)
-> Eq PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Bool
== :: PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity' where
  toJSON :: PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Value
toJSON PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"enabled" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Bool
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Enabled PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"maximum" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Maybe Int
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Maximum PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"minimum" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Maybe Int
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Minimum PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Encoding
toEncoding PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"enabled" Text -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Bool
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Enabled PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"maximum" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Maybe Int
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Maximum PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"minimum" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
-> Maybe Int
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Minimum PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
obj)))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
parseJSON = String
-> (Object
    -> Parser
         PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity')
-> Value
-> Parser
     PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'" (\Object
obj -> (((Bool
 -> Maybe Int
 -> Maybe Int
 -> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity')
-> Parser
     (Bool
      -> Maybe Int
      -> Maybe Int
      -> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Bool
-> Maybe Int
-> Maybe Int
-> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity' Parser
  (Bool
   -> Maybe Int
   -> Maybe Int
   -> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity')
-> Parser Bool
-> Parser
     (Maybe Int
      -> Maybe Int
      -> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"enabled")) Parser
  (Maybe Int
   -> Maybe Int
   -> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity')
-> Parser (Maybe Int)
-> Parser
     (Maybe Int
      -> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"maximum")) Parser
  (Maybe Int
   -> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity')
-> Parser (Maybe Int)
-> Parser
     PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"minimum"))

-- | Create a new 'PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'' with all required fields.
mkPostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity' ::
  -- | 'postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Enabled'
  GHC.Types.Bool ->
  PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
mkPostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity' :: Bool
-> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
mkPostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity' Bool
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Enabled =
  PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity' :: Bool
-> Maybe Int
-> Maybe Int
-> PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
PostCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'
    { postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Enabled :: Bool
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Enabled = Bool
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Enabled,
      postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Maximum :: Maybe Int
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Maximum = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Minimum :: Maybe Int
postCheckoutSessionsRequestBodyLineItems'AdjustableQuantity'Minimum = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.line_items.items.properties.price_data@ in the specification.
data PostCheckoutSessionsRequestBodyLineItems'PriceData' = PostCheckoutSessionsRequestBodyLineItems'PriceData'
  { -- | currency
    PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Text
postCheckoutSessionsRequestBodyLineItems'PriceData'Currency :: Data.Text.Internal.Text,
    -- | product
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'Product :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | product_data
    PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'),
    -- | recurring
    PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'),
    -- | tax_behavior
    PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
postCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'),
    -- | unit_amount
    PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Maybe Int
postCheckoutSessionsRequestBodyLineItems'PriceData'UnitAmount :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | unit_amount_decimal
    PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'UnitAmountDecimal :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int -> PostCheckoutSessionsRequestBodyLineItems'PriceData' -> ShowS
[PostCheckoutSessionsRequestBodyLineItems'PriceData'] -> ShowS
PostCheckoutSessionsRequestBodyLineItems'PriceData' -> String
(Int
 -> PostCheckoutSessionsRequestBodyLineItems'PriceData' -> ShowS)
-> (PostCheckoutSessionsRequestBodyLineItems'PriceData' -> String)
-> ([PostCheckoutSessionsRequestBodyLineItems'PriceData'] -> ShowS)
-> Show PostCheckoutSessionsRequestBodyLineItems'PriceData'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyLineItems'PriceData'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyLineItems'PriceData'] -> ShowS
show :: PostCheckoutSessionsRequestBodyLineItems'PriceData' -> String
$cshow :: PostCheckoutSessionsRequestBodyLineItems'PriceData' -> String
showsPrec :: Int -> PostCheckoutSessionsRequestBodyLineItems'PriceData' -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsRequestBodyLineItems'PriceData' -> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Bool
(PostCheckoutSessionsRequestBodyLineItems'PriceData'
 -> PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Bool)
-> (PostCheckoutSessionsRequestBodyLineItems'PriceData'
    -> PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Bool)
-> Eq PostCheckoutSessionsRequestBodyLineItems'PriceData'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Bool
$c/= :: PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Bool
== :: PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Bool
$c== :: PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyLineItems'PriceData' where
  toJSON :: PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Value
toJSON PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"currency" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Text
postCheckoutSessionsRequestBodyLineItems'PriceData'Currency PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"product" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'Product PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"product_data" Text
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"recurring" Text
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"tax_behavior" Text
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
postCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"unit_amount" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Maybe Int
postCheckoutSessionsRequestBodyLineItems'PriceData'UnitAmount PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"unit_amount_decimal" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'UnitAmountDecimal PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Encoding
toEncoding PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"currency" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Text
postCheckoutSessionsRequestBodyLineItems'PriceData'Currency PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"product" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'Product PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"product_data" Text
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"recurring" Text
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"tax_behavior" Text
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
postCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"unit_amount" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Maybe Int
postCheckoutSessionsRequestBodyLineItems'PriceData'UnitAmount PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"unit_amount_decimal" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData' -> Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'UnitAmountDecimal PostCheckoutSessionsRequestBodyLineItems'PriceData'
obj)))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyLineItems'PriceData' where
  parseJSON :: Value -> Parser PostCheckoutSessionsRequestBodyLineItems'PriceData'
parseJSON = String
-> (Object
    -> Parser PostCheckoutSessionsRequestBodyLineItems'PriceData')
-> Value
-> Parser PostCheckoutSessionsRequestBodyLineItems'PriceData'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyLineItems'PriceData'" (\Object
obj -> (((((((Text
 -> Maybe Text
 -> Maybe
      PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
 -> Maybe
      PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
 -> Maybe
      PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
 -> Maybe Int
 -> Maybe Text
 -> PostCheckoutSessionsRequestBodyLineItems'PriceData')
-> Parser
     (Text
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
      -> Maybe
           PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
      -> Maybe
           PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
      -> Maybe Int
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyLineItems'PriceData')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Text
-> Maybe Text
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> Maybe Int
-> Maybe Text
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'
PostCheckoutSessionsRequestBodyLineItems'PriceData' Parser
  (Text
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
   -> Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
   -> Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
   -> Maybe Int
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyLineItems'PriceData')
-> Parser Text
-> Parser
     (Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
      -> Maybe
           PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
      -> Maybe
           PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
      -> Maybe Int
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyLineItems'PriceData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"currency")) Parser
  (Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
   -> Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
   -> Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
   -> Maybe Int
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyLineItems'PriceData')
-> Parser (Maybe Text)
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
      -> Maybe
           PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
      -> Maybe
           PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
      -> Maybe Int
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyLineItems'PriceData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"product")) Parser
  (Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
   -> Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
   -> Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
   -> Maybe Int
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyLineItems'PriceData')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
      -> Maybe
           PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
      -> Maybe Int
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyLineItems'PriceData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"product_data")) Parser
  (Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
   -> Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
   -> Maybe Int
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyLineItems'PriceData')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
      -> Maybe Int
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyLineItems'PriceData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"recurring")) Parser
  (Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
   -> Maybe Int
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyLineItems'PriceData')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior')
-> Parser
     (Maybe Int
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyLineItems'PriceData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"tax_behavior")) Parser
  (Maybe Int
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyLineItems'PriceData')
-> Parser (Maybe Int)
-> Parser
     (Maybe Text -> PostCheckoutSessionsRequestBodyLineItems'PriceData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"unit_amount")) Parser
  (Maybe Text -> PostCheckoutSessionsRequestBodyLineItems'PriceData')
-> Parser (Maybe Text)
-> Parser PostCheckoutSessionsRequestBodyLineItems'PriceData'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"unit_amount_decimal"))

-- | Create a new 'PostCheckoutSessionsRequestBodyLineItems'PriceData'' with all required fields.
mkPostCheckoutSessionsRequestBodyLineItems'PriceData' ::
  -- | 'postCheckoutSessionsRequestBodyLineItems'PriceData'Currency'
  Data.Text.Internal.Text ->
  PostCheckoutSessionsRequestBodyLineItems'PriceData'
mkPostCheckoutSessionsRequestBodyLineItems'PriceData' :: Text -> PostCheckoutSessionsRequestBodyLineItems'PriceData'
mkPostCheckoutSessionsRequestBodyLineItems'PriceData' Text
postCheckoutSessionsRequestBodyLineItems'PriceData'Currency =
  PostCheckoutSessionsRequestBodyLineItems'PriceData' :: Text
-> Maybe Text
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> Maybe
     PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> Maybe Int
-> Maybe Text
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'
PostCheckoutSessionsRequestBodyLineItems'PriceData'
    { postCheckoutSessionsRequestBodyLineItems'PriceData'Currency :: Text
postCheckoutSessionsRequestBodyLineItems'PriceData'Currency = Text
postCheckoutSessionsRequestBodyLineItems'PriceData'Currency,
      postCheckoutSessionsRequestBodyLineItems'PriceData'Product :: Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'Product = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData :: Maybe
  PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData = Maybe
  PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring :: Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring = Maybe PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior :: Maybe
  PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
postCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior = Maybe
  PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'PriceData'UnitAmount :: Maybe Int
postCheckoutSessionsRequestBodyLineItems'PriceData'UnitAmount = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'PriceData'UnitAmountDecimal :: Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'UnitAmountDecimal = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.line_items.items.properties.price_data.properties.product_data@ in the specification.
data PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData' = PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
  { -- | description
    --
    -- Constraints:
    --
    -- * Maximum length of 40000
    PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Description :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | images
    PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Images :: (GHC.Maybe.Maybe ([Data.Text.Internal.Text])),
    -- | metadata
    PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Maybe Object
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Metadata :: (GHC.Maybe.Maybe Data.Aeson.Types.Internal.Object),
    -- | name
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Text
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Name :: Data.Text.Internal.Text,
    -- | tax_code
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'TaxCode :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> ShowS
[PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData']
-> ShowS
PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
    -> String)
-> ([PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData']
-> ShowS
show :: PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> String
$cshow :: PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Bool
(PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
 -> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
    -> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
    -> Bool)
-> Eq
     PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Bool
== :: PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData' where
  toJSON :: PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Value
toJSON PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"description" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Description PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"images" Text -> Maybe [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Images PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text -> Maybe Object -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Maybe Object
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Metadata PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"name" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Text
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Name PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"tax_code" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'TaxCode PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Encoding
toEncoding PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"description" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Description PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"images" Text -> Maybe [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Images PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"metadata" Text -> Maybe Object -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Maybe Object
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Metadata PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"name" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Text
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Name PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"tax_code" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
-> Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'TaxCode PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
obj)))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
parseJSON = String
-> (Object
    -> Parser
         PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData')
-> Value
-> Parser
     PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'" (\Object
obj -> (((((Maybe Text
 -> Maybe [Text]
 -> Maybe Object
 -> Text
 -> Maybe Text
 -> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData')
-> Parser
     (Maybe Text
      -> Maybe [Text]
      -> Maybe Object
      -> Text
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe [Text]
-> Maybe Object
-> Text
-> Maybe Text
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData' Parser
  (Maybe Text
   -> Maybe [Text]
   -> Maybe Object
   -> Text
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData')
-> Parser (Maybe Text)
-> Parser
     (Maybe [Text]
      -> Maybe Object
      -> Text
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"description")) Parser
  (Maybe [Text]
   -> Maybe Object
   -> Text
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData')
-> Parser (Maybe [Text])
-> Parser
     (Maybe Object
      -> Text
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"images")) Parser
  (Maybe Object
   -> Text
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData')
-> Parser (Maybe Object)
-> Parser
     (Text
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"metadata")) Parser
  (Text
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData')
-> Parser Text
-> Parser
     (Maybe Text
      -> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"name")) Parser
  (Maybe Text
   -> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData')
-> Parser (Maybe Text)
-> Parser
     PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"tax_code"))

-- | Create a new 'PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'' with all required fields.
mkPostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData' ::
  -- | 'postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Name'
  Data.Text.Internal.Text ->
  PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
mkPostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData' :: Text
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
mkPostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData' Text
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Name =
  PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData' :: Maybe Text
-> Maybe [Text]
-> Maybe Object
-> Text
-> Maybe Text
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
PostCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'
    { postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Description :: Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Description = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Images :: Maybe [Text]
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Images = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Metadata :: Maybe Object
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Metadata = Maybe Object
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Name :: Text
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Name = Text
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'Name,
      postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'TaxCode :: Maybe Text
postCheckoutSessionsRequestBodyLineItems'PriceData'ProductData'TaxCode = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.line_items.items.properties.price_data.properties.recurring@ in the specification.
data PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring' = PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
  { -- | interval
    PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval',
    -- | interval_count
    PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> Maybe Int
postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'IntervalCount :: (GHC.Maybe.Maybe GHC.Types.Int)
  }
  deriving
    ( Int
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> ShowS
[PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring']
-> ShowS
PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
    -> String)
-> ([PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring']
-> ShowS
show :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> String
$cshow :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> Bool
(PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
 -> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
    -> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
    -> Bool)
-> Eq PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> Bool
== :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring' where
  toJSON :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> Value
toJSON PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"interval" Text
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"interval_count" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> Maybe Int
postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'IntervalCount PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> Encoding
toEncoding PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"interval" Text
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"interval_count" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
-> Maybe Int
postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'IntervalCount PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
obj))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
parseJSON = String
-> (Object
    -> Parser
         PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring')
-> Value
-> Parser
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'" (\Object
obj -> ((PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
 -> Maybe Int
 -> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring')
-> Parser
     (PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
      -> Maybe Int
      -> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> Maybe Int
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring' Parser
  (PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
   -> Maybe Int
   -> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring')
-> Parser
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> Parser
     (Maybe Int
      -> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"interval")) Parser
  (Maybe Int
   -> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring')
-> Parser (Maybe Int)
-> Parser
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"interval_count"))

-- | Create a new 'PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'' with all required fields.
mkPostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring' ::
  -- | 'postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
  PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval' ->
  PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
mkPostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring' :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
mkPostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring' PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval =
  PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring' :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> Maybe Int
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'
    { postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval = PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval,
      postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'IntervalCount :: Maybe Int
postCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'IntervalCount = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.line_items.items.properties.price_data.properties.recurring.properties.interval@ in the specification.
data PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"day"@
    PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'EnumDay
  | -- | Represents the JSON value @"month"@
    PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'EnumMonth
  | -- | Represents the JSON value @"week"@
    PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'EnumWeek
  | -- | Represents the JSON value @"year"@
    PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'EnumYear
  deriving (Int
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> ShowS
[PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval']
-> ShowS
PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
    -> String)
-> ([PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval']
-> ShowS
show :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> String
$cshow :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> Bool
(PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
 -> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
    -> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
    -> Bool)
-> Eq
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> Bool
== :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval' where
  toJSON :: PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> Value
toJSON (PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'EnumDay) = Value
"day"
  toJSON (PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'EnumMonth) = Value
"month"
  toJSON (PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'EnumWeek) = Value
"week"
  toJSON (PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'EnumYear) = Value
"year"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
-> Parser
     PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"day" -> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'EnumDay
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"month" -> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'EnumMonth
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"week" -> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'EnumWeek
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"year" -> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'EnumYear
            | Bool
GHC.Base.otherwise -> Value
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'
PostCheckoutSessionsRequestBodyLineItems'PriceData'Recurring'Interval'Other Value
val
      )

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.line_items.items.properties.price_data.properties.tax_behavior@ in the specification.
data PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"exclusive"@
    PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'EnumExclusive
  | -- | Represents the JSON value @"inclusive"@
    PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'EnumInclusive
  | -- | Represents the JSON value @"unspecified"@
    PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'EnumUnspecified
  deriving (Int
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> ShowS
[PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior']
-> ShowS
PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
    -> String)
-> ([PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior']
-> ShowS
show :: PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> String
$cshow :: PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> Bool
(PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
 -> PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
    -> PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
    -> Bool)
-> Eq
     PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> Bool
== :: PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior' where
  toJSON :: PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> Value
toJSON (PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'EnumExclusive) = Value
"exclusive"
  toJSON (PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'EnumInclusive) = Value
"inclusive"
  toJSON (PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'EnumUnspecified) = Value
"unspecified"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
-> Parser
     PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"exclusive" -> PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'EnumExclusive
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"inclusive" -> PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'EnumInclusive
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"unspecified" -> PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'EnumUnspecified
            | Bool
GHC.Base.otherwise -> Value
-> PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'
PostCheckoutSessionsRequestBodyLineItems'PriceData'TaxBehavior'Other Value
val
      )

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.locale@ in the specification.
--
-- The IETF language tag of the locale Checkout is displayed in. If blank or \`auto\`, the browser\'s locale is used.
data PostCheckoutSessionsRequestBodyLocale'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyLocale'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyLocale'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"auto"@
    PostCheckoutSessionsRequestBodyLocale'EnumAuto
  | -- | Represents the JSON value @"bg"@
    PostCheckoutSessionsRequestBodyLocale'EnumBg
  | -- | Represents the JSON value @"cs"@
    PostCheckoutSessionsRequestBodyLocale'EnumCs
  | -- | Represents the JSON value @"da"@
    PostCheckoutSessionsRequestBodyLocale'EnumDa
  | -- | Represents the JSON value @"de"@
    PostCheckoutSessionsRequestBodyLocale'EnumDe
  | -- | Represents the JSON value @"el"@
    PostCheckoutSessionsRequestBodyLocale'EnumEl
  | -- | Represents the JSON value @"en"@
    PostCheckoutSessionsRequestBodyLocale'EnumEn
  | -- | Represents the JSON value @"en-GB"@
    PostCheckoutSessionsRequestBodyLocale'EnumEnGB
  | -- | Represents the JSON value @"es"@
    PostCheckoutSessionsRequestBodyLocale'EnumEs
  | -- | Represents the JSON value @"es-419"@
    PostCheckoutSessionsRequestBodyLocale'EnumEs_419
  | -- | Represents the JSON value @"et"@
    PostCheckoutSessionsRequestBodyLocale'EnumEt
  | -- | Represents the JSON value @"fi"@
    PostCheckoutSessionsRequestBodyLocale'EnumFi
  | -- | Represents the JSON value @"fr"@
    PostCheckoutSessionsRequestBodyLocale'EnumFr
  | -- | Represents the JSON value @"fr-CA"@
    PostCheckoutSessionsRequestBodyLocale'EnumFrCA
  | -- | Represents the JSON value @"hu"@
    PostCheckoutSessionsRequestBodyLocale'EnumHu
  | -- | Represents the JSON value @"id"@
    PostCheckoutSessionsRequestBodyLocale'EnumId
  | -- | Represents the JSON value @"it"@
    PostCheckoutSessionsRequestBodyLocale'EnumIt
  | -- | Represents the JSON value @"ja"@
    PostCheckoutSessionsRequestBodyLocale'EnumJa
  | -- | Represents the JSON value @"lt"@
    PostCheckoutSessionsRequestBodyLocale'EnumLt
  | -- | Represents the JSON value @"lv"@
    PostCheckoutSessionsRequestBodyLocale'EnumLv
  | -- | Represents the JSON value @"ms"@
    PostCheckoutSessionsRequestBodyLocale'EnumMs
  | -- | Represents the JSON value @"mt"@
    PostCheckoutSessionsRequestBodyLocale'EnumMt
  | -- | Represents the JSON value @"nb"@
    PostCheckoutSessionsRequestBodyLocale'EnumNb
  | -- | Represents the JSON value @"nl"@
    PostCheckoutSessionsRequestBodyLocale'EnumNl
  | -- | Represents the JSON value @"pl"@
    PostCheckoutSessionsRequestBodyLocale'EnumPl
  | -- | Represents the JSON value @"pt"@
    PostCheckoutSessionsRequestBodyLocale'EnumPt
  | -- | Represents the JSON value @"pt-BR"@
    PostCheckoutSessionsRequestBodyLocale'EnumPtBR
  | -- | Represents the JSON value @"ro"@
    PostCheckoutSessionsRequestBodyLocale'EnumRo
  | -- | Represents the JSON value @"ru"@
    PostCheckoutSessionsRequestBodyLocale'EnumRu
  | -- | Represents the JSON value @"sk"@
    PostCheckoutSessionsRequestBodyLocale'EnumSk
  | -- | Represents the JSON value @"sl"@
    PostCheckoutSessionsRequestBodyLocale'EnumSl
  | -- | Represents the JSON value @"sv"@
    PostCheckoutSessionsRequestBodyLocale'EnumSv
  | -- | Represents the JSON value @"th"@
    PostCheckoutSessionsRequestBodyLocale'EnumTh
  | -- | Represents the JSON value @"tr"@
    PostCheckoutSessionsRequestBodyLocale'EnumTr
  | -- | Represents the JSON value @"zh"@
    PostCheckoutSessionsRequestBodyLocale'EnumZh
  | -- | Represents the JSON value @"zh-HK"@
    PostCheckoutSessionsRequestBodyLocale'EnumZhHK
  | -- | Represents the JSON value @"zh-TW"@
    PostCheckoutSessionsRequestBodyLocale'EnumZhTW
  deriving (Int -> PostCheckoutSessionsRequestBodyLocale' -> ShowS
[PostCheckoutSessionsRequestBodyLocale'] -> ShowS
PostCheckoutSessionsRequestBodyLocale' -> String
(Int -> PostCheckoutSessionsRequestBodyLocale' -> ShowS)
-> (PostCheckoutSessionsRequestBodyLocale' -> String)
-> ([PostCheckoutSessionsRequestBodyLocale'] -> ShowS)
-> Show PostCheckoutSessionsRequestBodyLocale'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyLocale'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyLocale'] -> ShowS
show :: PostCheckoutSessionsRequestBodyLocale' -> String
$cshow :: PostCheckoutSessionsRequestBodyLocale' -> String
showsPrec :: Int -> PostCheckoutSessionsRequestBodyLocale' -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsRequestBodyLocale' -> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyLocale'
-> PostCheckoutSessionsRequestBodyLocale' -> Bool
(PostCheckoutSessionsRequestBodyLocale'
 -> PostCheckoutSessionsRequestBodyLocale' -> Bool)
-> (PostCheckoutSessionsRequestBodyLocale'
    -> PostCheckoutSessionsRequestBodyLocale' -> Bool)
-> Eq PostCheckoutSessionsRequestBodyLocale'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyLocale'
-> PostCheckoutSessionsRequestBodyLocale' -> Bool
$c/= :: PostCheckoutSessionsRequestBodyLocale'
-> PostCheckoutSessionsRequestBodyLocale' -> Bool
== :: PostCheckoutSessionsRequestBodyLocale'
-> PostCheckoutSessionsRequestBodyLocale' -> Bool
$c== :: PostCheckoutSessionsRequestBodyLocale'
-> PostCheckoutSessionsRequestBodyLocale' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyLocale' where
  toJSON :: PostCheckoutSessionsRequestBodyLocale' -> Value
toJSON (PostCheckoutSessionsRequestBodyLocale'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyLocale'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumAuto) = Value
"auto"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumBg) = Value
"bg"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumCs) = Value
"cs"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumDa) = Value
"da"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumDe) = Value
"de"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumEl) = Value
"el"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumEn) = Value
"en"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumEnGB) = Value
"en-GB"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumEs) = Value
"es"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumEs_419) = Value
"es-419"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumEt) = Value
"et"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumFi) = Value
"fi"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumFr) = Value
"fr"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumFrCA) = Value
"fr-CA"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumHu) = Value
"hu"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumId) = Value
"id"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumIt) = Value
"it"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumJa) = Value
"ja"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumLt) = Value
"lt"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumLv) = Value
"lv"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumMs) = Value
"ms"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumMt) = Value
"mt"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumNb) = Value
"nb"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumNl) = Value
"nl"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumPl) = Value
"pl"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumPt) = Value
"pt"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumPtBR) = Value
"pt-BR"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumRo) = Value
"ro"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumRu) = Value
"ru"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumSk) = Value
"sk"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumSl) = Value
"sl"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumSv) = Value
"sv"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumTh) = Value
"th"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumTr) = Value
"tr"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumZh) = Value
"zh"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumZhHK) = Value
"zh-HK"
  toJSON (PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumZhTW) = Value
"zh-TW"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyLocale' where
  parseJSON :: Value -> Parser PostCheckoutSessionsRequestBodyLocale'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyLocale'
-> Parser PostCheckoutSessionsRequestBodyLocale'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"auto" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumAuto
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"bg" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumBg
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"cs" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumCs
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"da" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumDa
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"de" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumDe
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"el" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumEl
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"en" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumEn
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"en-GB" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumEnGB
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"es" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumEs
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"es-419" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumEs_419
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"et" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumEt
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"fi" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumFi
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"fr" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumFr
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"fr-CA" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumFrCA
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"hu" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumHu
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"id" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumId
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"it" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumIt
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ja" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumJa
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"lt" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumLt
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"lv" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumLv
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ms" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumMs
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"mt" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumMt
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"nb" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumNb
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"nl" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumNl
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"pl" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumPl
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"pt" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumPt
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"pt-BR" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumPtBR
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ro" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumRo
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ru" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumRu
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"sk" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumSk
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"sl" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumSl
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"sv" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumSv
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"th" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumTh
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"tr" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumTr
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"zh" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumZh
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"zh-HK" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumZhHK
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"zh-TW" -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'EnumZhTW
            | Bool
GHC.Base.otherwise -> Value -> PostCheckoutSessionsRequestBodyLocale'
PostCheckoutSessionsRequestBodyLocale'Other Value
val
      )

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.mode@ in the specification.
--
-- The mode of the Checkout Session. Required when using prices or \`setup\` mode. Pass \`subscription\` if the Checkout Session includes at least one recurring item.
data PostCheckoutSessionsRequestBodyMode'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyMode'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyMode'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"payment"@
    PostCheckoutSessionsRequestBodyMode'EnumPayment
  | -- | Represents the JSON value @"setup"@
    PostCheckoutSessionsRequestBodyMode'EnumSetup
  | -- | Represents the JSON value @"subscription"@
    PostCheckoutSessionsRequestBodyMode'EnumSubscription
  deriving (Int -> PostCheckoutSessionsRequestBodyMode' -> ShowS
[PostCheckoutSessionsRequestBodyMode'] -> ShowS
PostCheckoutSessionsRequestBodyMode' -> String
(Int -> PostCheckoutSessionsRequestBodyMode' -> ShowS)
-> (PostCheckoutSessionsRequestBodyMode' -> String)
-> ([PostCheckoutSessionsRequestBodyMode'] -> ShowS)
-> Show PostCheckoutSessionsRequestBodyMode'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyMode'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyMode'] -> ShowS
show :: PostCheckoutSessionsRequestBodyMode' -> String
$cshow :: PostCheckoutSessionsRequestBodyMode' -> String
showsPrec :: Int -> PostCheckoutSessionsRequestBodyMode' -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsRequestBodyMode' -> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyMode'
-> PostCheckoutSessionsRequestBodyMode' -> Bool
(PostCheckoutSessionsRequestBodyMode'
 -> PostCheckoutSessionsRequestBodyMode' -> Bool)
-> (PostCheckoutSessionsRequestBodyMode'
    -> PostCheckoutSessionsRequestBodyMode' -> Bool)
-> Eq PostCheckoutSessionsRequestBodyMode'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyMode'
-> PostCheckoutSessionsRequestBodyMode' -> Bool
$c/= :: PostCheckoutSessionsRequestBodyMode'
-> PostCheckoutSessionsRequestBodyMode' -> Bool
== :: PostCheckoutSessionsRequestBodyMode'
-> PostCheckoutSessionsRequestBodyMode' -> Bool
$c== :: PostCheckoutSessionsRequestBodyMode'
-> PostCheckoutSessionsRequestBodyMode' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyMode' where
  toJSON :: PostCheckoutSessionsRequestBodyMode' -> Value
toJSON (PostCheckoutSessionsRequestBodyMode'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyMode'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyMode'
PostCheckoutSessionsRequestBodyMode'EnumPayment) = Value
"payment"
  toJSON (PostCheckoutSessionsRequestBodyMode'
PostCheckoutSessionsRequestBodyMode'EnumSetup) = Value
"setup"
  toJSON (PostCheckoutSessionsRequestBodyMode'
PostCheckoutSessionsRequestBodyMode'EnumSubscription) = Value
"subscription"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyMode' where
  parseJSON :: Value -> Parser PostCheckoutSessionsRequestBodyMode'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyMode'
-> Parser PostCheckoutSessionsRequestBodyMode'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"payment" -> PostCheckoutSessionsRequestBodyMode'
PostCheckoutSessionsRequestBodyMode'EnumPayment
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"setup" -> PostCheckoutSessionsRequestBodyMode'
PostCheckoutSessionsRequestBodyMode'EnumSetup
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"subscription" -> PostCheckoutSessionsRequestBodyMode'
PostCheckoutSessionsRequestBodyMode'EnumSubscription
            | Bool
GHC.Base.otherwise -> Value -> PostCheckoutSessionsRequestBodyMode'
PostCheckoutSessionsRequestBodyMode'Other Value
val
      )

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.payment_intent_data@ in the specification.
--
-- A subset of parameters to be passed to PaymentIntent creation for Checkout Sessions in \`payment\` mode.
data PostCheckoutSessionsRequestBodyPaymentIntentData' = PostCheckoutSessionsRequestBodyPaymentIntentData'
  { -- | application_fee_amount
    PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Int
postCheckoutSessionsRequestBodyPaymentIntentData'ApplicationFeeAmount :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | capture_method
    PostCheckoutSessionsRequestBodyPaymentIntentData'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
postCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'),
    -- | description
    --
    -- Constraints:
    --
    -- * Maximum length of 1000
    PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Description :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | metadata
    PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Object
postCheckoutSessionsRequestBodyPaymentIntentData'Metadata :: (GHC.Maybe.Maybe Data.Aeson.Types.Internal.Object),
    -- | on_behalf_of
    PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'OnBehalfOf :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | receipt_email
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'ReceiptEmail :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | setup_future_usage
    PostCheckoutSessionsRequestBodyPaymentIntentData'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
postCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'),
    -- | shipping
    PostCheckoutSessionsRequestBodyPaymentIntentData'
-> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'),
    -- | statement_descriptor
    --
    -- Constraints:
    --
    -- * Maximum length of 22
    PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'StatementDescriptor :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | statement_descriptor_suffix
    --
    -- Constraints:
    --
    -- * Maximum length of 22
    PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'StatementDescriptorSuffix :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | transfer_data
    PostCheckoutSessionsRequestBodyPaymentIntentData'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
postCheckoutSessionsRequestBodyPaymentIntentData'TransferData :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'),
    -- | transfer_group
    PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'TransferGroup :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int -> PostCheckoutSessionsRequestBodyPaymentIntentData' -> ShowS
[PostCheckoutSessionsRequestBodyPaymentIntentData'] -> ShowS
PostCheckoutSessionsRequestBodyPaymentIntentData' -> String
(Int -> PostCheckoutSessionsRequestBodyPaymentIntentData' -> ShowS)
-> (PostCheckoutSessionsRequestBodyPaymentIntentData' -> String)
-> ([PostCheckoutSessionsRequestBodyPaymentIntentData'] -> ShowS)
-> Show PostCheckoutSessionsRequestBodyPaymentIntentData'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyPaymentIntentData'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyPaymentIntentData'] -> ShowS
show :: PostCheckoutSessionsRequestBodyPaymentIntentData' -> String
$cshow :: PostCheckoutSessionsRequestBodyPaymentIntentData' -> String
showsPrec :: Int -> PostCheckoutSessionsRequestBodyPaymentIntentData' -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsRequestBodyPaymentIntentData' -> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyPaymentIntentData'
-> PostCheckoutSessionsRequestBodyPaymentIntentData' -> Bool
(PostCheckoutSessionsRequestBodyPaymentIntentData'
 -> PostCheckoutSessionsRequestBodyPaymentIntentData' -> Bool)
-> (PostCheckoutSessionsRequestBodyPaymentIntentData'
    -> PostCheckoutSessionsRequestBodyPaymentIntentData' -> Bool)
-> Eq PostCheckoutSessionsRequestBodyPaymentIntentData'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyPaymentIntentData'
-> PostCheckoutSessionsRequestBodyPaymentIntentData' -> Bool
$c/= :: PostCheckoutSessionsRequestBodyPaymentIntentData'
-> PostCheckoutSessionsRequestBodyPaymentIntentData' -> Bool
== :: PostCheckoutSessionsRequestBodyPaymentIntentData'
-> PostCheckoutSessionsRequestBodyPaymentIntentData' -> Bool
$c== :: PostCheckoutSessionsRequestBodyPaymentIntentData'
-> PostCheckoutSessionsRequestBodyPaymentIntentData' -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyPaymentIntentData' where
  toJSON :: PostCheckoutSessionsRequestBodyPaymentIntentData' -> Value
toJSON PostCheckoutSessionsRequestBodyPaymentIntentData'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"application_fee_amount" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Int
postCheckoutSessionsRequestBodyPaymentIntentData'ApplicationFeeAmount PostCheckoutSessionsRequestBodyPaymentIntentData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"capture_method" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
postCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod PostCheckoutSessionsRequestBodyPaymentIntentData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"description" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Description PostCheckoutSessionsRequestBodyPaymentIntentData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text -> Maybe Object -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Object
postCheckoutSessionsRequestBodyPaymentIntentData'Metadata PostCheckoutSessionsRequestBodyPaymentIntentData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"on_behalf_of" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'OnBehalfOf PostCheckoutSessionsRequestBodyPaymentIntentData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"receipt_email" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'ReceiptEmail PostCheckoutSessionsRequestBodyPaymentIntentData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"setup_future_usage" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
postCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage PostCheckoutSessionsRequestBodyPaymentIntentData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"shipping" Text
-> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'
-> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping PostCheckoutSessionsRequestBodyPaymentIntentData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"statement_descriptor" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'StatementDescriptor PostCheckoutSessionsRequestBodyPaymentIntentData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"statement_descriptor_suffix" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'StatementDescriptorSuffix PostCheckoutSessionsRequestBodyPaymentIntentData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"transfer_data" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
postCheckoutSessionsRequestBodyPaymentIntentData'TransferData PostCheckoutSessionsRequestBodyPaymentIntentData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"transfer_group" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'TransferGroup PostCheckoutSessionsRequestBodyPaymentIntentData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyPaymentIntentData' -> Encoding
toEncoding PostCheckoutSessionsRequestBodyPaymentIntentData'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"application_fee_amount" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Int
postCheckoutSessionsRequestBodyPaymentIntentData'ApplicationFeeAmount PostCheckoutSessionsRequestBodyPaymentIntentData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"capture_method" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
postCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod PostCheckoutSessionsRequestBodyPaymentIntentData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"description" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Description PostCheckoutSessionsRequestBodyPaymentIntentData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"metadata" Text -> Maybe Object -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Object
postCheckoutSessionsRequestBodyPaymentIntentData'Metadata PostCheckoutSessionsRequestBodyPaymentIntentData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"on_behalf_of" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'OnBehalfOf PostCheckoutSessionsRequestBodyPaymentIntentData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"receipt_email" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'ReceiptEmail PostCheckoutSessionsRequestBodyPaymentIntentData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"setup_future_usage" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
postCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage PostCheckoutSessionsRequestBodyPaymentIntentData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"shipping" Text
-> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'
-> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping PostCheckoutSessionsRequestBodyPaymentIntentData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"statement_descriptor" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'StatementDescriptor PostCheckoutSessionsRequestBodyPaymentIntentData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"statement_descriptor_suffix" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'StatementDescriptorSuffix PostCheckoutSessionsRequestBodyPaymentIntentData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"transfer_data" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
postCheckoutSessionsRequestBodyPaymentIntentData'TransferData PostCheckoutSessionsRequestBodyPaymentIntentData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"transfer_group" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData' -> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'TransferGroup PostCheckoutSessionsRequestBodyPaymentIntentData'
obj))))))))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyPaymentIntentData' where
  parseJSON :: Value -> Parser PostCheckoutSessionsRequestBodyPaymentIntentData'
parseJSON = String
-> (Object
    -> Parser PostCheckoutSessionsRequestBodyPaymentIntentData')
-> Value
-> Parser PostCheckoutSessionsRequestBodyPaymentIntentData'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyPaymentIntentData'" (\Object
obj -> ((((((((((((Maybe Int
 -> Maybe
      PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
 -> Maybe Text
 -> Maybe Object
 -> Maybe Text
 -> Maybe Text
 -> Maybe
      PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
 -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
 -> Maybe Text
 -> Maybe Text
 -> Maybe
      PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
 -> Maybe Text
 -> PostCheckoutSessionsRequestBodyPaymentIntentData')
-> Parser
     (Maybe Int
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
      -> Maybe Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Int
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> Maybe Text
-> Maybe Object
-> Maybe Text
-> Maybe Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Maybe Text
-> Maybe Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Maybe Text
-> PostCheckoutSessionsRequestBodyPaymentIntentData'
PostCheckoutSessionsRequestBodyPaymentIntentData' Parser
  (Maybe Int
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
   -> Maybe Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData')
-> Parser (Maybe Int)
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
      -> Maybe Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"application_fee_amount")) Parser
  (Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
   -> Maybe Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod')
-> Parser
     (Maybe Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"capture_method")) Parser
  (Maybe Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData')
-> Parser (Maybe Text)
-> Parser
     (Maybe Object
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"description")) Parser
  (Maybe Object
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData')
-> Parser (Maybe Object)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"metadata")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"on_behalf_of")) Parser
  (Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData')
-> Parser (Maybe Text)
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
      -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"receipt_email")) Parser
  (Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
   -> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage')
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"setup_future_usage")) Parser
  (Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData')
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping')
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"shipping")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"statement_descriptor")) Parser
  (Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData')
-> Parser (Maybe Text)
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
      -> Maybe Text -> PostCheckoutSessionsRequestBodyPaymentIntentData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"statement_descriptor_suffix")) Parser
  (Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
   -> Maybe Text -> PostCheckoutSessionsRequestBodyPaymentIntentData')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData')
-> Parser
     (Maybe Text -> PostCheckoutSessionsRequestBodyPaymentIntentData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"transfer_data")) Parser
  (Maybe Text -> PostCheckoutSessionsRequestBodyPaymentIntentData')
-> Parser (Maybe Text)
-> Parser PostCheckoutSessionsRequestBodyPaymentIntentData'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"transfer_group"))

-- | Create a new 'PostCheckoutSessionsRequestBodyPaymentIntentData'' with all required fields.
mkPostCheckoutSessionsRequestBodyPaymentIntentData' :: PostCheckoutSessionsRequestBodyPaymentIntentData'
mkPostCheckoutSessionsRequestBodyPaymentIntentData' :: PostCheckoutSessionsRequestBodyPaymentIntentData'
mkPostCheckoutSessionsRequestBodyPaymentIntentData' =
  PostCheckoutSessionsRequestBodyPaymentIntentData' :: Maybe Int
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> Maybe Text
-> Maybe Object
-> Maybe Text
-> Maybe Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Maybe Text
-> Maybe Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Maybe Text
-> PostCheckoutSessionsRequestBodyPaymentIntentData'
PostCheckoutSessionsRequestBodyPaymentIntentData'
    { postCheckoutSessionsRequestBodyPaymentIntentData'ApplicationFeeAmount :: Maybe Int
postCheckoutSessionsRequestBodyPaymentIntentData'ApplicationFeeAmount = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod :: Maybe
  PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
postCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod = Maybe
  PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'Description :: Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Description = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'Metadata :: Maybe Object
postCheckoutSessionsRequestBodyPaymentIntentData'Metadata = Maybe Object
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'OnBehalfOf :: Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'OnBehalfOf = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'ReceiptEmail :: Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'ReceiptEmail = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage :: Maybe
  PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
postCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage = Maybe
  PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'Shipping :: Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping = Maybe PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'StatementDescriptor :: Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'StatementDescriptor = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'StatementDescriptorSuffix :: Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'StatementDescriptorSuffix = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'TransferData :: Maybe
  PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
postCheckoutSessionsRequestBodyPaymentIntentData'TransferData = Maybe
  PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'TransferGroup :: Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'TransferGroup = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.payment_intent_data.properties.capture_method@ in the specification.
data PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"automatic"@
    PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'EnumAutomatic
  | -- | Represents the JSON value @"manual"@
    PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'EnumManual
  deriving (Int
-> PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> ShowS
[PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod']
-> ShowS
PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
    -> String)
-> ([PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod']
-> ShowS
show :: PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> String
$cshow :: PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> Bool
(PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
 -> PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
    -> PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
    -> Bool)
-> Eq
     PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> Bool
== :: PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod' where
  toJSON :: PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> Value
toJSON (PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'EnumAutomatic) = Value
"automatic"
  toJSON (PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'EnumManual) = Value
"manual"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
-> Parser
     PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"automatic" -> PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'EnumAutomatic
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"manual" -> PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'EnumManual
            | Bool
GHC.Base.otherwise -> Value
-> PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'
PostCheckoutSessionsRequestBodyPaymentIntentData'CaptureMethod'Other Value
val
      )

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.payment_intent_data.properties.setup_future_usage@ in the specification.
data PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"off_session"@
    PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'EnumOffSession
  | -- | Represents the JSON value @"on_session"@
    PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'EnumOnSession
  deriving (Int
-> PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> ShowS
[PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage']
-> ShowS
PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
    -> String)
-> ([PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage']
-> ShowS
show :: PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> String
$cshow :: PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> Bool
(PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
 -> PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
    -> PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
    -> Bool)
-> Eq
     PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> Bool
== :: PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage' where
  toJSON :: PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> Value
toJSON (PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'EnumOffSession) = Value
"off_session"
  toJSON (PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'EnumOnSession) = Value
"on_session"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
-> Parser
     PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"off_session" -> PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'EnumOffSession
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"on_session" -> PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'EnumOnSession
            | Bool
GHC.Base.otherwise -> Value
-> PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'
PostCheckoutSessionsRequestBodyPaymentIntentData'SetupFutureUsage'Other Value
val
      )

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.payment_intent_data.properties.shipping@ in the specification.
data PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping' = PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
  { -- | address
    PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address',
    -- | carrier
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Carrier :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | name
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping' -> Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Name :: Data.Text.Internal.Text,
    -- | phone
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Phone :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | tracking_number
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'TrackingNumber :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> ShowS
[PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping']
-> ShowS
PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
    -> String)
-> ([PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping']
    -> ShowS)
-> Show PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping']
-> ShowS
show :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> String
$cshow :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Bool
(PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
 -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
    -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
    -> Bool)
-> Eq PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Bool
== :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping' where
  toJSON :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping' -> Value
toJSON PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"address" Text
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"carrier" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Carrier PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"name" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping' -> Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Name PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"phone" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Phone PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"tracking_number" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'TrackingNumber PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Encoding
toEncoding PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"address" Text
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"carrier" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Carrier PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"name" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping' -> Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Name PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"phone" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Phone PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"tracking_number" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'TrackingNumber PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
obj)))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
parseJSON = String
-> (Object
    -> Parser
         PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping')
-> Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'" (\Object
obj -> (((((PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
 -> Maybe Text
 -> Text
 -> Maybe Text
 -> Maybe Text
 -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping')
-> Parser
     (PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
      -> Maybe Text
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
-> Text
-> Maybe Text
-> Maybe Text
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping' Parser
  (PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
   -> Maybe Text
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping')
-> Parser
     PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Parser
     (Maybe Text
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"address")) Parser
  (Maybe Text
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping')
-> Parser (Maybe Text)
-> Parser
     (Text
      -> Maybe Text
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"carrier")) Parser
  (Text
   -> Maybe Text
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping')
-> Parser Text
-> Parser
     (Maybe Text
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"name")) Parser
  (Maybe Text
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"phone")) Parser
  (Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping')
-> Parser (Maybe Text)
-> Parser
     PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"tracking_number"))

-- | Create a new 'PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'' with all required fields.
mkPostCheckoutSessionsRequestBodyPaymentIntentData'Shipping' ::
  -- | 'postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
  PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address' ->
  -- | 'postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Name'
  Data.Text.Internal.Text ->
  PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
mkPostCheckoutSessionsRequestBodyPaymentIntentData'Shipping' :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Text
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
mkPostCheckoutSessionsRequestBodyPaymentIntentData'Shipping' PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Name =
  PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping' :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
-> Text
-> Maybe Text
-> Maybe Text
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'
    { postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address = PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address,
      postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Carrier :: Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Carrier = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Name :: Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Name = Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Name,
      postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Phone :: Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Phone = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'TrackingNumber :: Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'TrackingNumber = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.payment_intent_data.properties.shipping.properties.address@ in the specification.
data PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address' = PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
  { -- | city
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'City :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | country
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Country :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | line1
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Line1 :: Data.Text.Internal.Text,
    -- | line2
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Line2 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | postal_code
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'PostalCode :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | state
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'State :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> ShowS
[PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address']
-> ShowS
PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
    -> String)
-> ([PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address']
-> ShowS
show :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> String
$cshow :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Bool
(PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
 -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
    -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
    -> Bool)
-> Eq
     PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Bool
== :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address' where
  toJSON :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Value
toJSON PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"city" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'City PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"country" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Country PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"line1" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Line1 PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"line2" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Line2 PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"postal_code" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'PostalCode PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"state" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'State PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Encoding
toEncoding PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"city" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'City PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"country" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Country PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"line1" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Line1 PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"line2" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Line2 PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"postal_code" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'PostalCode PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"state" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'State PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
obj))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
parseJSON = String
-> (Object
    -> Parser
         PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address')
-> Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'" (\Object
obj -> ((((((Maybe Text
 -> Maybe Text
 -> Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address')
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe Text
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address' Parser
  (Maybe Text
   -> Maybe Text
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"city")) Parser
  (Maybe Text
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address')
-> Parser (Maybe Text)
-> Parser
     (Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"country")) Parser
  (Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address')
-> Parser Text
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"line1")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"line2")) Parser
  (Maybe Text
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"postal_code")) Parser
  (Maybe Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address')
-> Parser (Maybe Text)
-> Parser
     PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"state"))

-- | Create a new 'PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'' with all required fields.
mkPostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address' ::
  -- | 'postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Line1'
  Data.Text.Internal.Text ->
  PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
mkPostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address' :: Text
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
mkPostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address' Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Line1 =
  PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address' :: Maybe Text
-> Maybe Text
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
PostCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'
    { postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'City :: Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'City = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Country :: Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Country = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Line1 :: Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Line1 = Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Line1,
      postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Line2 :: Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'Line2 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'PostalCode :: Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'PostalCode = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'State :: Maybe Text
postCheckoutSessionsRequestBodyPaymentIntentData'Shipping'Address'State = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.payment_intent_data.properties.transfer_data@ in the specification.
data PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData' = PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
  { -- | amount
    PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Maybe Int
postCheckoutSessionsRequestBodyPaymentIntentData'TransferData'Amount :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | destination
    PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Text
postCheckoutSessionsRequestBodyPaymentIntentData'TransferData'Destination :: Data.Text.Internal.Text
  }
  deriving
    ( Int
-> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> ShowS
[PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData']
-> ShowS
PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
    -> String)
-> ([PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData']
-> ShowS
show :: PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> String
$cshow :: PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Bool
(PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
 -> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
    -> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
    -> Bool)
-> Eq
     PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Bool
== :: PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData' where
  toJSON :: PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Value
toJSON PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"amount" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Maybe Int
postCheckoutSessionsRequestBodyPaymentIntentData'TransferData'Amount PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"destination" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Text
postCheckoutSessionsRequestBodyPaymentIntentData'TransferData'Destination PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Encoding
toEncoding PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"amount" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Maybe Int
postCheckoutSessionsRequestBodyPaymentIntentData'TransferData'Amount PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"destination" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
-> Text
postCheckoutSessionsRequestBodyPaymentIntentData'TransferData'Destination PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
obj))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
parseJSON = String
-> (Object
    -> Parser
         PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData')
-> Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'" (\Object
obj -> ((Maybe Int
 -> Text
 -> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData')
-> Parser
     (Maybe Int
      -> Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Int
-> Text
-> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData' Parser
  (Maybe Int
   -> Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData')
-> Parser (Maybe Int)
-> Parser
     (Text
      -> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"amount")) Parser
  (Text
   -> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData')
-> Parser Text
-> Parser
     PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"destination"))

-- | Create a new 'PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'' with all required fields.
mkPostCheckoutSessionsRequestBodyPaymentIntentData'TransferData' ::
  -- | 'postCheckoutSessionsRequestBodyPaymentIntentData'TransferData'Destination'
  Data.Text.Internal.Text ->
  PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
mkPostCheckoutSessionsRequestBodyPaymentIntentData'TransferData' :: Text
-> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
mkPostCheckoutSessionsRequestBodyPaymentIntentData'TransferData' Text
postCheckoutSessionsRequestBodyPaymentIntentData'TransferData'Destination =
  PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData' :: Maybe Int
-> Text
-> PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
PostCheckoutSessionsRequestBodyPaymentIntentData'TransferData'
    { postCheckoutSessionsRequestBodyPaymentIntentData'TransferData'Amount :: Maybe Int
postCheckoutSessionsRequestBodyPaymentIntentData'TransferData'Amount = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentIntentData'TransferData'Destination :: Text
postCheckoutSessionsRequestBodyPaymentIntentData'TransferData'Destination = Text
postCheckoutSessionsRequestBodyPaymentIntentData'TransferData'Destination
    }

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.payment_method_options@ in the specification.
--
-- Payment-method-specific configuration.
data PostCheckoutSessionsRequestBodyPaymentMethodOptions' = PostCheckoutSessionsRequestBodyPaymentMethodOptions'
  { -- | acss_debit
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit')
  }
  deriving
    ( Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> ShowS
[PostCheckoutSessionsRequestBodyPaymentMethodOptions'] -> ShowS
PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> String
(Int
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> ShowS)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> String)
-> ([PostCheckoutSessionsRequestBodyPaymentMethodOptions']
    -> ShowS)
-> Show PostCheckoutSessionsRequestBodyPaymentMethodOptions'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'] -> ShowS
show :: PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> String
$cshow :: PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyPaymentMethodOptions'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> Bool
(PostCheckoutSessionsRequestBodyPaymentMethodOptions'
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> Bool)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions'
    -> PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> Bool)
-> Eq PostCheckoutSessionsRequestBodyPaymentMethodOptions'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> Bool
$c/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> Bool
== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> Bool
$c== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions' where
  toJSON :: PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> Value
toJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"acss_debit" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit PostCheckoutSessionsRequestBodyPaymentMethodOptions'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyPaymentMethodOptions' -> Encoding
toEncoding PostCheckoutSessionsRequestBodyPaymentMethodOptions'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs (Text
"acss_debit" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit PostCheckoutSessionsRequestBodyPaymentMethodOptions'
obj)

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions' where
  parseJSON :: Value
-> Parser PostCheckoutSessionsRequestBodyPaymentMethodOptions'
parseJSON = String
-> (Object
    -> Parser PostCheckoutSessionsRequestBodyPaymentMethodOptions')
-> Value
-> Parser PostCheckoutSessionsRequestBodyPaymentMethodOptions'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyPaymentMethodOptions'" (\Object
obj -> (Maybe
   PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
      -> PostCheckoutSessionsRequestBodyPaymentMethodOptions')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'
PostCheckoutSessionsRequestBodyPaymentMethodOptions' Parser
  (Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
   -> PostCheckoutSessionsRequestBodyPaymentMethodOptions')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit')
-> Parser PostCheckoutSessionsRequestBodyPaymentMethodOptions'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"acss_debit"))

-- | Create a new 'PostCheckoutSessionsRequestBodyPaymentMethodOptions'' with all required fields.
mkPostCheckoutSessionsRequestBodyPaymentMethodOptions' :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'
mkPostCheckoutSessionsRequestBodyPaymentMethodOptions' :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'
mkPostCheckoutSessionsRequestBodyPaymentMethodOptions' = PostCheckoutSessionsRequestBodyPaymentMethodOptions' :: Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'
PostCheckoutSessionsRequestBodyPaymentMethodOptions' {postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit :: Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit = Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
forall a. Maybe a
GHC.Maybe.Nothing}

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.payment_method_options.properties.acss_debit@ in the specification.
data PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit' = PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
  { -- | currency
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'),
    -- | mandate_options
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'),
    -- | verification_method
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod')
  }
  deriving
    ( Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> ShowS
[PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit']
-> ShowS
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
    -> String)
-> ([PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit']
-> ShowS
show :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> String
$cshow :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Bool
(PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
    -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
    -> Bool)
-> Eq
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Bool
== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit' where
  toJSON :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Value
toJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"currency" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"mandate_options" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"verification_method" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Encoding
toEncoding PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"currency" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"mandate_options" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"verification_method" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
obj)))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
parseJSON = String
-> (Object
    -> Parser
         PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit')
-> Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'" (\Object
obj -> (((Maybe
   PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
 -> Maybe
      PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
 -> Maybe
      PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
      -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit' Parser
  (Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
   -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
      -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"currency")) Parser
  (Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
   -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
      -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"mandate_options")) Parser
  (Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
   -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod')
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"verification_method"))

-- | Create a new 'PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'' with all required fields.
mkPostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit' :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
mkPostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit' :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
mkPostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit' =
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit' :: Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'
    { postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency :: Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency = Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions :: Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions = Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod :: Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod = Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.payment_method_options.properties.acss_debit.properties.currency@ in the specification.
data PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"cad"@
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'EnumCad
  | -- | Represents the JSON value @"usd"@
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'EnumUsd
  deriving (Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> ShowS
[PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency']
-> ShowS
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
    -> String)
-> ([PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency']
-> ShowS
show :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> String
$cshow :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> Bool
(PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
    -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
    -> Bool)
-> Eq
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> Bool
== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency' where
  toJSON :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> Value
toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'EnumCad) = Value
"cad"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'EnumUsd) = Value
"usd"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"cad" -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'EnumCad
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"usd" -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'EnumUsd
            | Bool
GHC.Base.otherwise -> Value
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'Currency'Other Value
val
      )

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.payment_method_options.properties.acss_debit.properties.mandate_options@ in the specification.
data PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions' = PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
  { -- | custom_mandate_url
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants),
    -- | interval_description
    --
    -- Constraints:
    --
    -- * Maximum length of 500
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'IntervalDescription :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | payment_schedule
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'),
    -- | transaction_type
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType')
  }
  deriving
    ( Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> ShowS
[PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions']
-> ShowS
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
    -> String)
-> ([PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions']
-> ShowS
show :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> String
$cshow :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Bool
(PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
    -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
    -> Bool)
-> Eq
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Bool
== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions' where
  toJSON :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Value
toJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"custom_mandate_url" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"interval_description" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'IntervalDescription PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"payment_schedule" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"transaction_type" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Encoding
toEncoding PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"custom_mandate_url" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"interval_description" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Maybe Text
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'IntervalDescription PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"payment_schedule" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"transaction_type" Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
obj))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
parseJSON = String
-> (Object
    -> Parser
         PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions')
-> Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'" (\Object
obj -> ((((Maybe
   PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
 -> Maybe Text
 -> Maybe
      PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
 -> Maybe
      PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
      -> Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
      -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> Maybe Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions' Parser
  (Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
   -> Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
   -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants)
-> Parser
     (Maybe Text
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
      -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"custom_mandate_url")) Parser
  (Maybe Text
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
   -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions')
-> Parser (Maybe Text)
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
      -> Maybe
           PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
      -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"interval_description")) Parser
  (Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
   -> Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
   -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
      -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"payment_schedule")) Parser
  (Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
   -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType')
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"transaction_type"))

-- | Create a new 'PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'' with all required fields.
mkPostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions' :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
mkPostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions' :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
mkPostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions' =
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions' :: Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> Maybe Text
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> Maybe
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'
    { postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl :: Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl = Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'IntervalDescription :: Maybe Text
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'IntervalDescription = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule :: Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule = Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType :: Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
postCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType = Maybe
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the oneOf schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.payment_method_options.properties.acss_debit.properties.mandate_options.properties.custom_mandate_url.anyOf@ in the specification.
data PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
  = -- | Represents the JSON value @""@
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'EmptyString
  | PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Text Data.Text.Internal.Text
  deriving (Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> ShowS
[PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants]
-> ShowS
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> String
(Int
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
    -> String)
-> ([PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants]
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants]
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants]
-> ShowS
show :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> String
$cshow :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> Bool
(PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
 -> Bool)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
    -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
    -> Bool)
-> Eq
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> Bool
== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> Bool
$c== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants where
  toJSON :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> Value
toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Text Text
a) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
a
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'EmptyString) = Value
""

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
parseJSON Value
val =
    if
        | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"" -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'EmptyString
        | Bool
GHC.Base.otherwise -> case (Text
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Text (Text
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants)
-> Result Text
-> Result
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Text
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result
  PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> Result
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> Result
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched" of
          Data.Aeson.Types.Internal.Success PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
a -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
a
          Data.Aeson.Types.Internal.Error String
a -> String
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'CustomMandateUrl'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.payment_method_options.properties.acss_debit.properties.mandate_options.properties.payment_schedule@ in the specification.
data PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"combined"@
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'EnumCombined
  | -- | Represents the JSON value @"interval"@
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'EnumInterval
  | -- | Represents the JSON value @"sporadic"@
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'EnumSporadic
  deriving (Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> ShowS
[PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule']
-> ShowS
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
    -> String)
-> ([PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule']
-> ShowS
show :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> String
$cshow :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> Bool
(PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
    -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
    -> Bool)
-> Eq
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> Bool
== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule' where
  toJSON :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> Value
toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'EnumCombined) = Value
"combined"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'EnumInterval) = Value
"interval"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'EnumSporadic) = Value
"sporadic"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"combined" -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'EnumCombined
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"interval" -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'EnumInterval
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"sporadic" -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'EnumSporadic
            | Bool
GHC.Base.otherwise -> Value
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'PaymentSchedule'Other Value
val
      )

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.payment_method_options.properties.acss_debit.properties.mandate_options.properties.transaction_type@ in the specification.
data PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"business"@
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'EnumBusiness
  | -- | Represents the JSON value @"personal"@
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'EnumPersonal
  deriving (Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> ShowS
[PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType']
-> ShowS
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
    -> String)
-> ([PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType']
-> ShowS
show :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> String
$cshow :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> Bool
(PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
    -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
    -> Bool)
-> Eq
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> Bool
== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType' where
  toJSON :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> Value
toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'EnumBusiness) = Value
"business"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'EnumPersonal) = Value
"personal"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"business" -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'EnumBusiness
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"personal" -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'EnumPersonal
            | Bool
GHC.Base.otherwise -> Value
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'MandateOptions'TransactionType'Other Value
val
      )

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.payment_method_options.properties.acss_debit.properties.verification_method@ in the specification.
data PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"automatic"@
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'EnumAutomatic
  | -- | Represents the JSON value @"instant"@
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'EnumInstant
  | -- | Represents the JSON value @"microdeposits"@
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'EnumMicrodeposits
  deriving (Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> ShowS
[PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod']
-> ShowS
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
    -> String)
-> ([PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod']
-> ShowS
show :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> String
$cshow :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> Bool
(PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
 -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
    -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
    -> Bool)
-> Eq
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> Bool
== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod' where
  toJSON :: PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> Value
toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'EnumAutomatic) = Value
"automatic"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'EnumInstant) = Value
"instant"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'EnumMicrodeposits) = Value
"microdeposits"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
-> Parser
     PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"automatic" -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'EnumAutomatic
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"instant" -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'EnumInstant
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"microdeposits" -> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'EnumMicrodeposits
            | Bool
GHC.Base.otherwise -> Value
-> PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'
PostCheckoutSessionsRequestBodyPaymentMethodOptions'AcssDebit'VerificationMethod'Other Value
val
      )

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.payment_method_types.items@ in the specification.
data PostCheckoutSessionsRequestBodyPaymentMethodTypes'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"acss_debit"@
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumAcssDebit
  | -- | Represents the JSON value @"afterpay_clearpay"@
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumAfterpayClearpay
  | -- | Represents the JSON value @"alipay"@
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumAlipay
  | -- | Represents the JSON value @"bacs_debit"@
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumBacsDebit
  | -- | Represents the JSON value @"bancontact"@
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumBancontact
  | -- | Represents the JSON value @"card"@
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumCard
  | -- | Represents the JSON value @"eps"@
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumEps
  | -- | Represents the JSON value @"fpx"@
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumFpx
  | -- | Represents the JSON value @"giropay"@
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumGiropay
  | -- | Represents the JSON value @"grabpay"@
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumGrabpay
  | -- | Represents the JSON value @"ideal"@
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumIdeal
  | -- | Represents the JSON value @"p24"@
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumP24
  | -- | Represents the JSON value @"sepa_debit"@
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumSepaDebit
  | -- | Represents the JSON value @"sofort"@
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumSofort
  deriving (Int -> PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> ShowS
[PostCheckoutSessionsRequestBodyPaymentMethodTypes'] -> ShowS
PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> String
(Int
 -> PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> ShowS)
-> (PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> String)
-> ([PostCheckoutSessionsRequestBodyPaymentMethodTypes'] -> ShowS)
-> Show PostCheckoutSessionsRequestBodyPaymentMethodTypes'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyPaymentMethodTypes'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyPaymentMethodTypes'] -> ShowS
show :: PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> String
$cshow :: PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> String
showsPrec :: Int -> PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyPaymentMethodTypes'
-> PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> Bool
(PostCheckoutSessionsRequestBodyPaymentMethodTypes'
 -> PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> Bool)
-> (PostCheckoutSessionsRequestBodyPaymentMethodTypes'
    -> PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> Bool)
-> Eq PostCheckoutSessionsRequestBodyPaymentMethodTypes'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyPaymentMethodTypes'
-> PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> Bool
$c/= :: PostCheckoutSessionsRequestBodyPaymentMethodTypes'
-> PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> Bool
== :: PostCheckoutSessionsRequestBodyPaymentMethodTypes'
-> PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> Bool
$c== :: PostCheckoutSessionsRequestBodyPaymentMethodTypes'
-> PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyPaymentMethodTypes' where
  toJSON :: PostCheckoutSessionsRequestBodyPaymentMethodTypes' -> Value
toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumAcssDebit) = Value
"acss_debit"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumAfterpayClearpay) = Value
"afterpay_clearpay"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumAlipay) = Value
"alipay"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumBacsDebit) = Value
"bacs_debit"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumBancontact) = Value
"bancontact"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumCard) = Value
"card"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumEps) = Value
"eps"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumFpx) = Value
"fpx"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumGiropay) = Value
"giropay"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumGrabpay) = Value
"grabpay"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumIdeal) = Value
"ideal"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumP24) = Value
"p24"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumSepaDebit) = Value
"sepa_debit"
  toJSON (PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumSofort) = Value
"sofort"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyPaymentMethodTypes' where
  parseJSON :: Value -> Parser PostCheckoutSessionsRequestBodyPaymentMethodTypes'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyPaymentMethodTypes'
-> Parser PostCheckoutSessionsRequestBodyPaymentMethodTypes'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"acss_debit" -> PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumAcssDebit
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"afterpay_clearpay" -> PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumAfterpayClearpay
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"alipay" -> PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumAlipay
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"bacs_debit" -> PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumBacsDebit
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"bancontact" -> PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumBancontact
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"card" -> PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumCard
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"eps" -> PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumEps
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"fpx" -> PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumFpx
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"giropay" -> PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumGiropay
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"grabpay" -> PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumGrabpay
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ideal" -> PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumIdeal
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"p24" -> PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumP24
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"sepa_debit" -> PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumSepaDebit
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"sofort" -> PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'EnumSofort
            | Bool
GHC.Base.otherwise -> Value -> PostCheckoutSessionsRequestBodyPaymentMethodTypes'
PostCheckoutSessionsRequestBodyPaymentMethodTypes'Other Value
val
      )

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.setup_intent_data@ in the specification.
--
-- A subset of parameters to be passed to SetupIntent creation for Checkout Sessions in \`setup\` mode.
data PostCheckoutSessionsRequestBodySetupIntentData' = PostCheckoutSessionsRequestBodySetupIntentData'
  { -- | description
    --
    -- Constraints:
    --
    -- * Maximum length of 1000
    PostCheckoutSessionsRequestBodySetupIntentData' -> Maybe Text
postCheckoutSessionsRequestBodySetupIntentData'Description :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | metadata
    PostCheckoutSessionsRequestBodySetupIntentData' -> Maybe Object
postCheckoutSessionsRequestBodySetupIntentData'Metadata :: (GHC.Maybe.Maybe Data.Aeson.Types.Internal.Object),
    -- | on_behalf_of
    PostCheckoutSessionsRequestBodySetupIntentData' -> Maybe Text
postCheckoutSessionsRequestBodySetupIntentData'OnBehalfOf :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int -> PostCheckoutSessionsRequestBodySetupIntentData' -> ShowS
[PostCheckoutSessionsRequestBodySetupIntentData'] -> ShowS
PostCheckoutSessionsRequestBodySetupIntentData' -> String
(Int -> PostCheckoutSessionsRequestBodySetupIntentData' -> ShowS)
-> (PostCheckoutSessionsRequestBodySetupIntentData' -> String)
-> ([PostCheckoutSessionsRequestBodySetupIntentData'] -> ShowS)
-> Show PostCheckoutSessionsRequestBodySetupIntentData'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodySetupIntentData'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodySetupIntentData'] -> ShowS
show :: PostCheckoutSessionsRequestBodySetupIntentData' -> String
$cshow :: PostCheckoutSessionsRequestBodySetupIntentData' -> String
showsPrec :: Int -> PostCheckoutSessionsRequestBodySetupIntentData' -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsRequestBodySetupIntentData' -> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodySetupIntentData'
-> PostCheckoutSessionsRequestBodySetupIntentData' -> Bool
(PostCheckoutSessionsRequestBodySetupIntentData'
 -> PostCheckoutSessionsRequestBodySetupIntentData' -> Bool)
-> (PostCheckoutSessionsRequestBodySetupIntentData'
    -> PostCheckoutSessionsRequestBodySetupIntentData' -> Bool)
-> Eq PostCheckoutSessionsRequestBodySetupIntentData'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodySetupIntentData'
-> PostCheckoutSessionsRequestBodySetupIntentData' -> Bool
$c/= :: PostCheckoutSessionsRequestBodySetupIntentData'
-> PostCheckoutSessionsRequestBodySetupIntentData' -> Bool
== :: PostCheckoutSessionsRequestBodySetupIntentData'
-> PostCheckoutSessionsRequestBodySetupIntentData' -> Bool
$c== :: PostCheckoutSessionsRequestBodySetupIntentData'
-> PostCheckoutSessionsRequestBodySetupIntentData' -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodySetupIntentData' where
  toJSON :: PostCheckoutSessionsRequestBodySetupIntentData' -> Value
toJSON PostCheckoutSessionsRequestBodySetupIntentData'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"description" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySetupIntentData' -> Maybe Text
postCheckoutSessionsRequestBodySetupIntentData'Description PostCheckoutSessionsRequestBodySetupIntentData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text -> Maybe Object -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySetupIntentData' -> Maybe Object
postCheckoutSessionsRequestBodySetupIntentData'Metadata PostCheckoutSessionsRequestBodySetupIntentData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"on_behalf_of" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySetupIntentData' -> Maybe Text
postCheckoutSessionsRequestBodySetupIntentData'OnBehalfOf PostCheckoutSessionsRequestBodySetupIntentData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodySetupIntentData' -> Encoding
toEncoding PostCheckoutSessionsRequestBodySetupIntentData'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"description" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySetupIntentData' -> Maybe Text
postCheckoutSessionsRequestBodySetupIntentData'Description PostCheckoutSessionsRequestBodySetupIntentData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"metadata" Text -> Maybe Object -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySetupIntentData' -> Maybe Object
postCheckoutSessionsRequestBodySetupIntentData'Metadata PostCheckoutSessionsRequestBodySetupIntentData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"on_behalf_of" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySetupIntentData' -> Maybe Text
postCheckoutSessionsRequestBodySetupIntentData'OnBehalfOf PostCheckoutSessionsRequestBodySetupIntentData'
obj)))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodySetupIntentData' where
  parseJSON :: Value -> Parser PostCheckoutSessionsRequestBodySetupIntentData'
parseJSON = String
-> (Object
    -> Parser PostCheckoutSessionsRequestBodySetupIntentData')
-> Value
-> Parser PostCheckoutSessionsRequestBodySetupIntentData'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodySetupIntentData'" (\Object
obj -> (((Maybe Text
 -> Maybe Object
 -> Maybe Text
 -> PostCheckoutSessionsRequestBodySetupIntentData')
-> Parser
     (Maybe Text
      -> Maybe Object
      -> Maybe Text
      -> PostCheckoutSessionsRequestBodySetupIntentData')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe Object
-> Maybe Text
-> PostCheckoutSessionsRequestBodySetupIntentData'
PostCheckoutSessionsRequestBodySetupIntentData' Parser
  (Maybe Text
   -> Maybe Object
   -> Maybe Text
   -> PostCheckoutSessionsRequestBodySetupIntentData')
-> Parser (Maybe Text)
-> Parser
     (Maybe Object
      -> Maybe Text -> PostCheckoutSessionsRequestBodySetupIntentData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"description")) Parser
  (Maybe Object
   -> Maybe Text -> PostCheckoutSessionsRequestBodySetupIntentData')
-> Parser (Maybe Object)
-> Parser
     (Maybe Text -> PostCheckoutSessionsRequestBodySetupIntentData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"metadata")) Parser
  (Maybe Text -> PostCheckoutSessionsRequestBodySetupIntentData')
-> Parser (Maybe Text)
-> Parser PostCheckoutSessionsRequestBodySetupIntentData'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"on_behalf_of"))

-- | Create a new 'PostCheckoutSessionsRequestBodySetupIntentData'' with all required fields.
mkPostCheckoutSessionsRequestBodySetupIntentData' :: PostCheckoutSessionsRequestBodySetupIntentData'
mkPostCheckoutSessionsRequestBodySetupIntentData' :: PostCheckoutSessionsRequestBodySetupIntentData'
mkPostCheckoutSessionsRequestBodySetupIntentData' =
  PostCheckoutSessionsRequestBodySetupIntentData' :: Maybe Text
-> Maybe Object
-> Maybe Text
-> PostCheckoutSessionsRequestBodySetupIntentData'
PostCheckoutSessionsRequestBodySetupIntentData'
    { postCheckoutSessionsRequestBodySetupIntentData'Description :: Maybe Text
postCheckoutSessionsRequestBodySetupIntentData'Description = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodySetupIntentData'Metadata :: Maybe Object
postCheckoutSessionsRequestBodySetupIntentData'Metadata = Maybe Object
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodySetupIntentData'OnBehalfOf :: Maybe Text
postCheckoutSessionsRequestBodySetupIntentData'OnBehalfOf = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.shipping_address_collection@ in the specification.
--
-- When set, provides configuration for Checkout to collect a shipping address from a customer.
data PostCheckoutSessionsRequestBodyShippingAddressCollection' = PostCheckoutSessionsRequestBodyShippingAddressCollection'
  { -- | allowed_countries
    PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
postCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries :: ([PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'])
  }
  deriving
    ( Int
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> ShowS
[PostCheckoutSessionsRequestBodyShippingAddressCollection']
-> ShowS
PostCheckoutSessionsRequestBodyShippingAddressCollection' -> String
(Int
 -> PostCheckoutSessionsRequestBodyShippingAddressCollection'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyShippingAddressCollection'
    -> String)
-> ([PostCheckoutSessionsRequestBodyShippingAddressCollection']
    -> ShowS)
-> Show PostCheckoutSessionsRequestBodyShippingAddressCollection'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyShippingAddressCollection']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyShippingAddressCollection']
-> ShowS
show :: PostCheckoutSessionsRequestBodyShippingAddressCollection' -> String
$cshow :: PostCheckoutSessionsRequestBodyShippingAddressCollection' -> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> Bool
(PostCheckoutSessionsRequestBodyShippingAddressCollection'
 -> PostCheckoutSessionsRequestBodyShippingAddressCollection'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyShippingAddressCollection'
    -> PostCheckoutSessionsRequestBodyShippingAddressCollection'
    -> Bool)
-> Eq PostCheckoutSessionsRequestBodyShippingAddressCollection'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> Bool
== :: PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyShippingAddressCollection' where
  toJSON :: PostCheckoutSessionsRequestBodyShippingAddressCollection' -> Value
toJSON PostCheckoutSessionsRequestBodyShippingAddressCollection'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"allowed_countries" Text
-> [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
postCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries PostCheckoutSessionsRequestBodyShippingAddressCollection'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> Encoding
toEncoding PostCheckoutSessionsRequestBodyShippingAddressCollection'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs (Text
"allowed_countries" Text
-> [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyShippingAddressCollection'
-> [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
postCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries PostCheckoutSessionsRequestBodyShippingAddressCollection'
obj)

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyShippingAddressCollection' where
  parseJSON :: Value
-> Parser PostCheckoutSessionsRequestBodyShippingAddressCollection'
parseJSON = String
-> (Object
    -> Parser
         PostCheckoutSessionsRequestBodyShippingAddressCollection')
-> Value
-> Parser PostCheckoutSessionsRequestBodyShippingAddressCollection'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyShippingAddressCollection'" (\Object
obj -> ([PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
 -> PostCheckoutSessionsRequestBodyShippingAddressCollection')
-> Parser
     ([PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
      -> PostCheckoutSessionsRequestBodyShippingAddressCollection')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'
PostCheckoutSessionsRequestBodyShippingAddressCollection' Parser
  ([PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
   -> PostCheckoutSessionsRequestBodyShippingAddressCollection')
-> Parser
     [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
-> Parser PostCheckoutSessionsRequestBodyShippingAddressCollection'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"allowed_countries"))

-- | Create a new 'PostCheckoutSessionsRequestBodyShippingAddressCollection'' with all required fields.
mkPostCheckoutSessionsRequestBodyShippingAddressCollection' ::
  -- | 'postCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
  [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'] ->
  PostCheckoutSessionsRequestBodyShippingAddressCollection'
mkPostCheckoutSessionsRequestBodyShippingAddressCollection' :: [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'
mkPostCheckoutSessionsRequestBodyShippingAddressCollection' [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
postCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries = PostCheckoutSessionsRequestBodyShippingAddressCollection' :: [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'
PostCheckoutSessionsRequestBodyShippingAddressCollection' {postCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries :: [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
postCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries = [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
postCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries}

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.shipping_address_collection.properties.allowed_countries.items@ in the specification.
data PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"AC"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAC
  | -- | Represents the JSON value @"AD"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAD
  | -- | Represents the JSON value @"AE"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAE
  | -- | Represents the JSON value @"AF"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAF
  | -- | Represents the JSON value @"AG"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAG
  | -- | Represents the JSON value @"AI"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAI
  | -- | Represents the JSON value @"AL"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAL
  | -- | Represents the JSON value @"AM"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAM
  | -- | Represents the JSON value @"AO"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAO
  | -- | Represents the JSON value @"AQ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAQ
  | -- | Represents the JSON value @"AR"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAR
  | -- | Represents the JSON value @"AT"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAT
  | -- | Represents the JSON value @"AU"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAU
  | -- | Represents the JSON value @"AW"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAW
  | -- | Represents the JSON value @"AX"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAX
  | -- | Represents the JSON value @"AZ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAZ
  | -- | Represents the JSON value @"BA"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBA
  | -- | Represents the JSON value @"BB"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBB
  | -- | Represents the JSON value @"BD"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBD
  | -- | Represents the JSON value @"BE"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBE
  | -- | Represents the JSON value @"BF"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBF
  | -- | Represents the JSON value @"BG"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBG
  | -- | Represents the JSON value @"BH"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBH
  | -- | Represents the JSON value @"BI"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBI
  | -- | Represents the JSON value @"BJ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBJ
  | -- | Represents the JSON value @"BL"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBL
  | -- | Represents the JSON value @"BM"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBM
  | -- | Represents the JSON value @"BN"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBN
  | -- | Represents the JSON value @"BO"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBO
  | -- | Represents the JSON value @"BQ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBQ
  | -- | Represents the JSON value @"BR"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBR
  | -- | Represents the JSON value @"BS"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBS
  | -- | Represents the JSON value @"BT"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBT
  | -- | Represents the JSON value @"BV"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBV
  | -- | Represents the JSON value @"BW"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBW
  | -- | Represents the JSON value @"BY"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBY
  | -- | Represents the JSON value @"BZ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBZ
  | -- | Represents the JSON value @"CA"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCA
  | -- | Represents the JSON value @"CD"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCD
  | -- | Represents the JSON value @"CF"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCF
  | -- | Represents the JSON value @"CG"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCG
  | -- | Represents the JSON value @"CH"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCH
  | -- | Represents the JSON value @"CI"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCI
  | -- | Represents the JSON value @"CK"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCK
  | -- | Represents the JSON value @"CL"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCL
  | -- | Represents the JSON value @"CM"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCM
  | -- | Represents the JSON value @"CN"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCN
  | -- | Represents the JSON value @"CO"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCO
  | -- | Represents the JSON value @"CR"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCR
  | -- | Represents the JSON value @"CV"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCV
  | -- | Represents the JSON value @"CW"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCW
  | -- | Represents the JSON value @"CY"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCY
  | -- | Represents the JSON value @"CZ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCZ
  | -- | Represents the JSON value @"DE"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDE
  | -- | Represents the JSON value @"DJ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDJ
  | -- | Represents the JSON value @"DK"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDK
  | -- | Represents the JSON value @"DM"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDM
  | -- | Represents the JSON value @"DO"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDO
  | -- | Represents the JSON value @"DZ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDZ
  | -- | Represents the JSON value @"EC"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumEC
  | -- | Represents the JSON value @"EE"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumEE
  | -- | Represents the JSON value @"EG"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumEG
  | -- | Represents the JSON value @"EH"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumEH
  | -- | Represents the JSON value @"ER"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumER
  | -- | Represents the JSON value @"ES"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumES
  | -- | Represents the JSON value @"ET"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumET
  | -- | Represents the JSON value @"FI"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumFI
  | -- | Represents the JSON value @"FJ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumFJ
  | -- | Represents the JSON value @"FK"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumFK
  | -- | Represents the JSON value @"FO"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumFO
  | -- | Represents the JSON value @"FR"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumFR
  | -- | Represents the JSON value @"GA"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGA
  | -- | Represents the JSON value @"GB"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGB
  | -- | Represents the JSON value @"GD"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGD
  | -- | Represents the JSON value @"GE"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGE
  | -- | Represents the JSON value @"GF"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGF
  | -- | Represents the JSON value @"GG"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGG
  | -- | Represents the JSON value @"GH"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGH
  | -- | Represents the JSON value @"GI"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGI
  | -- | Represents the JSON value @"GL"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGL
  | -- | Represents the JSON value @"GM"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGM
  | -- | Represents the JSON value @"GN"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGN
  | -- | Represents the JSON value @"GP"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGP
  | -- | Represents the JSON value @"GQ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGQ
  | -- | Represents the JSON value @"GR"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGR
  | -- | Represents the JSON value @"GS"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGS
  | -- | Represents the JSON value @"GT"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGT
  | -- | Represents the JSON value @"GU"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGU
  | -- | Represents the JSON value @"GW"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGW
  | -- | Represents the JSON value @"GY"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGY
  | -- | Represents the JSON value @"HK"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumHK
  | -- | Represents the JSON value @"HN"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumHN
  | -- | Represents the JSON value @"HR"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumHR
  | -- | Represents the JSON value @"HT"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumHT
  | -- | Represents the JSON value @"HU"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumHU
  | -- | Represents the JSON value @"ID"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumID
  | -- | Represents the JSON value @"IE"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIE
  | -- | Represents the JSON value @"IL"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIL
  | -- | Represents the JSON value @"IM"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIM
  | -- | Represents the JSON value @"IN"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIN
  | -- | Represents the JSON value @"IO"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIO
  | -- | Represents the JSON value @"IQ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIQ
  | -- | Represents the JSON value @"IS"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIS
  | -- | Represents the JSON value @"IT"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIT
  | -- | Represents the JSON value @"JE"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumJE
  | -- | Represents the JSON value @"JM"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumJM
  | -- | Represents the JSON value @"JO"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumJO
  | -- | Represents the JSON value @"JP"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumJP
  | -- | Represents the JSON value @"KE"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKE
  | -- | Represents the JSON value @"KG"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKG
  | -- | Represents the JSON value @"KH"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKH
  | -- | Represents the JSON value @"KI"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKI
  | -- | Represents the JSON value @"KM"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKM
  | -- | Represents the JSON value @"KN"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKN
  | -- | Represents the JSON value @"KR"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKR
  | -- | Represents the JSON value @"KW"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKW
  | -- | Represents the JSON value @"KY"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKY
  | -- | Represents the JSON value @"KZ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKZ
  | -- | Represents the JSON value @"LA"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLA
  | -- | Represents the JSON value @"LB"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLB
  | -- | Represents the JSON value @"LC"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLC
  | -- | Represents the JSON value @"LI"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLI
  | -- | Represents the JSON value @"LK"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLK
  | -- | Represents the JSON value @"LR"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLR
  | -- | Represents the JSON value @"LS"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLS
  | -- | Represents the JSON value @"LT"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLT
  | -- | Represents the JSON value @"LU"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLU
  | -- | Represents the JSON value @"LV"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLV
  | -- | Represents the JSON value @"LY"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLY
  | -- | Represents the JSON value @"MA"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMA
  | -- | Represents the JSON value @"MC"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMC
  | -- | Represents the JSON value @"MD"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMD
  | -- | Represents the JSON value @"ME"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumME
  | -- | Represents the JSON value @"MF"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMF
  | -- | Represents the JSON value @"MG"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMG
  | -- | Represents the JSON value @"MK"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMK
  | -- | Represents the JSON value @"ML"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumML
  | -- | Represents the JSON value @"MM"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMM
  | -- | Represents the JSON value @"MN"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMN
  | -- | Represents the JSON value @"MO"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMO
  | -- | Represents the JSON value @"MQ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMQ
  | -- | Represents the JSON value @"MR"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMR
  | -- | Represents the JSON value @"MS"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMS
  | -- | Represents the JSON value @"MT"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMT
  | -- | Represents the JSON value @"MU"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMU
  | -- | Represents the JSON value @"MV"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMV
  | -- | Represents the JSON value @"MW"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMW
  | -- | Represents the JSON value @"MX"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMX
  | -- | Represents the JSON value @"MY"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMY
  | -- | Represents the JSON value @"MZ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMZ
  | -- | Represents the JSON value @"NA"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNA
  | -- | Represents the JSON value @"NC"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNC
  | -- | Represents the JSON value @"NE"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNE
  | -- | Represents the JSON value @"NG"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNG
  | -- | Represents the JSON value @"NI"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNI
  | -- | Represents the JSON value @"NL"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNL
  | -- | Represents the JSON value @"NO"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNO
  | -- | Represents the JSON value @"NP"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNP
  | -- | Represents the JSON value @"NR"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNR
  | -- | Represents the JSON value @"NU"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNU
  | -- | Represents the JSON value @"NZ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNZ
  | -- | Represents the JSON value @"OM"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumOM
  | -- | Represents the JSON value @"PA"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPA
  | -- | Represents the JSON value @"PE"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPE
  | -- | Represents the JSON value @"PF"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPF
  | -- | Represents the JSON value @"PG"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPG
  | -- | Represents the JSON value @"PH"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPH
  | -- | Represents the JSON value @"PK"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPK
  | -- | Represents the JSON value @"PL"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPL
  | -- | Represents the JSON value @"PM"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPM
  | -- | Represents the JSON value @"PN"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPN
  | -- | Represents the JSON value @"PR"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPR
  | -- | Represents the JSON value @"PS"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPS
  | -- | Represents the JSON value @"PT"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPT
  | -- | Represents the JSON value @"PY"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPY
  | -- | Represents the JSON value @"QA"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumQA
  | -- | Represents the JSON value @"RE"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumRE
  | -- | Represents the JSON value @"RO"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumRO
  | -- | Represents the JSON value @"RS"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumRS
  | -- | Represents the JSON value @"RU"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumRU
  | -- | Represents the JSON value @"RW"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumRW
  | -- | Represents the JSON value @"SA"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSA
  | -- | Represents the JSON value @"SB"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSB
  | -- | Represents the JSON value @"SC"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSC
  | -- | Represents the JSON value @"SE"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSE
  | -- | Represents the JSON value @"SG"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSG
  | -- | Represents the JSON value @"SH"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSH
  | -- | Represents the JSON value @"SI"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSI
  | -- | Represents the JSON value @"SJ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSJ
  | -- | Represents the JSON value @"SK"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSK
  | -- | Represents the JSON value @"SL"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSL
  | -- | Represents the JSON value @"SM"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSM
  | -- | Represents the JSON value @"SN"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSN
  | -- | Represents the JSON value @"SO"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSO
  | -- | Represents the JSON value @"SR"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSR
  | -- | Represents the JSON value @"SS"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSS
  | -- | Represents the JSON value @"ST"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumST
  | -- | Represents the JSON value @"SV"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSV
  | -- | Represents the JSON value @"SX"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSX
  | -- | Represents the JSON value @"SZ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSZ
  | -- | Represents the JSON value @"TA"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTA
  | -- | Represents the JSON value @"TC"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTC
  | -- | Represents the JSON value @"TD"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTD
  | -- | Represents the JSON value @"TF"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTF
  | -- | Represents the JSON value @"TG"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTG
  | -- | Represents the JSON value @"TH"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTH
  | -- | Represents the JSON value @"TJ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTJ
  | -- | Represents the JSON value @"TK"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTK
  | -- | Represents the JSON value @"TL"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTL
  | -- | Represents the JSON value @"TM"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTM
  | -- | Represents the JSON value @"TN"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTN
  | -- | Represents the JSON value @"TO"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTO
  | -- | Represents the JSON value @"TR"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTR
  | -- | Represents the JSON value @"TT"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTT
  | -- | Represents the JSON value @"TV"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTV
  | -- | Represents the JSON value @"TW"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTW
  | -- | Represents the JSON value @"TZ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTZ
  | -- | Represents the JSON value @"UA"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumUA
  | -- | Represents the JSON value @"UG"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumUG
  | -- | Represents the JSON value @"US"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumUS
  | -- | Represents the JSON value @"UY"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumUY
  | -- | Represents the JSON value @"UZ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumUZ
  | -- | Represents the JSON value @"VA"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVA
  | -- | Represents the JSON value @"VC"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVC
  | -- | Represents the JSON value @"VE"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVE
  | -- | Represents the JSON value @"VG"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVG
  | -- | Represents the JSON value @"VN"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVN
  | -- | Represents the JSON value @"VU"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVU
  | -- | Represents the JSON value @"WF"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumWF
  | -- | Represents the JSON value @"WS"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumWS
  | -- | Represents the JSON value @"XK"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumXK
  | -- | Represents the JSON value @"YE"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumYE
  | -- | Represents the JSON value @"YT"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumYT
  | -- | Represents the JSON value @"ZA"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumZA
  | -- | Represents the JSON value @"ZM"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumZM
  | -- | Represents the JSON value @"ZW"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumZW
  | -- | Represents the JSON value @"ZZ"@
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumZZ
  deriving (Int
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> ShowS
[PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
-> ShowS
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> String
(Int
 -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
    -> String)
-> ([PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries']
-> ShowS
show :: PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> String
$cshow :: PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> Bool
(PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
 -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
 -> Bool)
-> (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
    -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
    -> Bool)
-> Eq
     PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> Bool
== :: PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> Bool
$c== :: PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries' where
  toJSON :: PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> Value
toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAC) = Value
"AC"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAD) = Value
"AD"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAE) = Value
"AE"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAF) = Value
"AF"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAG) = Value
"AG"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAI) = Value
"AI"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAL) = Value
"AL"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAM) = Value
"AM"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAO) = Value
"AO"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAQ) = Value
"AQ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAR) = Value
"AR"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAT) = Value
"AT"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAU) = Value
"AU"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAW) = Value
"AW"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAX) = Value
"AX"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAZ) = Value
"AZ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBA) = Value
"BA"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBB) = Value
"BB"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBD) = Value
"BD"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBE) = Value
"BE"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBF) = Value
"BF"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBG) = Value
"BG"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBH) = Value
"BH"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBI) = Value
"BI"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBJ) = Value
"BJ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBL) = Value
"BL"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBM) = Value
"BM"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBN) = Value
"BN"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBO) = Value
"BO"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBQ) = Value
"BQ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBR) = Value
"BR"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBS) = Value
"BS"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBT) = Value
"BT"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBV) = Value
"BV"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBW) = Value
"BW"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBY) = Value
"BY"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBZ) = Value
"BZ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCA) = Value
"CA"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCD) = Value
"CD"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCF) = Value
"CF"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCG) = Value
"CG"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCH) = Value
"CH"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCI) = Value
"CI"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCK) = Value
"CK"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCL) = Value
"CL"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCM) = Value
"CM"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCN) = Value
"CN"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCO) = Value
"CO"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCR) = Value
"CR"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCV) = Value
"CV"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCW) = Value
"CW"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCY) = Value
"CY"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCZ) = Value
"CZ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDE) = Value
"DE"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDJ) = Value
"DJ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDK) = Value
"DK"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDM) = Value
"DM"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDO) = Value
"DO"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDZ) = Value
"DZ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumEC) = Value
"EC"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumEE) = Value
"EE"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumEG) = Value
"EG"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumEH) = Value
"EH"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumER) = Value
"ER"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumES) = Value
"ES"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumET) = Value
"ET"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumFI) = Value
"FI"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumFJ) = Value
"FJ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumFK) = Value
"FK"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumFO) = Value
"FO"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumFR) = Value
"FR"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGA) = Value
"GA"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGB) = Value
"GB"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGD) = Value
"GD"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGE) = Value
"GE"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGF) = Value
"GF"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGG) = Value
"GG"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGH) = Value
"GH"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGI) = Value
"GI"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGL) = Value
"GL"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGM) = Value
"GM"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGN) = Value
"GN"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGP) = Value
"GP"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGQ) = Value
"GQ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGR) = Value
"GR"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGS) = Value
"GS"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGT) = Value
"GT"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGU) = Value
"GU"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGW) = Value
"GW"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGY) = Value
"GY"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumHK) = Value
"HK"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumHN) = Value
"HN"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumHR) = Value
"HR"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumHT) = Value
"HT"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumHU) = Value
"HU"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumID) = Value
"ID"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIE) = Value
"IE"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIL) = Value
"IL"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIM) = Value
"IM"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIN) = Value
"IN"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIO) = Value
"IO"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIQ) = Value
"IQ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIS) = Value
"IS"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIT) = Value
"IT"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumJE) = Value
"JE"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumJM) = Value
"JM"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumJO) = Value
"JO"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumJP) = Value
"JP"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKE) = Value
"KE"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKG) = Value
"KG"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKH) = Value
"KH"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKI) = Value
"KI"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKM) = Value
"KM"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKN) = Value
"KN"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKR) = Value
"KR"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKW) = Value
"KW"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKY) = Value
"KY"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKZ) = Value
"KZ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLA) = Value
"LA"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLB) = Value
"LB"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLC) = Value
"LC"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLI) = Value
"LI"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLK) = Value
"LK"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLR) = Value
"LR"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLS) = Value
"LS"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLT) = Value
"LT"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLU) = Value
"LU"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLV) = Value
"LV"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLY) = Value
"LY"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMA) = Value
"MA"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMC) = Value
"MC"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMD) = Value
"MD"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumME) = Value
"ME"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMF) = Value
"MF"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMG) = Value
"MG"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMK) = Value
"MK"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumML) = Value
"ML"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMM) = Value
"MM"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMN) = Value
"MN"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMO) = Value
"MO"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMQ) = Value
"MQ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMR) = Value
"MR"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMS) = Value
"MS"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMT) = Value
"MT"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMU) = Value
"MU"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMV) = Value
"MV"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMW) = Value
"MW"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMX) = Value
"MX"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMY) = Value
"MY"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMZ) = Value
"MZ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNA) = Value
"NA"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNC) = Value
"NC"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNE) = Value
"NE"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNG) = Value
"NG"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNI) = Value
"NI"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNL) = Value
"NL"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNO) = Value
"NO"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNP) = Value
"NP"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNR) = Value
"NR"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNU) = Value
"NU"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNZ) = Value
"NZ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumOM) = Value
"OM"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPA) = Value
"PA"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPE) = Value
"PE"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPF) = Value
"PF"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPG) = Value
"PG"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPH) = Value
"PH"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPK) = Value
"PK"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPL) = Value
"PL"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPM) = Value
"PM"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPN) = Value
"PN"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPR) = Value
"PR"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPS) = Value
"PS"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPT) = Value
"PT"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPY) = Value
"PY"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumQA) = Value
"QA"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumRE) = Value
"RE"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumRO) = Value
"RO"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumRS) = Value
"RS"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumRU) = Value
"RU"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumRW) = Value
"RW"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSA) = Value
"SA"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSB) = Value
"SB"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSC) = Value
"SC"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSE) = Value
"SE"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSG) = Value
"SG"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSH) = Value
"SH"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSI) = Value
"SI"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSJ) = Value
"SJ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSK) = Value
"SK"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSL) = Value
"SL"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSM) = Value
"SM"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSN) = Value
"SN"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSO) = Value
"SO"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSR) = Value
"SR"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSS) = Value
"SS"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumST) = Value
"ST"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSV) = Value
"SV"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSX) = Value
"SX"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSZ) = Value
"SZ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTA) = Value
"TA"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTC) = Value
"TC"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTD) = Value
"TD"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTF) = Value
"TF"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTG) = Value
"TG"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTH) = Value
"TH"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTJ) = Value
"TJ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTK) = Value
"TK"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTL) = Value
"TL"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTM) = Value
"TM"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTN) = Value
"TN"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTO) = Value
"TO"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTR) = Value
"TR"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTT) = Value
"TT"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTV) = Value
"TV"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTW) = Value
"TW"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTZ) = Value
"TZ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumUA) = Value
"UA"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumUG) = Value
"UG"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumUS) = Value
"US"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumUY) = Value
"UY"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumUZ) = Value
"UZ"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVA) = Value
"VA"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVC) = Value
"VC"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVE) = Value
"VE"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVG) = Value
"VG"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVN) = Value
"VN"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVU) = Value
"VU"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumWF) = Value
"WF"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumWS) = Value
"WS"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumXK) = Value
"XK"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumYE) = Value
"YE"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumYT) = Value
"YT"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumZA) = Value
"ZA"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumZM) = Value
"ZM"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumZW) = Value
"ZW"
  toJSON (PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumZZ) = Value
"ZZ"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
-> Parser
     PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AC" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAC
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AD" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAD
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AE" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAE
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AF" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAF
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AG" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAG
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AI" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAI
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AL" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAL
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AM" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAM
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AO" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAO
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AQ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAQ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AR" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAR
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AT" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAT
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AU" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAU
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AW" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAW
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AX" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAX
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"AZ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumAZ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BA" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBA
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BB" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBB
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BD" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBD
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BE" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBE
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BF" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBF
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BG" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBG
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BH" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBH
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BI" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBI
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BJ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBJ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BL" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBL
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BM" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBM
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BN" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBN
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BO" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBO
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BQ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBQ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BR" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBR
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BS" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBS
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BT" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBT
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BV" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBV
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BW" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBW
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BY" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBY
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"BZ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumBZ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CA" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCA
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CD" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCD
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CF" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCF
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CG" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCG
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CH" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCH
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CI" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCI
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CK" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCK
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CL" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCL
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CM" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCM
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CN" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCN
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CO" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCO
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CR" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCR
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CV" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCV
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CW" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCW
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CY" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCY
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"CZ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumCZ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"DE" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDE
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"DJ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDJ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"DK" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDK
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"DM" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDM
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"DO" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDO
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"DZ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumDZ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"EC" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumEC
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"EE" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumEE
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"EG" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumEG
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"EH" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumEH
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ER" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumER
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ES" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumES
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ET" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumET
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"FI" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumFI
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"FJ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumFJ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"FK" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumFK
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"FO" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumFO
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"FR" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumFR
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GA" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGA
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GB" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGB
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GD" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGD
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GE" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGE
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GF" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGF
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GG" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGG
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GH" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGH
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GI" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGI
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GL" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGL
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GM" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGM
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GN" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGN
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GP" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGP
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GQ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGQ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GR" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGR
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GS" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGS
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GT" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGT
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GU" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGU
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GW" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGW
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"GY" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumGY
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"HK" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumHK
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"HN" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumHN
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"HR" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumHR
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"HT" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumHT
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"HU" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumHU
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ID" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumID
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"IE" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIE
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"IL" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIL
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"IM" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIM
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"IN" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIN
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"IO" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIO
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"IQ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIQ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"IS" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIS
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"IT" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumIT
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"JE" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumJE
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"JM" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumJM
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"JO" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumJO
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"JP" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumJP
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"KE" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKE
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"KG" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKG
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"KH" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKH
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"KI" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKI
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"KM" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKM
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"KN" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKN
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"KR" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKR
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"KW" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKW
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"KY" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKY
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"KZ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumKZ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"LA" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLA
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"LB" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLB
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"LC" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLC
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"LI" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLI
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"LK" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLK
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"LR" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLR
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"LS" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLS
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"LT" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLT
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"LU" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLU
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"LV" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLV
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"LY" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumLY
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MA" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMA
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MC" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMC
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MD" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMD
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ME" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumME
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MF" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMF
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MG" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMG
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MK" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMK
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ML" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumML
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MM" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMM
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MN" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMN
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MO" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMO
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MQ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMQ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MR" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMR
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MS" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMS
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MT" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMT
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MU" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMU
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MV" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMV
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MW" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMW
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MX" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMX
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MY" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMY
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"MZ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumMZ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"NA" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNA
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"NC" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNC
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"NE" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNE
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"NG" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNG
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"NI" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNI
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"NL" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNL
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"NO" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNO
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"NP" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNP
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"NR" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNR
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"NU" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNU
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"NZ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumNZ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"OM" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumOM
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"PA" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPA
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"PE" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPE
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"PF" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPF
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"PG" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPG
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"PH" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPH
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"PK" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPK
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"PL" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPL
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"PM" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPM
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"PN" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPN
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"PR" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPR
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"PS" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPS
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"PT" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPT
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"PY" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumPY
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"QA" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumQA
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"RE" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumRE
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"RO" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumRO
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"RS" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumRS
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"RU" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumRU
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"RW" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumRW
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SA" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSA
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SB" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSB
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SC" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSC
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SE" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSE
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SG" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSG
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SH" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSH
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SI" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSI
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SJ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSJ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SK" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSK
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SL" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSL
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SM" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSM
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SN" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSN
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SO" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSO
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SR" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSR
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SS" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSS
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ST" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumST
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SV" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSV
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SX" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSX
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"SZ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumSZ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TA" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTA
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TC" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTC
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TD" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTD
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TF" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTF
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TG" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTG
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TH" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTH
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TJ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTJ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TK" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTK
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TL" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTL
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TM" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTM
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TN" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTN
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TO" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTO
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TR" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTR
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TT" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTT
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TV" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTV
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TW" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTW
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"TZ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumTZ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"UA" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumUA
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"UG" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumUG
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"US" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumUS
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"UY" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumUY
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"UZ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumUZ
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"VA" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVA
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"VC" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVC
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"VE" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVE
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"VG" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVG
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"VN" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVN
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"VU" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumVU
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"WF" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumWF
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"WS" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumWS
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"XK" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumXK
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"YE" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumYE
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"YT" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumYT
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ZA" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumZA
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ZM" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumZM
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ZW" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumZW
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ZZ" -> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'EnumZZ
            | Bool
GHC.Base.otherwise -> Value
-> PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'
PostCheckoutSessionsRequestBodyShippingAddressCollection'AllowedCountries'Other Value
val
      )

-- | Defines the enum schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.submit_type@ in the specification.
--
-- Describes the type of transaction being performed by Checkout in order to customize
-- relevant text on the page, such as the submit button. \`submit_type\` can only be
-- specified on Checkout Sessions in \`payment\` mode, but not Checkout Sessions
-- in \`subscription\` or \`setup\` mode.
data PostCheckoutSessionsRequestBodySubmitType'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCheckoutSessionsRequestBodySubmitType'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCheckoutSessionsRequestBodySubmitType'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"auto"@
    PostCheckoutSessionsRequestBodySubmitType'EnumAuto
  | -- | Represents the JSON value @"book"@
    PostCheckoutSessionsRequestBodySubmitType'EnumBook
  | -- | Represents the JSON value @"donate"@
    PostCheckoutSessionsRequestBodySubmitType'EnumDonate
  | -- | Represents the JSON value @"pay"@
    PostCheckoutSessionsRequestBodySubmitType'EnumPay
  deriving (Int -> PostCheckoutSessionsRequestBodySubmitType' -> ShowS
[PostCheckoutSessionsRequestBodySubmitType'] -> ShowS
PostCheckoutSessionsRequestBodySubmitType' -> String
(Int -> PostCheckoutSessionsRequestBodySubmitType' -> ShowS)
-> (PostCheckoutSessionsRequestBodySubmitType' -> String)
-> ([PostCheckoutSessionsRequestBodySubmitType'] -> ShowS)
-> Show PostCheckoutSessionsRequestBodySubmitType'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodySubmitType'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodySubmitType'] -> ShowS
show :: PostCheckoutSessionsRequestBodySubmitType' -> String
$cshow :: PostCheckoutSessionsRequestBodySubmitType' -> String
showsPrec :: Int -> PostCheckoutSessionsRequestBodySubmitType' -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsRequestBodySubmitType' -> ShowS
GHC.Show.Show, PostCheckoutSessionsRequestBodySubmitType'
-> PostCheckoutSessionsRequestBodySubmitType' -> Bool
(PostCheckoutSessionsRequestBodySubmitType'
 -> PostCheckoutSessionsRequestBodySubmitType' -> Bool)
-> (PostCheckoutSessionsRequestBodySubmitType'
    -> PostCheckoutSessionsRequestBodySubmitType' -> Bool)
-> Eq PostCheckoutSessionsRequestBodySubmitType'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodySubmitType'
-> PostCheckoutSessionsRequestBodySubmitType' -> Bool
$c/= :: PostCheckoutSessionsRequestBodySubmitType'
-> PostCheckoutSessionsRequestBodySubmitType' -> Bool
== :: PostCheckoutSessionsRequestBodySubmitType'
-> PostCheckoutSessionsRequestBodySubmitType' -> Bool
$c== :: PostCheckoutSessionsRequestBodySubmitType'
-> PostCheckoutSessionsRequestBodySubmitType' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodySubmitType' where
  toJSON :: PostCheckoutSessionsRequestBodySubmitType' -> Value
toJSON (PostCheckoutSessionsRequestBodySubmitType'Other Value
val) = Value
val
  toJSON (PostCheckoutSessionsRequestBodySubmitType'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCheckoutSessionsRequestBodySubmitType'
PostCheckoutSessionsRequestBodySubmitType'EnumAuto) = Value
"auto"
  toJSON (PostCheckoutSessionsRequestBodySubmitType'
PostCheckoutSessionsRequestBodySubmitType'EnumBook) = Value
"book"
  toJSON (PostCheckoutSessionsRequestBodySubmitType'
PostCheckoutSessionsRequestBodySubmitType'EnumDonate) = Value
"donate"
  toJSON (PostCheckoutSessionsRequestBodySubmitType'
PostCheckoutSessionsRequestBodySubmitType'EnumPay) = Value
"pay"

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodySubmitType' where
  parseJSON :: Value -> Parser PostCheckoutSessionsRequestBodySubmitType'
parseJSON Value
val =
    PostCheckoutSessionsRequestBodySubmitType'
-> Parser PostCheckoutSessionsRequestBodySubmitType'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"auto" -> PostCheckoutSessionsRequestBodySubmitType'
PostCheckoutSessionsRequestBodySubmitType'EnumAuto
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"book" -> PostCheckoutSessionsRequestBodySubmitType'
PostCheckoutSessionsRequestBodySubmitType'EnumBook
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"donate" -> PostCheckoutSessionsRequestBodySubmitType'
PostCheckoutSessionsRequestBodySubmitType'EnumDonate
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"pay" -> PostCheckoutSessionsRequestBodySubmitType'
PostCheckoutSessionsRequestBodySubmitType'EnumPay
            | Bool
GHC.Base.otherwise -> Value -> PostCheckoutSessionsRequestBodySubmitType'
PostCheckoutSessionsRequestBodySubmitType'Other Value
val
      )

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.subscription_data@ in the specification.
--
-- A subset of parameters to be passed to subscription creation for Checkout Sessions in \`subscription\` mode.
data PostCheckoutSessionsRequestBodySubscriptionData' = PostCheckoutSessionsRequestBodySubscriptionData'
  { -- | application_fee_percent
    PostCheckoutSessionsRequestBodySubscriptionData' -> Maybe Double
postCheckoutSessionsRequestBodySubscriptionData'ApplicationFeePercent :: (GHC.Maybe.Maybe GHC.Types.Double),
    -- | default_tax_rates
    PostCheckoutSessionsRequestBodySubscriptionData' -> Maybe [Text]
postCheckoutSessionsRequestBodySubscriptionData'DefaultTaxRates :: (GHC.Maybe.Maybe ([Data.Text.Internal.Text])),
    -- | items
    PostCheckoutSessionsRequestBodySubscriptionData'
-> Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
postCheckoutSessionsRequestBodySubscriptionData'Items :: (GHC.Maybe.Maybe ([PostCheckoutSessionsRequestBodySubscriptionData'Items'])),
    -- | metadata
    PostCheckoutSessionsRequestBodySubscriptionData' -> Maybe Object
postCheckoutSessionsRequestBodySubscriptionData'Metadata :: (GHC.Maybe.Maybe Data.Aeson.Types.Internal.Object),
    -- | transfer_data
    PostCheckoutSessionsRequestBodySubscriptionData'
-> Maybe
     PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
postCheckoutSessionsRequestBodySubscriptionData'TransferData :: (GHC.Maybe.Maybe PostCheckoutSessionsRequestBodySubscriptionData'TransferData'),
    -- | trial_end
    PostCheckoutSessionsRequestBodySubscriptionData' -> Maybe Int
postCheckoutSessionsRequestBodySubscriptionData'TrialEnd :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | trial_period_days
    PostCheckoutSessionsRequestBodySubscriptionData' -> Maybe Int
postCheckoutSessionsRequestBodySubscriptionData'TrialPeriodDays :: (GHC.Maybe.Maybe GHC.Types.Int)
  }
  deriving
    ( Int -> PostCheckoutSessionsRequestBodySubscriptionData' -> ShowS
[PostCheckoutSessionsRequestBodySubscriptionData'] -> ShowS
PostCheckoutSessionsRequestBodySubscriptionData' -> String
(Int -> PostCheckoutSessionsRequestBodySubscriptionData' -> ShowS)
-> (PostCheckoutSessionsRequestBodySubscriptionData' -> String)
-> ([PostCheckoutSessionsRequestBodySubscriptionData'] -> ShowS)
-> Show PostCheckoutSessionsRequestBodySubscriptionData'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodySubscriptionData'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodySubscriptionData'] -> ShowS
show :: PostCheckoutSessionsRequestBodySubscriptionData' -> String
$cshow :: PostCheckoutSessionsRequestBodySubscriptionData' -> String
showsPrec :: Int -> PostCheckoutSessionsRequestBodySubscriptionData' -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsRequestBodySubscriptionData' -> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodySubscriptionData'
-> PostCheckoutSessionsRequestBodySubscriptionData' -> Bool
(PostCheckoutSessionsRequestBodySubscriptionData'
 -> PostCheckoutSessionsRequestBodySubscriptionData' -> Bool)
-> (PostCheckoutSessionsRequestBodySubscriptionData'
    -> PostCheckoutSessionsRequestBodySubscriptionData' -> Bool)
-> Eq PostCheckoutSessionsRequestBodySubscriptionData'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodySubscriptionData'
-> PostCheckoutSessionsRequestBodySubscriptionData' -> Bool
$c/= :: PostCheckoutSessionsRequestBodySubscriptionData'
-> PostCheckoutSessionsRequestBodySubscriptionData' -> Bool
== :: PostCheckoutSessionsRequestBodySubscriptionData'
-> PostCheckoutSessionsRequestBodySubscriptionData' -> Bool
$c== :: PostCheckoutSessionsRequestBodySubscriptionData'
-> PostCheckoutSessionsRequestBodySubscriptionData' -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodySubscriptionData' where
  toJSON :: PostCheckoutSessionsRequestBodySubscriptionData' -> Value
toJSON PostCheckoutSessionsRequestBodySubscriptionData'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"application_fee_percent" Text -> Maybe Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData' -> Maybe Double
postCheckoutSessionsRequestBodySubscriptionData'ApplicationFeePercent PostCheckoutSessionsRequestBodySubscriptionData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"default_tax_rates" Text -> Maybe [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData' -> Maybe [Text]
postCheckoutSessionsRequestBodySubscriptionData'DefaultTaxRates PostCheckoutSessionsRequestBodySubscriptionData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"items" Text
-> Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData'
-> Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
postCheckoutSessionsRequestBodySubscriptionData'Items PostCheckoutSessionsRequestBodySubscriptionData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text -> Maybe Object -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData' -> Maybe Object
postCheckoutSessionsRequestBodySubscriptionData'Metadata PostCheckoutSessionsRequestBodySubscriptionData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"transfer_data" Text
-> Maybe
     PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData'
-> Maybe
     PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
postCheckoutSessionsRequestBodySubscriptionData'TransferData PostCheckoutSessionsRequestBodySubscriptionData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"trial_end" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData' -> Maybe Int
postCheckoutSessionsRequestBodySubscriptionData'TrialEnd PostCheckoutSessionsRequestBodySubscriptionData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"trial_period_days" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData' -> Maybe Int
postCheckoutSessionsRequestBodySubscriptionData'TrialPeriodDays PostCheckoutSessionsRequestBodySubscriptionData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodySubscriptionData' -> Encoding
toEncoding PostCheckoutSessionsRequestBodySubscriptionData'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"application_fee_percent" Text -> Maybe Double -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData' -> Maybe Double
postCheckoutSessionsRequestBodySubscriptionData'ApplicationFeePercent PostCheckoutSessionsRequestBodySubscriptionData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"default_tax_rates" Text -> Maybe [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData' -> Maybe [Text]
postCheckoutSessionsRequestBodySubscriptionData'DefaultTaxRates PostCheckoutSessionsRequestBodySubscriptionData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"items" Text
-> Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData'
-> Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
postCheckoutSessionsRequestBodySubscriptionData'Items PostCheckoutSessionsRequestBodySubscriptionData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"metadata" Text -> Maybe Object -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData' -> Maybe Object
postCheckoutSessionsRequestBodySubscriptionData'Metadata PostCheckoutSessionsRequestBodySubscriptionData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"transfer_data" Text
-> Maybe
     PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData'
-> Maybe
     PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
postCheckoutSessionsRequestBodySubscriptionData'TransferData PostCheckoutSessionsRequestBodySubscriptionData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"trial_end" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData' -> Maybe Int
postCheckoutSessionsRequestBodySubscriptionData'TrialEnd PostCheckoutSessionsRequestBodySubscriptionData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"trial_period_days" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData' -> Maybe Int
postCheckoutSessionsRequestBodySubscriptionData'TrialPeriodDays PostCheckoutSessionsRequestBodySubscriptionData'
obj)))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodySubscriptionData' where
  parseJSON :: Value -> Parser PostCheckoutSessionsRequestBodySubscriptionData'
parseJSON = String
-> (Object
    -> Parser PostCheckoutSessionsRequestBodySubscriptionData')
-> Value
-> Parser PostCheckoutSessionsRequestBodySubscriptionData'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodySubscriptionData'" (\Object
obj -> (((((((Maybe Double
 -> Maybe [Text]
 -> Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
 -> Maybe Object
 -> Maybe
      PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
 -> Maybe Int
 -> Maybe Int
 -> PostCheckoutSessionsRequestBodySubscriptionData')
-> Parser
     (Maybe Double
      -> Maybe [Text]
      -> Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
      -> Maybe Object
      -> Maybe
           PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
      -> Maybe Int
      -> Maybe Int
      -> PostCheckoutSessionsRequestBodySubscriptionData')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Double
-> Maybe [Text]
-> Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
-> Maybe Object
-> Maybe
     PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Maybe Int
-> Maybe Int
-> PostCheckoutSessionsRequestBodySubscriptionData'
PostCheckoutSessionsRequestBodySubscriptionData' Parser
  (Maybe Double
   -> Maybe [Text]
   -> Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
   -> Maybe Object
   -> Maybe
        PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
   -> Maybe Int
   -> Maybe Int
   -> PostCheckoutSessionsRequestBodySubscriptionData')
-> Parser (Maybe Double)
-> Parser
     (Maybe [Text]
      -> Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
      -> Maybe Object
      -> Maybe
           PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
      -> Maybe Int
      -> Maybe Int
      -> PostCheckoutSessionsRequestBodySubscriptionData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Double)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"application_fee_percent")) Parser
  (Maybe [Text]
   -> Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
   -> Maybe Object
   -> Maybe
        PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
   -> Maybe Int
   -> Maybe Int
   -> PostCheckoutSessionsRequestBodySubscriptionData')
-> Parser (Maybe [Text])
-> Parser
     (Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
      -> Maybe Object
      -> Maybe
           PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
      -> Maybe Int
      -> Maybe Int
      -> PostCheckoutSessionsRequestBodySubscriptionData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"default_tax_rates")) Parser
  (Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
   -> Maybe Object
   -> Maybe
        PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
   -> Maybe Int
   -> Maybe Int
   -> PostCheckoutSessionsRequestBodySubscriptionData')
-> Parser
     (Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items'])
-> Parser
     (Maybe Object
      -> Maybe
           PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
      -> Maybe Int
      -> Maybe Int
      -> PostCheckoutSessionsRequestBodySubscriptionData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items'])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"items")) Parser
  (Maybe Object
   -> Maybe
        PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
   -> Maybe Int
   -> Maybe Int
   -> PostCheckoutSessionsRequestBodySubscriptionData')
-> Parser (Maybe Object)
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
      -> Maybe Int
      -> Maybe Int
      -> PostCheckoutSessionsRequestBodySubscriptionData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"metadata")) Parser
  (Maybe
     PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
   -> Maybe Int
   -> Maybe Int
   -> PostCheckoutSessionsRequestBodySubscriptionData')
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodySubscriptionData'TransferData')
-> Parser
     (Maybe Int
      -> Maybe Int -> PostCheckoutSessionsRequestBodySubscriptionData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCheckoutSessionsRequestBodySubscriptionData'TransferData')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"transfer_data")) Parser
  (Maybe Int
   -> Maybe Int -> PostCheckoutSessionsRequestBodySubscriptionData')
-> Parser (Maybe Int)
-> Parser
     (Maybe Int -> PostCheckoutSessionsRequestBodySubscriptionData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"trial_end")) Parser
  (Maybe Int -> PostCheckoutSessionsRequestBodySubscriptionData')
-> Parser (Maybe Int)
-> Parser PostCheckoutSessionsRequestBodySubscriptionData'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"trial_period_days"))

-- | Create a new 'PostCheckoutSessionsRequestBodySubscriptionData'' with all required fields.
mkPostCheckoutSessionsRequestBodySubscriptionData' :: PostCheckoutSessionsRequestBodySubscriptionData'
mkPostCheckoutSessionsRequestBodySubscriptionData' :: PostCheckoutSessionsRequestBodySubscriptionData'
mkPostCheckoutSessionsRequestBodySubscriptionData' =
  PostCheckoutSessionsRequestBodySubscriptionData' :: Maybe Double
-> Maybe [Text]
-> Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
-> Maybe Object
-> Maybe
     PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Maybe Int
-> Maybe Int
-> PostCheckoutSessionsRequestBodySubscriptionData'
PostCheckoutSessionsRequestBodySubscriptionData'
    { postCheckoutSessionsRequestBodySubscriptionData'ApplicationFeePercent :: Maybe Double
postCheckoutSessionsRequestBodySubscriptionData'ApplicationFeePercent = Maybe Double
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodySubscriptionData'DefaultTaxRates :: Maybe [Text]
postCheckoutSessionsRequestBodySubscriptionData'DefaultTaxRates = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodySubscriptionData'Items :: Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
postCheckoutSessionsRequestBodySubscriptionData'Items = Maybe [PostCheckoutSessionsRequestBodySubscriptionData'Items']
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodySubscriptionData'Metadata :: Maybe Object
postCheckoutSessionsRequestBodySubscriptionData'Metadata = Maybe Object
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodySubscriptionData'TransferData :: Maybe PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
postCheckoutSessionsRequestBodySubscriptionData'TransferData = Maybe PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodySubscriptionData'TrialEnd :: Maybe Int
postCheckoutSessionsRequestBodySubscriptionData'TrialEnd = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodySubscriptionData'TrialPeriodDays :: Maybe Int
postCheckoutSessionsRequestBodySubscriptionData'TrialPeriodDays = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.subscription_data.properties.items.items@ in the specification.
data PostCheckoutSessionsRequestBodySubscriptionData'Items' = PostCheckoutSessionsRequestBodySubscriptionData'Items'
  { -- | plan
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCheckoutSessionsRequestBodySubscriptionData'Items' -> Text
postCheckoutSessionsRequestBodySubscriptionData'Items'Plan :: Data.Text.Internal.Text,
    -- | quantity
    PostCheckoutSessionsRequestBodySubscriptionData'Items' -> Maybe Int
postCheckoutSessionsRequestBodySubscriptionData'Items'Quantity :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | tax_rates
    PostCheckoutSessionsRequestBodySubscriptionData'Items'
-> Maybe [Text]
postCheckoutSessionsRequestBodySubscriptionData'Items'TaxRates :: (GHC.Maybe.Maybe ([Data.Text.Internal.Text]))
  }
  deriving
    ( Int
-> PostCheckoutSessionsRequestBodySubscriptionData'Items' -> ShowS
[PostCheckoutSessionsRequestBodySubscriptionData'Items'] -> ShowS
PostCheckoutSessionsRequestBodySubscriptionData'Items' -> String
(Int
 -> PostCheckoutSessionsRequestBodySubscriptionData'Items' -> ShowS)
-> (PostCheckoutSessionsRequestBodySubscriptionData'Items'
    -> String)
-> ([PostCheckoutSessionsRequestBodySubscriptionData'Items']
    -> ShowS)
-> Show PostCheckoutSessionsRequestBodySubscriptionData'Items'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodySubscriptionData'Items'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodySubscriptionData'Items'] -> ShowS
show :: PostCheckoutSessionsRequestBodySubscriptionData'Items' -> String
$cshow :: PostCheckoutSessionsRequestBodySubscriptionData'Items' -> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodySubscriptionData'Items' -> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodySubscriptionData'Items' -> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodySubscriptionData'Items'
-> PostCheckoutSessionsRequestBodySubscriptionData'Items' -> Bool
(PostCheckoutSessionsRequestBodySubscriptionData'Items'
 -> PostCheckoutSessionsRequestBodySubscriptionData'Items' -> Bool)
-> (PostCheckoutSessionsRequestBodySubscriptionData'Items'
    -> PostCheckoutSessionsRequestBodySubscriptionData'Items' -> Bool)
-> Eq PostCheckoutSessionsRequestBodySubscriptionData'Items'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodySubscriptionData'Items'
-> PostCheckoutSessionsRequestBodySubscriptionData'Items' -> Bool
$c/= :: PostCheckoutSessionsRequestBodySubscriptionData'Items'
-> PostCheckoutSessionsRequestBodySubscriptionData'Items' -> Bool
== :: PostCheckoutSessionsRequestBodySubscriptionData'Items'
-> PostCheckoutSessionsRequestBodySubscriptionData'Items' -> Bool
$c== :: PostCheckoutSessionsRequestBodySubscriptionData'Items'
-> PostCheckoutSessionsRequestBodySubscriptionData'Items' -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodySubscriptionData'Items' where
  toJSON :: PostCheckoutSessionsRequestBodySubscriptionData'Items' -> Value
toJSON PostCheckoutSessionsRequestBodySubscriptionData'Items'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"plan" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData'Items' -> Text
postCheckoutSessionsRequestBodySubscriptionData'Items'Plan PostCheckoutSessionsRequestBodySubscriptionData'Items'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"quantity" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData'Items' -> Maybe Int
postCheckoutSessionsRequestBodySubscriptionData'Items'Quantity PostCheckoutSessionsRequestBodySubscriptionData'Items'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"tax_rates" Text -> Maybe [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData'Items'
-> Maybe [Text]
postCheckoutSessionsRequestBodySubscriptionData'Items'TaxRates PostCheckoutSessionsRequestBodySubscriptionData'Items'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodySubscriptionData'Items' -> Encoding
toEncoding PostCheckoutSessionsRequestBodySubscriptionData'Items'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"plan" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData'Items' -> Text
postCheckoutSessionsRequestBodySubscriptionData'Items'Plan PostCheckoutSessionsRequestBodySubscriptionData'Items'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"quantity" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData'Items' -> Maybe Int
postCheckoutSessionsRequestBodySubscriptionData'Items'Quantity PostCheckoutSessionsRequestBodySubscriptionData'Items'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"tax_rates" Text -> Maybe [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData'Items'
-> Maybe [Text]
postCheckoutSessionsRequestBodySubscriptionData'Items'TaxRates PostCheckoutSessionsRequestBodySubscriptionData'Items'
obj)))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodySubscriptionData'Items' where
  parseJSON :: Value
-> Parser PostCheckoutSessionsRequestBodySubscriptionData'Items'
parseJSON = String
-> (Object
    -> Parser PostCheckoutSessionsRequestBodySubscriptionData'Items')
-> Value
-> Parser PostCheckoutSessionsRequestBodySubscriptionData'Items'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodySubscriptionData'Items'" (\Object
obj -> (((Text
 -> Maybe Int
 -> Maybe [Text]
 -> PostCheckoutSessionsRequestBodySubscriptionData'Items')
-> Parser
     (Text
      -> Maybe Int
      -> Maybe [Text]
      -> PostCheckoutSessionsRequestBodySubscriptionData'Items')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Text
-> Maybe Int
-> Maybe [Text]
-> PostCheckoutSessionsRequestBodySubscriptionData'Items'
PostCheckoutSessionsRequestBodySubscriptionData'Items' Parser
  (Text
   -> Maybe Int
   -> Maybe [Text]
   -> PostCheckoutSessionsRequestBodySubscriptionData'Items')
-> Parser Text
-> Parser
     (Maybe Int
      -> Maybe [Text]
      -> PostCheckoutSessionsRequestBodySubscriptionData'Items')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"plan")) Parser
  (Maybe Int
   -> Maybe [Text]
   -> PostCheckoutSessionsRequestBodySubscriptionData'Items')
-> Parser (Maybe Int)
-> Parser
     (Maybe [Text]
      -> PostCheckoutSessionsRequestBodySubscriptionData'Items')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"quantity")) Parser
  (Maybe [Text]
   -> PostCheckoutSessionsRequestBodySubscriptionData'Items')
-> Parser (Maybe [Text])
-> Parser PostCheckoutSessionsRequestBodySubscriptionData'Items'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"tax_rates"))

-- | Create a new 'PostCheckoutSessionsRequestBodySubscriptionData'Items'' with all required fields.
mkPostCheckoutSessionsRequestBodySubscriptionData'Items' ::
  -- | 'postCheckoutSessionsRequestBodySubscriptionData'Items'Plan'
  Data.Text.Internal.Text ->
  PostCheckoutSessionsRequestBodySubscriptionData'Items'
mkPostCheckoutSessionsRequestBodySubscriptionData'Items' :: Text -> PostCheckoutSessionsRequestBodySubscriptionData'Items'
mkPostCheckoutSessionsRequestBodySubscriptionData'Items' Text
postCheckoutSessionsRequestBodySubscriptionData'Items'Plan =
  PostCheckoutSessionsRequestBodySubscriptionData'Items' :: Text
-> Maybe Int
-> Maybe [Text]
-> PostCheckoutSessionsRequestBodySubscriptionData'Items'
PostCheckoutSessionsRequestBodySubscriptionData'Items'
    { postCheckoutSessionsRequestBodySubscriptionData'Items'Plan :: Text
postCheckoutSessionsRequestBodySubscriptionData'Items'Plan = Text
postCheckoutSessionsRequestBodySubscriptionData'Items'Plan,
      postCheckoutSessionsRequestBodySubscriptionData'Items'Quantity :: Maybe Int
postCheckoutSessionsRequestBodySubscriptionData'Items'Quantity = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodySubscriptionData'Items'TaxRates :: Maybe [Text]
postCheckoutSessionsRequestBodySubscriptionData'Items'TaxRates = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.subscription_data.properties.transfer_data@ in the specification.
data PostCheckoutSessionsRequestBodySubscriptionData'TransferData' = PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
  { -- | amount_percent
    PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Maybe Double
postCheckoutSessionsRequestBodySubscriptionData'TransferData'AmountPercent :: (GHC.Maybe.Maybe GHC.Types.Double),
    -- | destination
    PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Text
postCheckoutSessionsRequestBodySubscriptionData'TransferData'Destination :: Data.Text.Internal.Text
  }
  deriving
    ( Int
-> PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> ShowS
[PostCheckoutSessionsRequestBodySubscriptionData'TransferData']
-> ShowS
PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> String
(Int
 -> PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
 -> ShowS)
-> (PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
    -> String)
-> ([PostCheckoutSessionsRequestBodySubscriptionData'TransferData']
    -> ShowS)
-> Show
     PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodySubscriptionData'TransferData']
-> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodySubscriptionData'TransferData']
-> ShowS
show :: PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> String
$cshow :: PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> String
showsPrec :: Int
-> PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> ShowS
$cshowsPrec :: Int
-> PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Bool
(PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
 -> PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
 -> Bool)
-> (PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
    -> PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
    -> Bool)
-> Eq PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Bool
$c/= :: PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Bool
== :: PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Bool
$c== :: PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodySubscriptionData'TransferData' where
  toJSON :: PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Value
toJSON PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"amount_percent" Text -> Maybe Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Maybe Double
postCheckoutSessionsRequestBodySubscriptionData'TransferData'AmountPercent PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"destination" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Text
postCheckoutSessionsRequestBodySubscriptionData'TransferData'Destination PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Encoding
toEncoding PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"amount_percent" Text -> Maybe Double -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Maybe Double
postCheckoutSessionsRequestBodySubscriptionData'TransferData'AmountPercent PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"destination" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
-> Text
postCheckoutSessionsRequestBodySubscriptionData'TransferData'Destination PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
obj))

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodySubscriptionData'TransferData' where
  parseJSON :: Value
-> Parser
     PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
parseJSON = String
-> (Object
    -> Parser
         PostCheckoutSessionsRequestBodySubscriptionData'TransferData')
-> Value
-> Parser
     PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodySubscriptionData'TransferData'" (\Object
obj -> ((Maybe Double
 -> Text
 -> PostCheckoutSessionsRequestBodySubscriptionData'TransferData')
-> Parser
     (Maybe Double
      -> Text
      -> PostCheckoutSessionsRequestBodySubscriptionData'TransferData')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Double
-> Text
-> PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
PostCheckoutSessionsRequestBodySubscriptionData'TransferData' Parser
  (Maybe Double
   -> Text
   -> PostCheckoutSessionsRequestBodySubscriptionData'TransferData')
-> Parser (Maybe Double)
-> Parser
     (Text
      -> PostCheckoutSessionsRequestBodySubscriptionData'TransferData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Double)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"amount_percent")) Parser
  (Text
   -> PostCheckoutSessionsRequestBodySubscriptionData'TransferData')
-> Parser Text
-> Parser
     PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"destination"))

-- | Create a new 'PostCheckoutSessionsRequestBodySubscriptionData'TransferData'' with all required fields.
mkPostCheckoutSessionsRequestBodySubscriptionData'TransferData' ::
  -- | 'postCheckoutSessionsRequestBodySubscriptionData'TransferData'Destination'
  Data.Text.Internal.Text ->
  PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
mkPostCheckoutSessionsRequestBodySubscriptionData'TransferData' :: Text
-> PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
mkPostCheckoutSessionsRequestBodySubscriptionData'TransferData' Text
postCheckoutSessionsRequestBodySubscriptionData'TransferData'Destination =
  PostCheckoutSessionsRequestBodySubscriptionData'TransferData' :: Maybe Double
-> Text
-> PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
PostCheckoutSessionsRequestBodySubscriptionData'TransferData'
    { postCheckoutSessionsRequestBodySubscriptionData'TransferData'AmountPercent :: Maybe Double
postCheckoutSessionsRequestBodySubscriptionData'TransferData'AmountPercent = Maybe Double
forall a. Maybe a
GHC.Maybe.Nothing,
      postCheckoutSessionsRequestBodySubscriptionData'TransferData'Destination :: Text
postCheckoutSessionsRequestBodySubscriptionData'TransferData'Destination = Text
postCheckoutSessionsRequestBodySubscriptionData'TransferData'Destination
    }

-- | Defines the object schema located at @paths.\/v1\/checkout\/sessions.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.tax_id_collection@ in the specification.
--
-- Controls tax ID collection settings for the session.
data PostCheckoutSessionsRequestBodyTaxIdCollection' = PostCheckoutSessionsRequestBodyTaxIdCollection'
  { -- | enabled
    PostCheckoutSessionsRequestBodyTaxIdCollection' -> Bool
postCheckoutSessionsRequestBodyTaxIdCollection'Enabled :: GHC.Types.Bool
  }
  deriving
    ( Int -> PostCheckoutSessionsRequestBodyTaxIdCollection' -> ShowS
[PostCheckoutSessionsRequestBodyTaxIdCollection'] -> ShowS
PostCheckoutSessionsRequestBodyTaxIdCollection' -> String
(Int -> PostCheckoutSessionsRequestBodyTaxIdCollection' -> ShowS)
-> (PostCheckoutSessionsRequestBodyTaxIdCollection' -> String)
-> ([PostCheckoutSessionsRequestBodyTaxIdCollection'] -> ShowS)
-> Show PostCheckoutSessionsRequestBodyTaxIdCollection'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsRequestBodyTaxIdCollection'] -> ShowS
$cshowList :: [PostCheckoutSessionsRequestBodyTaxIdCollection'] -> ShowS
show :: PostCheckoutSessionsRequestBodyTaxIdCollection' -> String
$cshow :: PostCheckoutSessionsRequestBodyTaxIdCollection' -> String
showsPrec :: Int -> PostCheckoutSessionsRequestBodyTaxIdCollection' -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsRequestBodyTaxIdCollection' -> ShowS
GHC.Show.Show,
      PostCheckoutSessionsRequestBodyTaxIdCollection'
-> PostCheckoutSessionsRequestBodyTaxIdCollection' -> Bool
(PostCheckoutSessionsRequestBodyTaxIdCollection'
 -> PostCheckoutSessionsRequestBodyTaxIdCollection' -> Bool)
-> (PostCheckoutSessionsRequestBodyTaxIdCollection'
    -> PostCheckoutSessionsRequestBodyTaxIdCollection' -> Bool)
-> Eq PostCheckoutSessionsRequestBodyTaxIdCollection'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsRequestBodyTaxIdCollection'
-> PostCheckoutSessionsRequestBodyTaxIdCollection' -> Bool
$c/= :: PostCheckoutSessionsRequestBodyTaxIdCollection'
-> PostCheckoutSessionsRequestBodyTaxIdCollection' -> Bool
== :: PostCheckoutSessionsRequestBodyTaxIdCollection'
-> PostCheckoutSessionsRequestBodyTaxIdCollection' -> Bool
$c== :: PostCheckoutSessionsRequestBodyTaxIdCollection'
-> PostCheckoutSessionsRequestBodyTaxIdCollection' -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCheckoutSessionsRequestBodyTaxIdCollection' where
  toJSON :: PostCheckoutSessionsRequestBodyTaxIdCollection' -> Value
toJSON PostCheckoutSessionsRequestBodyTaxIdCollection'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"enabled" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyTaxIdCollection' -> Bool
postCheckoutSessionsRequestBodyTaxIdCollection'Enabled PostCheckoutSessionsRequestBodyTaxIdCollection'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCheckoutSessionsRequestBodyTaxIdCollection' -> Encoding
toEncoding PostCheckoutSessionsRequestBodyTaxIdCollection'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs (Text
"enabled" Text -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCheckoutSessionsRequestBodyTaxIdCollection' -> Bool
postCheckoutSessionsRequestBodyTaxIdCollection'Enabled PostCheckoutSessionsRequestBodyTaxIdCollection'
obj)

instance Data.Aeson.Types.FromJSON.FromJSON PostCheckoutSessionsRequestBodyTaxIdCollection' where
  parseJSON :: Value -> Parser PostCheckoutSessionsRequestBodyTaxIdCollection'
parseJSON = String
-> (Object
    -> Parser PostCheckoutSessionsRequestBodyTaxIdCollection')
-> Value
-> Parser PostCheckoutSessionsRequestBodyTaxIdCollection'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCheckoutSessionsRequestBodyTaxIdCollection'" (\Object
obj -> (Bool -> PostCheckoutSessionsRequestBodyTaxIdCollection')
-> Parser (Bool -> PostCheckoutSessionsRequestBodyTaxIdCollection')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Bool -> PostCheckoutSessionsRequestBodyTaxIdCollection'
PostCheckoutSessionsRequestBodyTaxIdCollection' Parser (Bool -> PostCheckoutSessionsRequestBodyTaxIdCollection')
-> Parser Bool
-> Parser PostCheckoutSessionsRequestBodyTaxIdCollection'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"enabled"))

-- | Create a new 'PostCheckoutSessionsRequestBodyTaxIdCollection'' with all required fields.
mkPostCheckoutSessionsRequestBodyTaxIdCollection' ::
  -- | 'postCheckoutSessionsRequestBodyTaxIdCollection'Enabled'
  GHC.Types.Bool ->
  PostCheckoutSessionsRequestBodyTaxIdCollection'
mkPostCheckoutSessionsRequestBodyTaxIdCollection' :: Bool -> PostCheckoutSessionsRequestBodyTaxIdCollection'
mkPostCheckoutSessionsRequestBodyTaxIdCollection' Bool
postCheckoutSessionsRequestBodyTaxIdCollection'Enabled = PostCheckoutSessionsRequestBodyTaxIdCollection' :: Bool -> PostCheckoutSessionsRequestBodyTaxIdCollection'
PostCheckoutSessionsRequestBodyTaxIdCollection' {postCheckoutSessionsRequestBodyTaxIdCollection'Enabled :: Bool
postCheckoutSessionsRequestBodyTaxIdCollection'Enabled = Bool
postCheckoutSessionsRequestBodyTaxIdCollection'Enabled}

-- | Represents a response of the operation 'postCheckoutSessions'.
--
-- The response constructor is chosen by the status code of the response. If no case matches (no specific case for the response code, no range case, no default case), 'PostCheckoutSessionsResponseError' is used.
data PostCheckoutSessionsResponse
  = -- | Means either no matching case available or a parse error
    PostCheckoutSessionsResponseError GHC.Base.String
  | -- | Successful response.
    PostCheckoutSessionsResponse200 Checkout'session
  | -- | Error response.
    PostCheckoutSessionsResponseDefault Error
  deriving (Int -> PostCheckoutSessionsResponse -> ShowS
[PostCheckoutSessionsResponse] -> ShowS
PostCheckoutSessionsResponse -> String
(Int -> PostCheckoutSessionsResponse -> ShowS)
-> (PostCheckoutSessionsResponse -> String)
-> ([PostCheckoutSessionsResponse] -> ShowS)
-> Show PostCheckoutSessionsResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCheckoutSessionsResponse] -> ShowS
$cshowList :: [PostCheckoutSessionsResponse] -> ShowS
show :: PostCheckoutSessionsResponse -> String
$cshow :: PostCheckoutSessionsResponse -> String
showsPrec :: Int -> PostCheckoutSessionsResponse -> ShowS
$cshowsPrec :: Int -> PostCheckoutSessionsResponse -> ShowS
GHC.Show.Show, PostCheckoutSessionsResponse
-> PostCheckoutSessionsResponse -> Bool
(PostCheckoutSessionsResponse
 -> PostCheckoutSessionsResponse -> Bool)
-> (PostCheckoutSessionsResponse
    -> PostCheckoutSessionsResponse -> Bool)
-> Eq PostCheckoutSessionsResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCheckoutSessionsResponse
-> PostCheckoutSessionsResponse -> Bool
$c/= :: PostCheckoutSessionsResponse
-> PostCheckoutSessionsResponse -> Bool
== :: PostCheckoutSessionsResponse
-> PostCheckoutSessionsResponse -> Bool
$c== :: PostCheckoutSessionsResponse
-> PostCheckoutSessionsResponse -> Bool
GHC.Classes.Eq)