{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module StripeAPI.Operations.PostCustomersCustomerSubscriptions 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
postCustomersCustomerSubscriptions ::
  forall m.
  StripeAPI.Common.MonadHTTP m =>
  
  Data.Text.Internal.Text ->
  
  GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBody ->
  
  StripeAPI.Common.ClientT m (Network.HTTP.Client.Types.Response PostCustomersCustomerSubscriptionsResponse)
postCustomersCustomerSubscriptions :: Text
-> Maybe PostCustomersCustomerSubscriptionsRequestBody
-> ClientT m (Response PostCustomersCustomerSubscriptionsResponse)
postCustomersCustomerSubscriptions
  Text
customer
  Maybe PostCustomersCustomerSubscriptionsRequestBody
body =
    (Response ByteString
 -> Response PostCustomersCustomerSubscriptionsResponse)
-> ClientT m (Response ByteString)
-> ClientT m (Response PostCustomersCustomerSubscriptionsResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
      ( \Response ByteString
response_0 ->
          (ByteString -> PostCustomersCustomerSubscriptionsResponse)
-> Response ByteString
-> Response PostCustomersCustomerSubscriptionsResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
            ( (String -> PostCustomersCustomerSubscriptionsResponse)
-> (PostCustomersCustomerSubscriptionsResponse
    -> PostCustomersCustomerSubscriptionsResponse)
-> Either String PostCustomersCustomerSubscriptionsResponse
-> PostCustomersCustomerSubscriptionsResponse
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
Data.Either.either String -> PostCustomersCustomerSubscriptionsResponse
PostCustomersCustomerSubscriptionsResponseError PostCustomersCustomerSubscriptionsResponse
-> PostCustomersCustomerSubscriptionsResponse
forall a. a -> a
GHC.Base.id
                (Either String PostCustomersCustomerSubscriptionsResponse
 -> PostCustomersCustomerSubscriptionsResponse)
-> (ByteString
    -> Either String PostCustomersCustomerSubscriptionsResponse)
-> ByteString
-> PostCustomersCustomerSubscriptionsResponse
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) ->
                                     Subscription -> PostCustomersCustomerSubscriptionsResponse
PostCustomersCustomerSubscriptionsResponse200
                                       (Subscription -> PostCustomersCustomerSubscriptionsResponse)
-> Either String Subscription
-> Either String PostCustomersCustomerSubscriptionsResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String Subscription
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                            Data.Either.Either
                                                              GHC.Base.String
                                                              Subscription
                                                        )
                                   | 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 -> PostCustomersCustomerSubscriptionsResponse
PostCustomersCustomerSubscriptionsResponseDefault
                                       (Error -> PostCustomersCustomerSubscriptionsResponse)
-> Either String Error
-> Either String PostCustomersCustomerSubscriptionsResponse
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 PostCustomersCustomerSubscriptionsResponse
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 PostCustomersCustomerSubscriptionsRequestBody
-> 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/customers/" String -> String -> String
forall a. [a] -> [a] -> [a]
GHC.Base.++ (ByteString -> String
Data.ByteString.Char8.unpack (Bool -> ByteString -> ByteString
Network.HTTP.Types.URI.urlEncode Bool
GHC.Types.True (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
GHC.Base.$ (String -> ByteString
Data.ByteString.Char8.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
GHC.Base.$ Text -> String
forall a. StringifyModel a => a -> String
StripeAPI.Common.stringifyModel Text
customer)) String -> String -> String
forall a. [a] -> [a] -> [a]
GHC.Base.++ String
"/subscriptions"))) [QueryParameter]
forall a. Monoid a => a
GHC.Base.mempty Maybe PostCustomersCustomerSubscriptionsRequestBody
body RequestBodyEncoding
StripeAPI.Common.RequestBodyEncodingFormData)
data PostCustomersCustomerSubscriptionsRequestBody = PostCustomersCustomerSubscriptionsRequestBody
  { 
    PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems :: (GHC.Maybe.Maybe ([PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'])),
    
    PostCustomersCustomerSubscriptionsRequestBody -> Maybe Double
postCustomersCustomerSubscriptionsRequestBodyApplicationFeePercent :: (GHC.Maybe.Maybe GHC.Types.Double),
    
    PostCustomersCustomerSubscriptionsRequestBody
-> Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
postCustomersCustomerSubscriptionsRequestBodyAutomaticTax :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'),
    
    PostCustomersCustomerSubscriptionsRequestBody -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyBackdateStartDate :: (GHC.Maybe.Maybe GHC.Types.Int),
    
    PostCustomersCustomerSubscriptionsRequestBody -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyBillingCycleAnchor :: (GHC.Maybe.Maybe GHC.Types.Int),
    
    PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
postCustomersCustomerSubscriptionsRequestBodyBillingThresholds :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants),
    
    PostCustomersCustomerSubscriptionsRequestBody -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyCancelAt :: (GHC.Maybe.Maybe GHC.Types.Int),
    
    PostCustomersCustomerSubscriptionsRequestBody -> Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyCancelAtPeriodEnd :: (GHC.Maybe.Maybe GHC.Types.Bool),
    
    PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
postCustomersCustomerSubscriptionsRequestBodyCollectionMethod :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'),
    
    
    
    
    
    PostCustomersCustomerSubscriptionsRequestBody -> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyCoupon :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    PostCustomersCustomerSubscriptionsRequestBody -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyDaysUntilDue :: (GHC.Maybe.Maybe GHC.Types.Int),
    
    
    
    
    
    PostCustomersCustomerSubscriptionsRequestBody -> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyDefaultPaymentMethod :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    
    
    PostCustomersCustomerSubscriptionsRequestBody -> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyDefaultSource :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
postCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants),
    
    PostCustomersCustomerSubscriptionsRequestBody -> Maybe [Text]
postCustomersCustomerSubscriptionsRequestBodyExpand :: (GHC.Maybe.Maybe ([Data.Text.Internal.Text])),
    
    PostCustomersCustomerSubscriptionsRequestBody
-> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
postCustomersCustomerSubscriptionsRequestBodyItems :: (GHC.Maybe.Maybe ([PostCustomersCustomerSubscriptionsRequestBodyItems'])),
    
    PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
postCustomersCustomerSubscriptionsRequestBodyMetadata :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants),
    
    PostCustomersCustomerSubscriptionsRequestBody -> Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyOffSession :: (GHC.Maybe.Maybe GHC.Types.Bool),
    
    
    
    
    
    
    
    PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
postCustomersCustomerSubscriptionsRequestBodyPaymentBehavior :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'),
    
    PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants),
    
    
    
    
    
    PostCustomersCustomerSubscriptionsRequestBody -> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyPromotionCode :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
postCustomersCustomerSubscriptionsRequestBodyProrationBehavior :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'),
    
    PostCustomersCustomerSubscriptionsRequestBody
-> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
postCustomersCustomerSubscriptionsRequestBodyTransferData :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'),
    
    PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
postCustomersCustomerSubscriptionsRequestBodyTrialEnd :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants),
    
    PostCustomersCustomerSubscriptionsRequestBody -> Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyTrialFromPlan :: (GHC.Maybe.Maybe GHC.Types.Bool),
    
    PostCustomersCustomerSubscriptionsRequestBody -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyTrialPeriodDays :: (GHC.Maybe.Maybe GHC.Types.Int)
  }
  deriving
    ( Int
-> PostCustomersCustomerSubscriptionsRequestBody
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBody] -> String -> String
PostCustomersCustomerSubscriptionsRequestBody -> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBody
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBody -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBody]
    -> String -> String)
-> Show PostCustomersCustomerSubscriptionsRequestBody
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBody] -> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBody] -> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBody -> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBody -> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBody
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBody
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerSubscriptionsRequestBody
-> PostCustomersCustomerSubscriptionsRequestBody -> Bool
(PostCustomersCustomerSubscriptionsRequestBody
 -> PostCustomersCustomerSubscriptionsRequestBody -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBody
    -> PostCustomersCustomerSubscriptionsRequestBody -> Bool)
-> Eq PostCustomersCustomerSubscriptionsRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBody
-> PostCustomersCustomerSubscriptionsRequestBody -> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBody
-> PostCustomersCustomerSubscriptionsRequestBody -> Bool
== :: PostCustomersCustomerSubscriptionsRequestBody
-> PostCustomersCustomerSubscriptionsRequestBody -> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBody
-> PostCustomersCustomerSubscriptionsRequestBody -> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBody where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBody -> Value
toJSON PostCustomersCustomerSubscriptionsRequestBody
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"add_invoice_items" Text
-> Maybe
     [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"application_fee_percent" Text -> Maybe Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Double
postCustomersCustomerSubscriptionsRequestBodyApplicationFeePercent PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"automatic_tax" Text
-> Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
postCustomersCustomerSubscriptionsRequestBodyAutomaticTax PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"backdate_start_date" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyBackdateStartDate PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"billing_cycle_anchor" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyBillingCycleAnchor PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"billing_thresholds" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
postCustomersCustomerSubscriptionsRequestBodyBillingThresholds PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"cancel_at" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyCancelAt PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"cancel_at_period_end" Text -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyCancelAtPeriodEnd PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"collection_method" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
postCustomersCustomerSubscriptionsRequestBodyCollectionMethod PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"coupon" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyCoupon PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"days_until_due" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyDaysUntilDue PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"default_payment_method" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyDefaultPaymentMethod PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"default_source" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyDefaultSource PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"default_tax_rates" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
postCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates PostCustomersCustomerSubscriptionsRequestBody
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..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe [Text]
postCustomersCustomerSubscriptionsRequestBodyExpand PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"items" Text
-> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
postCustomersCustomerSubscriptionsRequestBodyItems PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
postCustomersCustomerSubscriptionsRequestBodyMetadata PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"off_session" Text -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyOffSession PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"payment_behavior" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
postCustomersCustomerSubscriptionsRequestBodyPaymentBehavior PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"pending_invoice_item_interval" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval PostCustomersCustomerSubscriptionsRequestBody
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..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyPromotionCode PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"proration_behavior" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
postCustomersCustomerSubscriptionsRequestBodyProrationBehavior PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"transfer_data" Text
-> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
postCustomersCustomerSubscriptionsRequestBodyTransferData PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"trial_end" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
postCustomersCustomerSubscriptionsRequestBodyTrialEnd PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"trial_from_plan" Text -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyTrialFromPlan PostCustomersCustomerSubscriptionsRequestBody
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..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyTrialPeriodDays PostCustomersCustomerSubscriptionsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerSubscriptionsRequestBody -> Encoding
toEncoding PostCustomersCustomerSubscriptionsRequestBody
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"add_invoice_items" Text
-> Maybe
     [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"application_fee_percent" Text -> Maybe Double -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Double
postCustomersCustomerSubscriptionsRequestBodyApplicationFeePercent PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"automatic_tax" Text
-> Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
postCustomersCustomerSubscriptionsRequestBodyAutomaticTax PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"backdate_start_date" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyBackdateStartDate PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"billing_cycle_anchor" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyBillingCycleAnchor PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"billing_thresholds" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
postCustomersCustomerSubscriptionsRequestBodyBillingThresholds PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"cancel_at" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyCancelAt PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"cancel_at_period_end" Text -> Maybe Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyCancelAtPeriodEnd PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"collection_method" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
postCustomersCustomerSubscriptionsRequestBodyCollectionMethod PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"coupon" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyCoupon PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"days_until_due" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyDaysUntilDue PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"default_payment_method" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyDefaultPaymentMethod PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"default_source" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyDefaultSource PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"default_tax_rates" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
postCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates PostCustomersCustomerSubscriptionsRequestBody
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..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe [Text]
postCustomersCustomerSubscriptionsRequestBodyExpand PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"items" Text
-> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
postCustomersCustomerSubscriptionsRequestBodyItems PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"metadata" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
postCustomersCustomerSubscriptionsRequestBodyMetadata PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"off_session" Text -> Maybe Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyOffSession PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"payment_behavior" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
postCustomersCustomerSubscriptionsRequestBodyPaymentBehavior PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"pending_invoice_item_interval" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval PostCustomersCustomerSubscriptionsRequestBody
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..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyPromotionCode PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"proration_behavior" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
postCustomersCustomerSubscriptionsRequestBodyProrationBehavior PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"transfer_data" Text
-> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
postCustomersCustomerSubscriptionsRequestBodyTransferData PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"trial_end" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
postCustomersCustomerSubscriptionsRequestBodyTrialEnd PostCustomersCustomerSubscriptionsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"trial_from_plan" Text -> Maybe Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyTrialFromPlan PostCustomersCustomerSubscriptionsRequestBody
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..= PostCustomersCustomerSubscriptionsRequestBody -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyTrialPeriodDays PostCustomersCustomerSubscriptionsRequestBody
obj))))))))))))))))))))))))))
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBody where
  parseJSON :: Value -> Parser PostCustomersCustomerSubscriptionsRequestBody
parseJSON = String
-> (Object -> Parser PostCustomersCustomerSubscriptionsRequestBody)
-> Value
-> Parser PostCustomersCustomerSubscriptionsRequestBody
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerSubscriptionsRequestBody" (\Object
obj -> ((((((((((((((((((((((((((Maybe
   [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
 -> Maybe Double
 -> Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
 -> Maybe Int
 -> Maybe Int
 -> Maybe
      PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
 -> Maybe Int
 -> Maybe Bool
 -> Maybe
      PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
 -> Maybe Text
 -> Maybe Int
 -> Maybe Text
 -> Maybe Text
 -> Maybe
      PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
 -> Maybe [Text]
 -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
 -> Maybe
      PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
 -> Maybe Bool
 -> Maybe
      PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
 -> Maybe
      PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
 -> Maybe Text
 -> Maybe
      PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
 -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
 -> Maybe
      PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
 -> Maybe Bool
 -> Maybe Int
 -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser
     (Maybe
        [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
      -> Maybe Double
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
      -> Maybe Int
      -> Maybe Int
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
      -> Maybe Int
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
      -> Maybe [Text]
      -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe
  [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
-> Maybe Double
-> Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> Maybe Int
-> Maybe Int
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> Maybe Int
-> Maybe Bool
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> Maybe [Text]
-> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> Maybe Bool
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> Maybe Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> Maybe Bool
-> Maybe Int
-> PostCustomersCustomerSubscriptionsRequestBody
PostCustomersCustomerSubscriptionsRequestBody Parser
  (Maybe
     [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
   -> Maybe Double
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
   -> Maybe Int
   -> Maybe Int
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
   -> Maybe Int
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
   -> Maybe [Text]
   -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser
     (Maybe
        [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'])
-> Parser
     (Maybe Double
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
      -> Maybe Int
      -> Maybe Int
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
      -> Maybe Int
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
      -> Maybe [Text]
      -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"add_invoice_items")) Parser
  (Maybe Double
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
   -> Maybe Int
   -> Maybe Int
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
   -> Maybe Int
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
   -> Maybe [Text]
   -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser (Maybe Double)
-> Parser
     (Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
      -> Maybe Int
      -> Maybe Int
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
      -> Maybe Int
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
      -> Maybe [Text]
      -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
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 PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
   -> Maybe Int
   -> Maybe Int
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
   -> Maybe Int
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
   -> Maybe [Text]
   -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser
     (Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax')
-> Parser
     (Maybe Int
      -> Maybe Int
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
      -> Maybe Int
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
      -> Maybe [Text]
      -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"automatic_tax")) Parser
  (Maybe Int
   -> Maybe Int
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
   -> Maybe Int
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
   -> Maybe [Text]
   -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser (Maybe Int)
-> Parser
     (Maybe Int
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
      -> Maybe Int
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
      -> Maybe [Text]
      -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
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
"backdate_start_date")) Parser
  (Maybe Int
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
   -> Maybe Int
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
   -> Maybe [Text]
   -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser (Maybe Int)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
      -> Maybe Int
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
      -> Maybe [Text]
      -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
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
"billing_cycle_anchor")) Parser
  (Maybe
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
   -> Maybe Int
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
   -> Maybe [Text]
   -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants)
-> Parser
     (Maybe Int
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
      -> Maybe [Text]
      -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"billing_thresholds")) Parser
  (Maybe Int
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
   -> Maybe [Text]
   -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser (Maybe Int)
-> Parser
     (Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
      -> Maybe [Text]
      -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
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
"cancel_at")) Parser
  (Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
   -> Maybe [Text]
   -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser (Maybe Bool)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
      -> Maybe [Text]
      -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
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
"cancel_at_period_end")) Parser
  (Maybe
     PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
   -> Maybe [Text]
   -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod')
-> Parser
     (Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
      -> Maybe [Text]
      -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"collection_method")) Parser
  (Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
   -> Maybe [Text]
   -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser (Maybe Text)
-> Parser
     (Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
      -> Maybe [Text]
      -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
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 Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
   -> Maybe [Text]
   -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser (Maybe Int)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
      -> Maybe [Text]
      -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
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
"days_until_due")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
   -> Maybe [Text]
   -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
      -> Maybe [Text]
      -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
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_payment_method")) Parser
  (Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
   -> Maybe [Text]
   -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser (Maybe Text)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
      -> Maybe [Text]
      -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
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_source")) Parser
  (Maybe
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
   -> Maybe [Text]
   -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants)
-> Parser
     (Maybe [Text]
      -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"default_tax_rates")) Parser
  (Maybe [Text]
   -> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser (Maybe [Text])
-> Parser
     (Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
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 [PostCustomersCustomerSubscriptionsRequestBodyItems']
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser
     (Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems'])
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
      -> Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems'])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"items")) Parser
  (Maybe
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
   -> Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants)
-> Parser
     (Maybe Bool
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"metadata")) Parser
  (Maybe Bool
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser (Maybe Bool)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
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
"off_session")) Parser
  (Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior')
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"payment_behavior")) Parser
  (Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants)
-> Parser
     (Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"pending_invoice_item_interval")) Parser
  (Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser (Maybe Text)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
      -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
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")) Parser
  (Maybe
     PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
   -> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior')
-> Parser
     (Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"proration_behavior")) Parser
  (Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser
     (Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData')
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
      -> Maybe Bool
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"transfer_data")) Parser
  (Maybe
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
   -> Maybe Bool
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants)
-> Parser
     (Maybe Bool
      -> Maybe Int -> PostCustomersCustomerSubscriptionsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"trial_end")) Parser
  (Maybe Bool
   -> Maybe Int -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser (Maybe Bool)
-> Parser
     (Maybe Int -> PostCustomersCustomerSubscriptionsRequestBody)
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
"trial_from_plan")) Parser (Maybe Int -> PostCustomersCustomerSubscriptionsRequestBody)
-> Parser (Maybe Int)
-> Parser PostCustomersCustomerSubscriptionsRequestBody
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"))
mkPostCustomersCustomerSubscriptionsRequestBody :: PostCustomersCustomerSubscriptionsRequestBody
mkPostCustomersCustomerSubscriptionsRequestBody :: PostCustomersCustomerSubscriptionsRequestBody
mkPostCustomersCustomerSubscriptionsRequestBody =
  PostCustomersCustomerSubscriptionsRequestBody :: Maybe
  [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
-> Maybe Double
-> Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> Maybe Int
-> Maybe Int
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> Maybe Int
-> Maybe Bool
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> Maybe [Text]
-> Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> Maybe Bool
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> Maybe Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> Maybe Bool
-> Maybe Int
-> PostCustomersCustomerSubscriptionsRequestBody
PostCustomersCustomerSubscriptionsRequestBody
    { postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems :: Maybe
  [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems = Maybe
  [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyApplicationFeePercent :: Maybe Double
postCustomersCustomerSubscriptionsRequestBodyApplicationFeePercent = Maybe Double
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyAutomaticTax :: Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
postCustomersCustomerSubscriptionsRequestBodyAutomaticTax = Maybe PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyBackdateStartDate :: Maybe Int
postCustomersCustomerSubscriptionsRequestBodyBackdateStartDate = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyBillingCycleAnchor :: Maybe Int
postCustomersCustomerSubscriptionsRequestBodyBillingCycleAnchor = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyBillingThresholds :: Maybe
  PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
postCustomersCustomerSubscriptionsRequestBodyBillingThresholds = Maybe
  PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyCancelAt :: Maybe Int
postCustomersCustomerSubscriptionsRequestBodyCancelAt = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyCancelAtPeriodEnd :: Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyCancelAtPeriodEnd = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyCollectionMethod :: Maybe
  PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
postCustomersCustomerSubscriptionsRequestBodyCollectionMethod = Maybe
  PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyCoupon :: Maybe Text
postCustomersCustomerSubscriptionsRequestBodyCoupon = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyDaysUntilDue :: Maybe Int
postCustomersCustomerSubscriptionsRequestBodyDaysUntilDue = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyDefaultPaymentMethod :: Maybe Text
postCustomersCustomerSubscriptionsRequestBodyDefaultPaymentMethod = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyDefaultSource :: Maybe Text
postCustomersCustomerSubscriptionsRequestBodyDefaultSource = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates :: Maybe
  PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
postCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates = Maybe
  PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyExpand :: Maybe [Text]
postCustomersCustomerSubscriptionsRequestBodyExpand = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyItems :: Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
postCustomersCustomerSubscriptionsRequestBodyItems = Maybe [PostCustomersCustomerSubscriptionsRequestBodyItems']
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyMetadata :: Maybe
  PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
postCustomersCustomerSubscriptionsRequestBodyMetadata = Maybe
  PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyOffSession :: Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyOffSession = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyPaymentBehavior :: Maybe PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
postCustomersCustomerSubscriptionsRequestBodyPaymentBehavior = Maybe PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval :: Maybe
  PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval = Maybe
  PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyPromotionCode :: Maybe Text
postCustomersCustomerSubscriptionsRequestBodyPromotionCode = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyProrationBehavior :: Maybe
  PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
postCustomersCustomerSubscriptionsRequestBodyProrationBehavior = Maybe
  PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyTransferData :: Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
postCustomersCustomerSubscriptionsRequestBodyTransferData = Maybe PostCustomersCustomerSubscriptionsRequestBodyTransferData'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyTrialEnd :: Maybe
  PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
postCustomersCustomerSubscriptionsRequestBodyTrialEnd = Maybe
  PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyTrialFromPlan :: Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyTrialFromPlan = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyTrialPeriodDays :: Maybe Int
postCustomersCustomerSubscriptionsRequestBodyTrialPeriodDays = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
    }
data PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems' = PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
  { 
    
    
    
    
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'Price :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'),
    
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'Quantity :: (GHC.Maybe.Maybe GHC.Types.Int),
    
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants)
  }
  deriving
    ( Int
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems']
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
 -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
    -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
    -> Bool)
-> Eq PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems' where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Value
toJSON PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"price" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'Price PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"price_data" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
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..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'Quantity PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"tax_rates" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Encoding
toEncoding PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"price" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'Price PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"price_data" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
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..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'Quantity PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"tax_rates" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
obj))))
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
parseJSON = String
-> (Object
    -> Parser
         PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems')
-> Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'" (\Object
obj -> ((((Maybe Text
 -> Maybe
      PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
 -> Maybe Int
 -> Maybe
      PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
 -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems')
-> Parser
     (Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
      -> Maybe Int
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
      -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Maybe Int
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems' Parser
  (Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
   -> Maybe Int
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
   -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems')
-> Parser (Maybe Text)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
      -> Maybe Int
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
      -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems')
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
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
   -> Maybe Int
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
   -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems')
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData')
-> Parser
     (Maybe Int
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
      -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"price_data")) Parser
  (Maybe Int
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
   -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems')
-> Parser (Maybe Int)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
      -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems')
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
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
   -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems')
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants)
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"tax_rates"))
mkPostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems' :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
mkPostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems' :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
mkPostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems' =
  PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems' :: Maybe Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Maybe Int
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'
    { postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'Price :: Maybe Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'Price = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData :: Maybe
  PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData = Maybe
  PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'Quantity :: Maybe Int
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'Quantity = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates :: Maybe
  PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates = Maybe
  PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
forall a. Maybe a
GHC.Maybe.Nothing
    }
data PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData' = PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
  { 
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'Currency :: Data.Text.Internal.Text,
    
    
    
    
    
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'Product :: Data.Text.Internal.Text,
    
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'),
    
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'UnitAmount :: (GHC.Maybe.Maybe GHC.Types.Int),
    
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'UnitAmountDecimal :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData']
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData']
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData']
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData']
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
 -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
    -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData' where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Value
toJSON PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'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..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'Currency PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"product" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'Product PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"tax_behavior" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'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..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'UnitAmount PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'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..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'UnitAmountDecimal PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Encoding
toEncoding PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'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..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'Currency PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"product" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'Product PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"tax_behavior" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'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..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'UnitAmount PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'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..= PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
-> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'UnitAmountDecimal PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
obj)))))
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
parseJSON = String
-> (Object
    -> Parser
         PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData')
-> Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'" (\Object
obj -> (((((Text
 -> Text
 -> Maybe
      PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
 -> Maybe Int
 -> Maybe Text
 -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData')
-> Parser
     (Text
      -> Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
      -> Maybe Int
      -> Maybe Text
      -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Text
-> Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> Maybe Int
-> Maybe Text
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData' Parser
  (Text
   -> Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
   -> Maybe Int
   -> Maybe Text
   -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData')
-> Parser Text
-> Parser
     (Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
      -> Maybe Int
      -> Maybe Text
      -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'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
  (Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
   -> Maybe Int
   -> Maybe Text
   -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData')
-> Parser Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
      -> Maybe Int
      -> Maybe Text
      -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'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
"product")) Parser
  (Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
   -> Maybe Int
   -> Maybe Text
   -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData')
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior')
-> Parser
     (Maybe Int
      -> Maybe Text
      -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"tax_behavior")) Parser
  (Maybe Int
   -> Maybe Text
   -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData')
-> Parser (Maybe Int)
-> Parser
     (Maybe Text
      -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'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
   -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData')
-> Parser (Maybe Text)
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'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"))
mkPostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData' ::
  
  Data.Text.Internal.Text ->
  
  Data.Text.Internal.Text ->
  PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
mkPostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData' :: Text
-> Text
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
mkPostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData' Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'Currency Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'Product =
  PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData' :: Text
-> Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> Maybe Int
-> Maybe Text
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'
    { postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'Currency :: Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'Currency = Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'Currency,
      postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'Product :: Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'Product = Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'Product,
      postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior :: Maybe
  PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior = Maybe
  PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'UnitAmount :: Maybe Int
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'UnitAmount = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'UnitAmountDecimal :: Maybe Text
postCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'UnitAmountDecimal = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }
data PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
  = 
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'Other Data.Aeson.Types.Internal.Value
  | 
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'Typed Data.Text.Internal.Text
  | 
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'EnumExclusive
  | 
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'EnumInclusive
  | 
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'EnumUnspecified
  deriving (Int
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior']
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior']
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior']
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior']
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
 -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
    -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior' where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> Value
toJSON (PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'Other Value
val) = Value
val
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'EnumExclusive) = Value
"exclusive"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'EnumInclusive) = Value
"inclusive"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'EnumUnspecified) = Value
"unspecified"
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
parseJSON Value
val =
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'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" -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'EnumExclusive
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"inclusive" -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'EnumInclusive
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"unspecified" -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'EnumUnspecified
            | Bool
GHC.Base.otherwise -> Value
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'PriceData'TaxBehavior'Other Value
val
      )
data PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
  = 
    PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'EmptyString
  | PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'ListTText ([Data.Text.Internal.Text])
  deriving (Int
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants]
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants]
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants]
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants]
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
 -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
    -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> Value
toJSON (PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'ListTText [Text]
a) = [Text] -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON [Text]
a
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'EmptyString) = Value
""
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
parseJSON Value
val =
    if
        | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"" -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'EmptyString
        | Bool
GHC.Base.otherwise -> case ([Text]
-> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'ListTText ([Text]
 -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants)
-> Result [Text]
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'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
  PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched" of
          Data.Aeson.Types.Internal.Success PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
a -> PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
a
          Data.Aeson.Types.Internal.Error String
a -> String
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyAddInvoiceItems'TaxRates'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a
data PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax' = PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
  { 
    PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax' -> Bool
postCustomersCustomerSubscriptionsRequestBodyAutomaticTax'Enabled :: GHC.Types.Bool
  }
  deriving
    ( Int
-> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax']
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax']
    -> String -> String)
-> Show PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax']
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax']
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
 -> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
    -> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
    -> Bool)
-> Eq PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax' where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax' -> Value
toJSON PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
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..= PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax' -> Bool
postCustomersCustomerSubscriptionsRequestBodyAutomaticTax'Enabled PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
-> Encoding
toEncoding PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
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..= PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax' -> Bool
postCustomersCustomerSubscriptionsRequestBodyAutomaticTax'Enabled PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
obj)
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
parseJSON = String
-> (Object
    -> Parser
         PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax')
-> Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'" (\Object
obj -> (Bool
 -> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax')
-> Parser
     (Bool
      -> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Bool -> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax' Parser
  (Bool
   -> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax')
-> Parser Bool
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
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"))
mkPostCustomersCustomerSubscriptionsRequestBodyAutomaticTax' ::
  
  GHC.Types.Bool ->
  PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
mkPostCustomersCustomerSubscriptionsRequestBodyAutomaticTax' :: Bool -> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
mkPostCustomersCustomerSubscriptionsRequestBodyAutomaticTax' Bool
postCustomersCustomerSubscriptionsRequestBodyAutomaticTax'Enabled = PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax' :: Bool -> PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax'
PostCustomersCustomerSubscriptionsRequestBodyAutomaticTax' {postCustomersCustomerSubscriptionsRequestBodyAutomaticTax'Enabled :: Bool
postCustomersCustomerSubscriptionsRequestBodyAutomaticTax'Enabled = Bool
postCustomersCustomerSubscriptionsRequestBodyAutomaticTax'Enabled}
data PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1 = PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
  { 
    PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1AmountGte :: (GHC.Maybe.Maybe GHC.Types.Int),
    
    PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1ResetBillingCycleAnchor :: (GHC.Maybe.Maybe GHC.Types.Bool)
  }
  deriving
    ( Int
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1]
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1]
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1]
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1]
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
 -> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
    -> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1 where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> Value
toJSON PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"amount_gte" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1AmountGte PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"reset_billing_cycle_anchor" Text -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1ResetBillingCycleAnchor PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> Encoding
toEncoding PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"amount_gte" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1AmountGte PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"reset_billing_cycle_anchor" Text -> Maybe Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1ResetBillingCycleAnchor PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
obj))
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1 where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
parseJSON = String
-> (Object
    -> Parser
         PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1)
-> Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1" (\Object
obj -> ((Maybe Int
 -> Maybe Bool
 -> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1)
-> Parser
     (Maybe Int
      -> Maybe Bool
      -> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Int
-> Maybe Bool
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1 Parser
  (Maybe Int
   -> Maybe Bool
   -> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1)
-> Parser (Maybe Int)
-> Parser
     (Maybe Bool
      -> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1)
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_gte")) Parser
  (Maybe Bool
   -> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1)
-> Parser (Maybe Bool)
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
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
"reset_billing_cycle_anchor"))
mkPostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1 :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
mkPostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1 :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
mkPostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1 =
  PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1 :: Maybe Int
-> Maybe Bool
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
    { postCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1AmountGte :: Maybe Int
postCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1AmountGte = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1ResetBillingCycleAnchor :: Maybe Bool
postCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1ResetBillingCycleAnchor = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
    }
data PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
  = 
    PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'EmptyString
  | PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1 PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
  deriving (Int
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants]
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants]
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants]
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants]
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
 -> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
    -> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> Value
toJSON (PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1 PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
a) = PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
a
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'EmptyString) = Value
""
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
parseJSON Value
val =
    if
        | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"" -> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'EmptyString
        | Bool
GHC.Base.otherwise -> case (PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1 (PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
 -> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants)
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'OneOf1
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result
  PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched" of
          Data.Aeson.Types.Internal.Success PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
a -> PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
a
          Data.Aeson.Types.Internal.Error String
a -> String
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyBillingThresholds'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a
data PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
  = 
    PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'Other Data.Aeson.Types.Internal.Value
  | 
    PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'Typed Data.Text.Internal.Text
  | 
    PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'EnumChargeAutomatically
  | 
    PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'EnumSendInvoice
  deriving (Int
-> PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod']
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod']
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod']
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod']
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
 -> PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
    -> PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod' where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> Value
toJSON (PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'Other Value
val) = Value
val
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'EnumChargeAutomatically) = Value
"charge_automatically"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'EnumSendInvoice) = Value
"send_invoice"
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
parseJSON Value
val =
    PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
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
"charge_automatically" -> PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'EnumChargeAutomatically
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"send_invoice" -> PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'EnumSendInvoice
            | Bool
GHC.Base.otherwise -> Value
-> PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'
PostCustomersCustomerSubscriptionsRequestBodyCollectionMethod'Other Value
val
      )
data PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
  = 
    PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'EmptyString
  | PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'ListTText ([Data.Text.Internal.Text])
  deriving (Int
-> PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants]
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants]
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants]
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants]
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
 -> PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
    -> PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> Value
toJSON (PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'ListTText [Text]
a) = [Text] -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON [Text]
a
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'EmptyString) = Value
""
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
parseJSON Value
val =
    if
        | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"" -> PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'EmptyString
        | Bool
GHC.Base.otherwise -> case ([Text]
-> PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'ListTText ([Text]
 -> PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants)
-> Result [Text]
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'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
  PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched" of
          Data.Aeson.Types.Internal.Success PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
a -> PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
a
          Data.Aeson.Types.Internal.Error String
a -> String
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyDefaultTaxRates'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a
data PostCustomersCustomerSubscriptionsRequestBodyItems' = PostCustomersCustomerSubscriptionsRequestBodyItems'
  { 
    PostCustomersCustomerSubscriptionsRequestBodyItems'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
postCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants),
    
    PostCustomersCustomerSubscriptionsRequestBodyItems' -> Maybe Object
postCustomersCustomerSubscriptionsRequestBodyItems'Metadata :: (GHC.Maybe.Maybe Data.Aeson.Types.Internal.Object),
    
    
    
    
    
    PostCustomersCustomerSubscriptionsRequestBodyItems' -> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyItems'Price :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    PostCustomersCustomerSubscriptionsRequestBodyItems'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'),
    
    PostCustomersCustomerSubscriptionsRequestBodyItems' -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyItems'Quantity :: (GHC.Maybe.Maybe GHC.Types.Int),
    
    PostCustomersCustomerSubscriptionsRequestBodyItems'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
postCustomersCustomerSubscriptionsRequestBodyItems'TaxRates :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants)
  }
  deriving
    ( Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyItems']
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyItems' -> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems' -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyItems']
    -> String -> String)
-> Show PostCustomersCustomerSubscriptionsRequestBodyItems'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyItems']
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyItems']
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyItems' -> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyItems' -> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerSubscriptionsRequestBodyItems'
-> PostCustomersCustomerSubscriptionsRequestBodyItems' -> Bool
(PostCustomersCustomerSubscriptionsRequestBodyItems'
 -> PostCustomersCustomerSubscriptionsRequestBodyItems' -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems'
    -> PostCustomersCustomerSubscriptionsRequestBodyItems' -> Bool)
-> Eq PostCustomersCustomerSubscriptionsRequestBodyItems'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'
-> PostCustomersCustomerSubscriptionsRequestBodyItems' -> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'
-> PostCustomersCustomerSubscriptionsRequestBodyItems' -> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyItems'
-> PostCustomersCustomerSubscriptionsRequestBodyItems' -> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyItems'
-> PostCustomersCustomerSubscriptionsRequestBodyItems' -> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyItems' where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyItems' -> Value
toJSON PostCustomersCustomerSubscriptionsRequestBodyItems'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"billing_thresholds" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
postCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds PostCustomersCustomerSubscriptionsRequestBodyItems'
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..= PostCustomersCustomerSubscriptionsRequestBodyItems' -> Maybe Object
postCustomersCustomerSubscriptionsRequestBodyItems'Metadata PostCustomersCustomerSubscriptionsRequestBodyItems'
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..= PostCustomersCustomerSubscriptionsRequestBodyItems' -> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyItems'Price PostCustomersCustomerSubscriptionsRequestBodyItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"price_data" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData PostCustomersCustomerSubscriptionsRequestBodyItems'
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..= PostCustomersCustomerSubscriptionsRequestBodyItems' -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyItems'Quantity PostCustomersCustomerSubscriptionsRequestBodyItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"tax_rates" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
postCustomersCustomerSubscriptionsRequestBodyItems'TaxRates PostCustomersCustomerSubscriptionsRequestBodyItems'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerSubscriptionsRequestBodyItems' -> Encoding
toEncoding PostCustomersCustomerSubscriptionsRequestBodyItems'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"billing_thresholds" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
postCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds PostCustomersCustomerSubscriptionsRequestBodyItems'
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..= PostCustomersCustomerSubscriptionsRequestBodyItems' -> Maybe Object
postCustomersCustomerSubscriptionsRequestBodyItems'Metadata PostCustomersCustomerSubscriptionsRequestBodyItems'
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..= PostCustomersCustomerSubscriptionsRequestBodyItems' -> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyItems'Price PostCustomersCustomerSubscriptionsRequestBodyItems'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"price_data" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData PostCustomersCustomerSubscriptionsRequestBodyItems'
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..= PostCustomersCustomerSubscriptionsRequestBodyItems' -> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyItems'Quantity PostCustomersCustomerSubscriptionsRequestBodyItems'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"tax_rates" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
postCustomersCustomerSubscriptionsRequestBodyItems'TaxRates PostCustomersCustomerSubscriptionsRequestBodyItems'
obj))))))
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyItems' where
  parseJSON :: Value -> Parser PostCustomersCustomerSubscriptionsRequestBodyItems'
parseJSON = String
-> (Object
    -> Parser PostCustomersCustomerSubscriptionsRequestBodyItems')
-> Value
-> Parser PostCustomersCustomerSubscriptionsRequestBodyItems'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerSubscriptionsRequestBodyItems'" (\Object
obj -> ((((((Maybe
   PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
 -> Maybe Object
 -> Maybe Text
 -> Maybe
      PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
 -> Maybe Int
 -> Maybe
      PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
 -> PostCustomersCustomerSubscriptionsRequestBodyItems')
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
      -> Maybe Object
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
      -> Maybe Int
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
      -> PostCustomersCustomerSubscriptionsRequestBodyItems')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe
  PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> Maybe Object
-> Maybe Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Maybe Int
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyItems'
PostCustomersCustomerSubscriptionsRequestBodyItems' Parser
  (Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
   -> Maybe Object
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
   -> Maybe Int
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
   -> PostCustomersCustomerSubscriptionsRequestBodyItems')
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants)
-> Parser
     (Maybe Object
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
      -> Maybe Int
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
      -> PostCustomersCustomerSubscriptionsRequestBodyItems')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"billing_thresholds")) Parser
  (Maybe Object
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
   -> Maybe Int
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
   -> PostCustomersCustomerSubscriptionsRequestBodyItems')
-> Parser (Maybe Object)
-> Parser
     (Maybe Text
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
      -> Maybe Int
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
      -> PostCustomersCustomerSubscriptionsRequestBodyItems')
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
        PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
   -> Maybe Int
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
   -> PostCustomersCustomerSubscriptionsRequestBodyItems')
-> Parser (Maybe Text)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
      -> Maybe Int
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
      -> PostCustomersCustomerSubscriptionsRequestBodyItems')
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
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
   -> Maybe Int
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
   -> PostCustomersCustomerSubscriptionsRequestBodyItems')
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData')
-> Parser
     (Maybe Int
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
      -> PostCustomersCustomerSubscriptionsRequestBodyItems')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"price_data")) Parser
  (Maybe Int
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
   -> PostCustomersCustomerSubscriptionsRequestBodyItems')
-> Parser (Maybe Int)
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
      -> PostCustomersCustomerSubscriptionsRequestBodyItems')
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
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
   -> PostCustomersCustomerSubscriptionsRequestBodyItems')
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants)
-> Parser PostCustomersCustomerSubscriptionsRequestBodyItems'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"tax_rates"))
mkPostCustomersCustomerSubscriptionsRequestBodyItems' :: PostCustomersCustomerSubscriptionsRequestBodyItems'
mkPostCustomersCustomerSubscriptionsRequestBodyItems' :: PostCustomersCustomerSubscriptionsRequestBodyItems'
mkPostCustomersCustomerSubscriptionsRequestBodyItems' =
  PostCustomersCustomerSubscriptionsRequestBodyItems' :: Maybe
  PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> Maybe Object
-> Maybe Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Maybe Int
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyItems'
PostCustomersCustomerSubscriptionsRequestBodyItems'
    { postCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds :: Maybe
  PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
postCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds = Maybe
  PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyItems'Metadata :: Maybe Object
postCustomersCustomerSubscriptionsRequestBodyItems'Metadata = Maybe Object
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyItems'Price :: Maybe Text
postCustomersCustomerSubscriptionsRequestBodyItems'Price = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyItems'PriceData :: Maybe PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData = Maybe PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyItems'Quantity :: Maybe Int
postCustomersCustomerSubscriptionsRequestBodyItems'Quantity = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyItems'TaxRates :: Maybe
  PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
postCustomersCustomerSubscriptionsRequestBodyItems'TaxRates = Maybe
  PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
forall a. Maybe a
GHC.Maybe.Nothing
    }
data PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1 = PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
  { 
    PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> Int
postCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1UsageGte :: GHC.Types.Int
  }
  deriving
    ( Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1]
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1]
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1]
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1]
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
    -> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1 where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> Value
toJSON PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"usage_gte" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> Int
postCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1UsageGte PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> Encoding
toEncoding PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs (Text
"usage_gte" Text -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> Int
postCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1UsageGte PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
obj)
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1 where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
parseJSON = String
-> (Object
    -> Parser
         PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1)
-> Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1" (\Object
obj -> (Int
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1)
-> Parser
     (Int
      -> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1 Parser
  (Int
   -> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1)
-> Parser Int
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"usage_gte"))
mkPostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1 ::
  
  GHC.Types.Int ->
  PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
mkPostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1 :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
mkPostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1 Int
postCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1UsageGte = PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1 :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1 {postCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1UsageGte :: Int
postCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1UsageGte = Int
postCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1UsageGte}
data PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
  = 
    PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'EmptyString
  | PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1 PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
  deriving (Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants]
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants]
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants]
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants]
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
    -> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> Value
toJSON (PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1 PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
a) = PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
a
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'EmptyString) = Value
""
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
parseJSON Value
val =
    if
        | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"" -> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'EmptyString
        | Bool
GHC.Base.otherwise -> case (PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1 (PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants)
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'OneOf1
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result
  PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched" of
          Data.Aeson.Types.Internal.Success PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
a -> PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
a
          Data.Aeson.Types.Internal.Error String
a -> String
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'BillingThresholds'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a
data PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData' = PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
  { 
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Currency :: Data.Text.Internal.Text,
    
    
    
    
    
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Product :: Data.Text.Internal.Text,
    
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring',
    
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior :: (GHC.Maybe.Maybe PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'),
    
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'UnitAmount :: (GHC.Maybe.Maybe GHC.Types.Int),
    
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'UnitAmountDecimal :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData']
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData']
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData']
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData']
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
    -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
    -> Bool)
-> Eq PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData' where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Value
toJSON PostCustomersCustomerSubscriptionsRequestBodyItems'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..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Currency PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"product" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Product PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"recurring" Text
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"tax_behavior" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior PostCustomersCustomerSubscriptionsRequestBodyItems'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..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'UnitAmount PostCustomersCustomerSubscriptionsRequestBodyItems'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..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'UnitAmountDecimal PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Encoding
toEncoding PostCustomersCustomerSubscriptionsRequestBodyItems'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..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Currency PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"product" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Product PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"recurring" Text
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"tax_behavior" Text
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior PostCustomersCustomerSubscriptionsRequestBodyItems'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..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'UnitAmount PostCustomersCustomerSubscriptionsRequestBodyItems'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..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
-> Maybe Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'UnitAmountDecimal PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
obj))))))
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
parseJSON = String
-> (Object
    -> Parser
         PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData')
-> Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'" (\Object
obj -> ((((((Text
 -> Text
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
 -> Maybe
      PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
 -> Maybe Int
 -> Maybe Text
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData')
-> Parser
     (Text
      -> Text
      -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
      -> Maybe Int
      -> Maybe Text
      -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Text
-> Text
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> Maybe Int
-> Maybe Text
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData' Parser
  (Text
   -> Text
   -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
   -> Maybe Int
   -> Maybe Text
   -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData')
-> Parser Text
-> Parser
     (Text
      -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
      -> Maybe Int
      -> Maybe Text
      -> PostCustomersCustomerSubscriptionsRequestBodyItems'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
  (Text
   -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
   -> Maybe Int
   -> Maybe Text
   -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData')
-> Parser Text
-> Parser
     (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
      -> Maybe
           PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
      -> Maybe Int
      -> Maybe Text
      -> PostCustomersCustomerSubscriptionsRequestBodyItems'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
"product")) Parser
  (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
   -> Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
   -> Maybe Int
   -> Maybe Text
   -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData')
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
      -> Maybe Int
      -> Maybe Text
      -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"recurring")) Parser
  (Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
   -> Maybe Int
   -> Maybe Text
   -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData')
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior')
-> Parser
     (Maybe Int
      -> Maybe Text
      -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"tax_behavior")) Parser
  (Maybe Int
   -> Maybe Text
   -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData')
-> Parser (Maybe Int)
-> Parser
     (Maybe Text
      -> PostCustomersCustomerSubscriptionsRequestBodyItems'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
   -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData')
-> Parser (Maybe Text)
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'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"))
mkPostCustomersCustomerSubscriptionsRequestBodyItems'PriceData' ::
  
  Data.Text.Internal.Text ->
  
  Data.Text.Internal.Text ->
  
  PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring' ->
  PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
mkPostCustomersCustomerSubscriptionsRequestBodyItems'PriceData' :: Text
-> Text
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
mkPostCustomersCustomerSubscriptionsRequestBodyItems'PriceData' Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Currency Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Product PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring =
  PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData' :: Text
-> Text
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> Maybe
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> Maybe Int
-> Maybe Text
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'
    { postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Currency :: Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Currency = Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Currency,
      postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Product :: Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Product = Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Product,
      postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring = PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring,
      postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior :: Maybe
  PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior = Maybe
  PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'UnitAmount :: Maybe Int
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'UnitAmount = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'UnitAmountDecimal :: Maybe Text
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'UnitAmountDecimal = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }
data PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring' = PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
  { 
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval',
    
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'IntervalCount :: (GHC.Maybe.Maybe GHC.Types.Int)
  }
  deriving
    ( Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring']
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring']
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring']
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring']
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
    -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring' where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> Value
toJSON PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"interval" Text
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval PostCustomersCustomerSubscriptionsRequestBodyItems'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..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'IntervalCount PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> Encoding
toEncoding PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"interval" Text
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval PostCustomersCustomerSubscriptionsRequestBodyItems'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..= PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'IntervalCount PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
obj))
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
parseJSON = String
-> (Object
    -> Parser
         PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring')
-> Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'" (\Object
obj -> ((PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
 -> Maybe Int
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring')
-> Parser
     (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> Maybe Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring' Parser
  (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring')
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> Parser
     (Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"interval")) Parser
  (Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring')
-> Parser (Maybe Int)
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'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"))
mkPostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring' ::
  
  PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval' ->
  PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
mkPostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring' :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
mkPostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring' PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval =
  PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring' :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> Maybe Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'
    { postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval = PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval,
      postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'IntervalCount :: Maybe Int
postCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'IntervalCount = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
    }
data PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
  = 
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'Other Data.Aeson.Types.Internal.Value
  | 
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'Typed Data.Text.Internal.Text
  | 
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'EnumDay
  | 
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'EnumMonth
  | 
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'EnumWeek
  | 
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'EnumYear
  deriving (Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval']
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval']
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval']
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval']
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
    -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval' where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> Value
toJSON (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'Other Value
val) = Value
val
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'EnumDay) = Value
"day"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'EnumMonth) = Value
"month"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'EnumWeek) = Value
"week"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'EnumYear) = Value
"year"
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
parseJSON Value
val =
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'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" -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'EnumDay
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"month" -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'EnumMonth
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"week" -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'EnumWeek
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"year" -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'EnumYear
            | Bool
GHC.Base.otherwise -> Value
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'Recurring'Interval'Other Value
val
      )
data PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
  = 
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'Other Data.Aeson.Types.Internal.Value
  | 
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'Typed Data.Text.Internal.Text
  | 
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'EnumExclusive
  | 
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'EnumInclusive
  | 
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'EnumUnspecified
  deriving (Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior']
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior']
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior']
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior']
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
    -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior' where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> Value
toJSON (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'Other Value
val) = Value
val
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'EnumExclusive) = Value
"exclusive"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'EnumInclusive) = Value
"inclusive"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'EnumUnspecified) = Value
"unspecified"
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
parseJSON Value
val =
    PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'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" -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'EnumExclusive
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"inclusive" -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'EnumInclusive
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"unspecified" -> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'EnumUnspecified
            | Bool
GHC.Base.otherwise -> Value
-> PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'
PostCustomersCustomerSubscriptionsRequestBodyItems'PriceData'TaxBehavior'Other Value
val
      )
data PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
  = 
    PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'EmptyString
  | PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'ListTText ([Data.Text.Internal.Text])
  deriving (Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants]
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants]
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants]
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants]
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
    -> PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> Value
toJSON (PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'ListTText [Text]
a) = [Text] -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON [Text]
a
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'EmptyString) = Value
""
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
parseJSON Value
val =
    if
        | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"" -> PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'EmptyString
        | Bool
GHC.Base.otherwise -> case ([Text]
-> PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'ListTText ([Text]
 -> PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants)
-> Result [Text]
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'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
  PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched" of
          Data.Aeson.Types.Internal.Success PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
a -> PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
a
          Data.Aeson.Types.Internal.Error String
a -> String
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyItems'TaxRates'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a
data PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
  = 
    PostCustomersCustomerSubscriptionsRequestBodyMetadata'EmptyString
  | PostCustomersCustomerSubscriptionsRequestBodyMetadata'Object Data.Aeson.Types.Internal.Object
  deriving (Int
-> PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants]
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants]
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants]
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants]
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
 -> PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
    -> PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> Value
toJSON (PostCustomersCustomerSubscriptionsRequestBodyMetadata'Object Object
a) = Object -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Object
a
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
PostCustomersCustomerSubscriptionsRequestBodyMetadata'EmptyString) = Value
""
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
parseJSON Value
val =
    if
        | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"" -> PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
PostCustomersCustomerSubscriptionsRequestBodyMetadata'EmptyString
        | Bool
GHC.Base.otherwise -> case (Object
-> PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
PostCustomersCustomerSubscriptionsRequestBodyMetadata'Object (Object
 -> PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants)
-> Result Object
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Object
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result
  PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched" of
          Data.Aeson.Types.Internal.Success PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
a -> PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
a
          Data.Aeson.Types.Internal.Error String
a -> String
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyMetadata'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a
data PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
  = 
    PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'Other Data.Aeson.Types.Internal.Value
  | 
    PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'Typed Data.Text.Internal.Text
  | 
    PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'EnumAllowIncomplete
  | 
    PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'EnumDefaultIncomplete
  | 
    PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'EnumErrorIfIncomplete
  | 
    PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'EnumPendingIfIncomplete
  deriving (Int
-> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior']
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior']
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior']
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior']
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
 -> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
    -> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
    -> Bool)
-> Eq PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior' where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> Value
toJSON (PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'Other Value
val) = Value
val
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'EnumAllowIncomplete) = Value
"allow_incomplete"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'EnumDefaultIncomplete) = Value
"default_incomplete"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'EnumErrorIfIncomplete) = Value
"error_if_incomplete"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'EnumPendingIfIncomplete) = Value
"pending_if_incomplete"
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
parseJSON Value
val =
    PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
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
"allow_incomplete" -> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'EnumAllowIncomplete
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"default_incomplete" -> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'EnumDefaultIncomplete
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"error_if_incomplete" -> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'EnumErrorIfIncomplete
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"pending_if_incomplete" -> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'EnumPendingIfIncomplete
            | Bool
GHC.Base.otherwise -> Value
-> PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'
PostCustomersCustomerSubscriptionsRequestBodyPaymentBehavior'Other Value
val
      )
data PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1 = PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
  { 
    PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval',
    
    PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1IntervalCount :: (GHC.Maybe.Maybe GHC.Types.Int)
  }
  deriving
    ( Int
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1]
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1]
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1]
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1]
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
 -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
    -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1 where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> Value
toJSON PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"interval" Text
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
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..= PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1IntervalCount PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> Encoding
toEncoding PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"interval" Text
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
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..= PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> Maybe Int
postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1IntervalCount PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
obj))
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1 where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
parseJSON = String
-> (Object
    -> Parser
         PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1)
-> Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1" (\Object
obj -> ((PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
 -> Maybe Int
 -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1)
-> Parser
     (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
      -> Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> Maybe Int
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1 Parser
  (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
   -> Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1)
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> Parser
     (Maybe Int
      -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"interval")) Parser
  (Maybe Int
   -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1)
-> Parser (Maybe Int)
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
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"))
mkPostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1 ::
  
  PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval' ->
  PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
mkPostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1 :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
mkPostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1 PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval =
  PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1 :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> Maybe Int
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
    { postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval = PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval,
      postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1IntervalCount :: Maybe Int
postCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1IntervalCount = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
    }
data PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
  = 
    PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'Other Data.Aeson.Types.Internal.Value
  | 
    PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'Typed Data.Text.Internal.Text
  | 
    PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'EnumDay
  | 
    PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'EnumMonth
  | 
    PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'EnumWeek
  | 
    PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'EnumYear
  deriving (Int
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval']
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval']
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval']
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval']
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
 -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
    -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval' where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> Value
toJSON (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'Other Value
val) = Value
val
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'EnumDay) = Value
"day"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'EnumMonth) = Value
"month"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'EnumWeek) = Value
"week"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'EnumYear) = Value
"year"
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
parseJSON Value
val =
    PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
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" -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'EnumDay
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"month" -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'EnumMonth
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"week" -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'EnumWeek
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"year" -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'EnumYear
            | Bool
GHC.Base.otherwise -> Value
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1Interval'Other Value
val
      )
data PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
  = 
    PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'EmptyString
  | PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1 PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
  deriving (Int
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants]
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants]
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants]
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants]
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
 -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
    -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> Value
toJSON (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1 PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
a) = PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
a
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'EmptyString) = Value
""
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
parseJSON Value
val =
    if
        | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"" -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'EmptyString
        | Bool
GHC.Base.otherwise -> case (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1 (PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
 -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants)
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'OneOf1
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result
  PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched" of
          Data.Aeson.Types.Internal.Success PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
a -> PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
a
          Data.Aeson.Types.Internal.Error String
a -> String
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyPendingInvoiceItemInterval'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a
data PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
  = 
    PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'Other Data.Aeson.Types.Internal.Value
  | 
    PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'Typed Data.Text.Internal.Text
  | 
    PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'EnumAlwaysInvoice
  | 
    PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'EnumCreateProrations
  | 
    PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'EnumNone
  deriving (Int
-> PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior']
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior']
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior']
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior']
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
 -> PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
    -> PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior' where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> Value
toJSON (PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'Other Value
val) = Value
val
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'EnumAlwaysInvoice) = Value
"always_invoice"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'EnumCreateProrations) = Value
"create_prorations"
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'EnumNone) = Value
"none"
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
parseJSON Value
val =
    PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
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
"always_invoice" -> PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'EnumAlwaysInvoice
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"create_prorations" -> PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'EnumCreateProrations
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"none" -> PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'EnumNone
            | Bool
GHC.Base.otherwise -> Value
-> PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'
PostCustomersCustomerSubscriptionsRequestBodyProrationBehavior'Other Value
val
      )
data PostCustomersCustomerSubscriptionsRequestBodyTransferData' = PostCustomersCustomerSubscriptionsRequestBodyTransferData'
  { 
    PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> Maybe Double
postCustomersCustomerSubscriptionsRequestBodyTransferData'AmountPercent :: (GHC.Maybe.Maybe GHC.Types.Double),
    
    PostCustomersCustomerSubscriptionsRequestBodyTransferData' -> Text
postCustomersCustomerSubscriptionsRequestBodyTransferData'Destination :: Data.Text.Internal.Text
  }
  deriving
    ( Int
-> PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyTransferData']
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyTransferData'
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyTransferData'
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyTransferData']
    -> String -> String)
-> Show PostCustomersCustomerSubscriptionsRequestBodyTransferData'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyTransferData']
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyTransferData']
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyTransferData'
 -> PostCustomersCustomerSubscriptionsRequestBodyTransferData'
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyTransferData'
    -> PostCustomersCustomerSubscriptionsRequestBodyTransferData'
    -> Bool)
-> Eq PostCustomersCustomerSubscriptionsRequestBodyTransferData'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyTransferData' where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyTransferData' -> Value
toJSON PostCustomersCustomerSubscriptionsRequestBodyTransferData'
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..= PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> Maybe Double
postCustomersCustomerSubscriptionsRequestBodyTransferData'AmountPercent PostCustomersCustomerSubscriptionsRequestBodyTransferData'
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..= PostCustomersCustomerSubscriptionsRequestBodyTransferData' -> Text
postCustomersCustomerSubscriptionsRequestBodyTransferData'Destination PostCustomersCustomerSubscriptionsRequestBodyTransferData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> Encoding
toEncoding PostCustomersCustomerSubscriptionsRequestBodyTransferData'
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..= PostCustomersCustomerSubscriptionsRequestBodyTransferData'
-> Maybe Double
postCustomersCustomerSubscriptionsRequestBodyTransferData'AmountPercent PostCustomersCustomerSubscriptionsRequestBodyTransferData'
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..= PostCustomersCustomerSubscriptionsRequestBodyTransferData' -> Text
postCustomersCustomerSubscriptionsRequestBodyTransferData'Destination PostCustomersCustomerSubscriptionsRequestBodyTransferData'
obj))
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyTransferData' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyTransferData'
parseJSON = String
-> (Object
    -> Parser
         PostCustomersCustomerSubscriptionsRequestBodyTransferData')
-> Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyTransferData'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerSubscriptionsRequestBodyTransferData'" (\Object
obj -> ((Maybe Double
 -> Text
 -> PostCustomersCustomerSubscriptionsRequestBodyTransferData')
-> Parser
     (Maybe Double
      -> Text
      -> PostCustomersCustomerSubscriptionsRequestBodyTransferData')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Double
-> Text
-> PostCustomersCustomerSubscriptionsRequestBodyTransferData'
PostCustomersCustomerSubscriptionsRequestBodyTransferData' Parser
  (Maybe Double
   -> Text
   -> PostCustomersCustomerSubscriptionsRequestBodyTransferData')
-> Parser (Maybe Double)
-> Parser
     (Text
      -> PostCustomersCustomerSubscriptionsRequestBodyTransferData')
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
   -> PostCustomersCustomerSubscriptionsRequestBodyTransferData')
-> Parser Text
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyTransferData'
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"))
mkPostCustomersCustomerSubscriptionsRequestBodyTransferData' ::
  
  Data.Text.Internal.Text ->
  PostCustomersCustomerSubscriptionsRequestBodyTransferData'
mkPostCustomersCustomerSubscriptionsRequestBodyTransferData' :: Text -> PostCustomersCustomerSubscriptionsRequestBodyTransferData'
mkPostCustomersCustomerSubscriptionsRequestBodyTransferData' Text
postCustomersCustomerSubscriptionsRequestBodyTransferData'Destination =
  PostCustomersCustomerSubscriptionsRequestBodyTransferData' :: Maybe Double
-> Text
-> PostCustomersCustomerSubscriptionsRequestBodyTransferData'
PostCustomersCustomerSubscriptionsRequestBodyTransferData'
    { postCustomersCustomerSubscriptionsRequestBodyTransferData'AmountPercent :: Maybe Double
postCustomersCustomerSubscriptionsRequestBodyTransferData'AmountPercent = Maybe Double
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSubscriptionsRequestBodyTransferData'Destination :: Text
postCustomersCustomerSubscriptionsRequestBodyTransferData'Destination = Text
postCustomersCustomerSubscriptionsRequestBodyTransferData'Destination
    }
data PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
  = 
    PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Now
  | PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Int GHC.Types.Int
  deriving (Int
-> PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> String
-> String
[PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants]
-> String -> String
PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> String
(Int
 -> PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
 -> String
 -> String)
-> (PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
    -> String)
-> ([PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants]
    -> String -> String)
-> Show
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants]
-> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants]
-> String -> String
show :: PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> String
$cshow :: PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> Bool
(PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
 -> PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
 -> Bool)
-> (PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
    -> PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
    -> Bool)
-> Eq
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> Bool
$c/= :: PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> Bool
== :: PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> Bool
$c== :: PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants where
  toJSON :: PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> Value
toJSON (PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Int Int
a) = Int -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Int
a
  toJSON (PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Now) = Value
"now"
instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
parseJSON Value
val =
    if
        | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"now" -> PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Now
        | Bool
GHC.Base.otherwise -> case (Int
-> PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Int (Int
 -> PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants)
-> Result Int
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Int
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result
  PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched" of
          Data.Aeson.Types.Internal.Success PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
a -> PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
a
          Data.Aeson.Types.Internal.Error String
a -> String
-> Parser
     PostCustomersCustomerSubscriptionsRequestBodyTrialEnd'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a
data PostCustomersCustomerSubscriptionsResponse
  = 
    PostCustomersCustomerSubscriptionsResponseError GHC.Base.String
  | 
    PostCustomersCustomerSubscriptionsResponse200 Subscription
  | 
    PostCustomersCustomerSubscriptionsResponseDefault Error
  deriving (Int
-> PostCustomersCustomerSubscriptionsResponse -> String -> String
[PostCustomersCustomerSubscriptionsResponse] -> String -> String
PostCustomersCustomerSubscriptionsResponse -> String
(Int
 -> PostCustomersCustomerSubscriptionsResponse -> String -> String)
-> (PostCustomersCustomerSubscriptionsResponse -> String)
-> ([PostCustomersCustomerSubscriptionsResponse]
    -> String -> String)
-> Show PostCustomersCustomerSubscriptionsResponse
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSubscriptionsResponse] -> String -> String
$cshowList :: [PostCustomersCustomerSubscriptionsResponse] -> String -> String
show :: PostCustomersCustomerSubscriptionsResponse -> String
$cshow :: PostCustomersCustomerSubscriptionsResponse -> String
showsPrec :: Int
-> PostCustomersCustomerSubscriptionsResponse -> String -> String
$cshowsPrec :: Int
-> PostCustomersCustomerSubscriptionsResponse -> String -> String
GHC.Show.Show, PostCustomersCustomerSubscriptionsResponse
-> PostCustomersCustomerSubscriptionsResponse -> Bool
(PostCustomersCustomerSubscriptionsResponse
 -> PostCustomersCustomerSubscriptionsResponse -> Bool)
-> (PostCustomersCustomerSubscriptionsResponse
    -> PostCustomersCustomerSubscriptionsResponse -> Bool)
-> Eq PostCustomersCustomerSubscriptionsResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSubscriptionsResponse
-> PostCustomersCustomerSubscriptionsResponse -> Bool
$c/= :: PostCustomersCustomerSubscriptionsResponse
-> PostCustomersCustomerSubscriptionsResponse -> Bool
== :: PostCustomersCustomerSubscriptionsResponse
-> PostCustomersCustomerSubscriptionsResponse -> Bool
$c== :: PostCustomersCustomerSubscriptionsResponse
-> PostCustomersCustomerSubscriptionsResponse -> Bool
GHC.Classes.Eq)