{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module StripeAPI.Types.SubscriptionSchedulePhaseConfiguration where
import qualified Control.Monad.Fail
import qualified Data.Aeson
import qualified Data.Aeson as Data.Aeson.Encoding.Internal
import qualified Data.Aeson as Data.Aeson.Types
import qualified Data.Aeson as Data.Aeson.Types.FromJSON
import qualified Data.Aeson as Data.Aeson.Types.Internal
import qualified Data.Aeson as Data.Aeson.Types.ToJSON
import qualified Data.ByteString.Char8
import qualified Data.ByteString.Char8 as Data.ByteString.Internal
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 GHC.Base
import qualified GHC.Classes
import qualified GHC.Int
import qualified GHC.Show
import qualified GHC.Types
import qualified StripeAPI.Common
import StripeAPI.TypeAlias
import {-# SOURCE #-} StripeAPI.Types.Account
import {-# SOURCE #-} StripeAPI.Types.Coupon
import {-# SOURCE #-} StripeAPI.Types.DeletedCoupon
import {-# SOURCE #-} StripeAPI.Types.InvoiceSettingSubscriptionScheduleSetting
import {-# SOURCE #-} StripeAPI.Types.PaymentMethod
import {-# SOURCE #-} StripeAPI.Types.SchedulesPhaseAutomaticTax
import {-# SOURCE #-} StripeAPI.Types.SubscriptionBillingThresholds
import {-# SOURCE #-} StripeAPI.Types.SubscriptionScheduleAddInvoiceItem
import {-# SOURCE #-} StripeAPI.Types.SubscriptionScheduleConfigurationItem
import {-# SOURCE #-} StripeAPI.Types.SubscriptionTransferData
import {-# SOURCE #-} StripeAPI.Types.TaxRate
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe
data SubscriptionSchedulePhaseConfiguration = SubscriptionSchedulePhaseConfiguration
{
SubscriptionSchedulePhaseConfiguration
-> [SubscriptionScheduleAddInvoiceItem]
subscriptionSchedulePhaseConfigurationAddInvoiceItems :: ([SubscriptionScheduleAddInvoiceItem]),
SubscriptionSchedulePhaseConfiguration -> Maybe Double
subscriptionSchedulePhaseConfigurationApplicationFeePercent :: (GHC.Maybe.Maybe GHC.Types.Double),
SubscriptionSchedulePhaseConfiguration
-> Maybe SchedulesPhaseAutomaticTax
subscriptionSchedulePhaseConfigurationAutomaticTax :: (GHC.Maybe.Maybe SchedulesPhaseAutomaticTax),
SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
subscriptionSchedulePhaseConfigurationBillingCycleAnchor :: (GHC.Maybe.Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'),
SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
subscriptionSchedulePhaseConfigurationBillingThresholds :: (GHC.Maybe.Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'),
SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
subscriptionSchedulePhaseConfigurationCollectionMethod :: (GHC.Maybe.Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'),
SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
subscriptionSchedulePhaseConfigurationCoupon :: (GHC.Maybe.Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants),
SubscriptionSchedulePhaseConfiguration
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
subscriptionSchedulePhaseConfigurationDefaultPaymentMethod :: (GHC.Maybe.Maybe SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants),
SubscriptionSchedulePhaseConfiguration -> Maybe [TaxRate]
subscriptionSchedulePhaseConfigurationDefaultTaxRates :: (GHC.Maybe.Maybe ([TaxRate])),
SubscriptionSchedulePhaseConfiguration -> Int
subscriptionSchedulePhaseConfigurationEndDate :: GHC.Types.Int,
SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
subscriptionSchedulePhaseConfigurationInvoiceSettings :: (GHC.Maybe.Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'),
SubscriptionSchedulePhaseConfiguration
-> [SubscriptionScheduleConfigurationItem]
subscriptionSchedulePhaseConfigurationItems :: ([SubscriptionScheduleConfigurationItem]),
SubscriptionSchedulePhaseConfiguration
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
subscriptionSchedulePhaseConfigurationProrationBehavior :: SubscriptionSchedulePhaseConfigurationProrationBehavior',
SubscriptionSchedulePhaseConfiguration -> Int
subscriptionSchedulePhaseConfigurationStartDate :: GHC.Types.Int,
SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
subscriptionSchedulePhaseConfigurationTransferData :: (GHC.Maybe.Maybe SubscriptionSchedulePhaseConfigurationTransferData'),
SubscriptionSchedulePhaseConfiguration -> Maybe Int
subscriptionSchedulePhaseConfigurationTrialEnd :: (GHC.Maybe.Maybe GHC.Types.Int)
}
deriving
( Int -> SubscriptionSchedulePhaseConfiguration -> ShowS
[SubscriptionSchedulePhaseConfiguration] -> ShowS
SubscriptionSchedulePhaseConfiguration -> String
(Int -> SubscriptionSchedulePhaseConfiguration -> ShowS)
-> (SubscriptionSchedulePhaseConfiguration -> String)
-> ([SubscriptionSchedulePhaseConfiguration] -> ShowS)
-> Show SubscriptionSchedulePhaseConfiguration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionSchedulePhaseConfiguration] -> ShowS
$cshowList :: [SubscriptionSchedulePhaseConfiguration] -> ShowS
show :: SubscriptionSchedulePhaseConfiguration -> String
$cshow :: SubscriptionSchedulePhaseConfiguration -> String
showsPrec :: Int -> SubscriptionSchedulePhaseConfiguration -> ShowS
$cshowsPrec :: Int -> SubscriptionSchedulePhaseConfiguration -> ShowS
GHC.Show.Show,
SubscriptionSchedulePhaseConfiguration
-> SubscriptionSchedulePhaseConfiguration -> Bool
(SubscriptionSchedulePhaseConfiguration
-> SubscriptionSchedulePhaseConfiguration -> Bool)
-> (SubscriptionSchedulePhaseConfiguration
-> SubscriptionSchedulePhaseConfiguration -> Bool)
-> Eq SubscriptionSchedulePhaseConfiguration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionSchedulePhaseConfiguration
-> SubscriptionSchedulePhaseConfiguration -> Bool
$c/= :: SubscriptionSchedulePhaseConfiguration
-> SubscriptionSchedulePhaseConfiguration -> Bool
== :: SubscriptionSchedulePhaseConfiguration
-> SubscriptionSchedulePhaseConfiguration -> Bool
$c== :: SubscriptionSchedulePhaseConfiguration
-> SubscriptionSchedulePhaseConfiguration -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionSchedulePhaseConfiguration where
toJSON :: SubscriptionSchedulePhaseConfiguration -> Value
toJSON SubscriptionSchedulePhaseConfiguration
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"add_invoice_items" Text -> [SubscriptionScheduleAddInvoiceItem] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> [SubscriptionScheduleAddInvoiceItem]
subscriptionSchedulePhaseConfigurationAddInvoiceItems SubscriptionSchedulePhaseConfiguration
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..= SubscriptionSchedulePhaseConfiguration -> Maybe Double
subscriptionSchedulePhaseConfigurationApplicationFeePercent SubscriptionSchedulePhaseConfiguration
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"automatic_tax" Text -> Maybe SchedulesPhaseAutomaticTax -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe SchedulesPhaseAutomaticTax
subscriptionSchedulePhaseConfigurationAutomaticTax SubscriptionSchedulePhaseConfiguration
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"billing_cycle_anchor" Text
-> Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
subscriptionSchedulePhaseConfigurationBillingCycleAnchor SubscriptionSchedulePhaseConfiguration
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"billing_thresholds" Text
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
subscriptionSchedulePhaseConfigurationBillingThresholds SubscriptionSchedulePhaseConfiguration
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"collection_method" Text
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
subscriptionSchedulePhaseConfigurationCollectionMethod SubscriptionSchedulePhaseConfiguration
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"coupon" Text
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
subscriptionSchedulePhaseConfigurationCoupon SubscriptionSchedulePhaseConfiguration
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"default_payment_method" Text
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
subscriptionSchedulePhaseConfigurationDefaultPaymentMethod SubscriptionSchedulePhaseConfiguration
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"default_tax_rates" Text -> Maybe [TaxRate] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration -> Maybe [TaxRate]
subscriptionSchedulePhaseConfigurationDefaultTaxRates SubscriptionSchedulePhaseConfiguration
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"end_date" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration -> Int
subscriptionSchedulePhaseConfigurationEndDate SubscriptionSchedulePhaseConfiguration
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"invoice_settings" Text
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
subscriptionSchedulePhaseConfigurationInvoiceSettings SubscriptionSchedulePhaseConfiguration
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"items" Text -> [SubscriptionScheduleConfigurationItem] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> [SubscriptionScheduleConfigurationItem]
subscriptionSchedulePhaseConfigurationItems SubscriptionSchedulePhaseConfiguration
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"proration_behavior" Text
-> SubscriptionSchedulePhaseConfigurationProrationBehavior' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
subscriptionSchedulePhaseConfigurationProrationBehavior SubscriptionSchedulePhaseConfiguration
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"start_date" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration -> Int
subscriptionSchedulePhaseConfigurationStartDate SubscriptionSchedulePhaseConfiguration
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"transfer_data" Text
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
subscriptionSchedulePhaseConfigurationTransferData SubscriptionSchedulePhaseConfiguration
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"trial_end" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration -> Maybe Int
subscriptionSchedulePhaseConfigurationTrialEnd SubscriptionSchedulePhaseConfiguration
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
toEncoding :: SubscriptionSchedulePhaseConfiguration -> Encoding
toEncoding SubscriptionSchedulePhaseConfiguration
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"add_invoice_items" Text -> [SubscriptionScheduleAddInvoiceItem] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> [SubscriptionScheduleAddInvoiceItem]
subscriptionSchedulePhaseConfigurationAddInvoiceItems SubscriptionSchedulePhaseConfiguration
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..= SubscriptionSchedulePhaseConfiguration -> Maybe Double
subscriptionSchedulePhaseConfigurationApplicationFeePercent SubscriptionSchedulePhaseConfiguration
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"automatic_tax" Text -> Maybe SchedulesPhaseAutomaticTax -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe SchedulesPhaseAutomaticTax
subscriptionSchedulePhaseConfigurationAutomaticTax SubscriptionSchedulePhaseConfiguration
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"billing_cycle_anchor" Text
-> Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
subscriptionSchedulePhaseConfigurationBillingCycleAnchor SubscriptionSchedulePhaseConfiguration
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"billing_thresholds" Text
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
subscriptionSchedulePhaseConfigurationBillingThresholds SubscriptionSchedulePhaseConfiguration
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"collection_method" Text
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
subscriptionSchedulePhaseConfigurationCollectionMethod SubscriptionSchedulePhaseConfiguration
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"coupon" Text
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
subscriptionSchedulePhaseConfigurationCoupon SubscriptionSchedulePhaseConfiguration
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"default_payment_method" Text
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
subscriptionSchedulePhaseConfigurationDefaultPaymentMethod SubscriptionSchedulePhaseConfiguration
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"default_tax_rates" Text -> Maybe [TaxRate] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration -> Maybe [TaxRate]
subscriptionSchedulePhaseConfigurationDefaultTaxRates SubscriptionSchedulePhaseConfiguration
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"end_date" Text -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration -> Int
subscriptionSchedulePhaseConfigurationEndDate SubscriptionSchedulePhaseConfiguration
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"invoice_settings" Text
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
subscriptionSchedulePhaseConfigurationInvoiceSettings SubscriptionSchedulePhaseConfiguration
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"items" Text -> [SubscriptionScheduleConfigurationItem] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> [SubscriptionScheduleConfigurationItem]
subscriptionSchedulePhaseConfigurationItems SubscriptionSchedulePhaseConfiguration
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"proration_behavior" Text
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
subscriptionSchedulePhaseConfigurationProrationBehavior SubscriptionSchedulePhaseConfiguration
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"start_date" Text -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration -> Int
subscriptionSchedulePhaseConfigurationStartDate SubscriptionSchedulePhaseConfiguration
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"transfer_data" Text
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
subscriptionSchedulePhaseConfigurationTransferData SubscriptionSchedulePhaseConfiguration
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"trial_end" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfiguration -> Maybe Int
subscriptionSchedulePhaseConfigurationTrialEnd SubscriptionSchedulePhaseConfiguration
obj))))))))))))))))
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionSchedulePhaseConfiguration where
parseJSON :: Value -> Parser SubscriptionSchedulePhaseConfiguration
parseJSON = String
-> (Object -> Parser SubscriptionSchedulePhaseConfiguration)
-> Value
-> Parser SubscriptionSchedulePhaseConfiguration
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"SubscriptionSchedulePhaseConfiguration" (\Object
obj -> (((((((((((((((([SubscriptionScheduleAddInvoiceItem]
-> Maybe Double
-> Maybe SchedulesPhaseAutomaticTax
-> Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
-> Parser
([SubscriptionScheduleAddInvoiceItem]
-> Maybe Double
-> Maybe SchedulesPhaseAutomaticTax
-> Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure [SubscriptionScheduleAddInvoiceItem]
-> Maybe Double
-> Maybe SchedulesPhaseAutomaticTax
-> Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration
SubscriptionSchedulePhaseConfiguration Parser
([SubscriptionScheduleAddInvoiceItem]
-> Maybe Double
-> Maybe SchedulesPhaseAutomaticTax
-> Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
-> Parser [SubscriptionScheduleAddInvoiceItem]
-> Parser
(Maybe Double
-> Maybe SchedulesPhaseAutomaticTax
-> Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser [SubscriptionScheduleAddInvoiceItem]
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"add_invoice_items")) Parser
(Maybe Double
-> Maybe SchedulesPhaseAutomaticTax
-> Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
-> Parser (Maybe Double)
-> Parser
(Maybe SchedulesPhaseAutomaticTax
-> Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
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 SchedulesPhaseAutomaticTax
-> Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
-> Parser (Maybe SchedulesPhaseAutomaticTax)
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SchedulesPhaseAutomaticTax)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"automatic_tax")) Parser
(Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor')
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"billing_cycle_anchor")) Parser
(Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds')
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"billing_thresholds")) Parser
(Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod')
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"collection_method")) Parser
(Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants)
-> Parser
(Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"coupon")) Parser
(Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
-> Parser
(Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants)
-> Parser
(Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
(Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"default_payment_method")) Parser
(Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
-> Parser (Maybe [TaxRate])
-> Parser
(Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [TaxRate])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"default_tax_rates")) Parser
(Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
-> Parser Int
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
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
"end_date")) Parser
(Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings')
-> Parser
([SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"invoice_settings")) Parser
([SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
-> Parser [SubscriptionScheduleConfigurationItem]
-> Parser
(SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser [SubscriptionScheduleConfigurationItem]
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"items")) Parser
(SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
-> Parser SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Parser
(Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser SubscriptionSchedulePhaseConfigurationProrationBehavior'
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"proration_behavior")) Parser
(Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration)
-> Parser Int
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int -> SubscriptionSchedulePhaseConfiguration)
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
"start_date")) Parser
(Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int -> SubscriptionSchedulePhaseConfiguration)
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationTransferData')
-> Parser (Maybe Int -> SubscriptionSchedulePhaseConfiguration)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
(Maybe SubscriptionSchedulePhaseConfigurationTransferData')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"transfer_data")) Parser (Maybe Int -> SubscriptionSchedulePhaseConfiguration)
-> Parser (Maybe Int)
-> Parser SubscriptionSchedulePhaseConfiguration
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"trial_end"))
mkSubscriptionSchedulePhaseConfiguration ::
[SubscriptionScheduleAddInvoiceItem] ->
GHC.Types.Int ->
[SubscriptionScheduleConfigurationItem] ->
SubscriptionSchedulePhaseConfigurationProrationBehavior' ->
GHC.Types.Int ->
SubscriptionSchedulePhaseConfiguration
mkSubscriptionSchedulePhaseConfiguration :: [SubscriptionScheduleAddInvoiceItem]
-> Int
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> SubscriptionSchedulePhaseConfiguration
mkSubscriptionSchedulePhaseConfiguration [SubscriptionScheduleAddInvoiceItem]
subscriptionSchedulePhaseConfigurationAddInvoiceItems Int
subscriptionSchedulePhaseConfigurationEndDate [SubscriptionScheduleConfigurationItem]
subscriptionSchedulePhaseConfigurationItems SubscriptionSchedulePhaseConfigurationProrationBehavior'
subscriptionSchedulePhaseConfigurationProrationBehavior Int
subscriptionSchedulePhaseConfigurationStartDate =
SubscriptionSchedulePhaseConfiguration :: [SubscriptionScheduleAddInvoiceItem]
-> Maybe Double
-> Maybe SchedulesPhaseAutomaticTax
-> Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Maybe [TaxRate]
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> [SubscriptionScheduleConfigurationItem]
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Int
-> Maybe SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe Int
-> SubscriptionSchedulePhaseConfiguration
SubscriptionSchedulePhaseConfiguration
{ subscriptionSchedulePhaseConfigurationAddInvoiceItems :: [SubscriptionScheduleAddInvoiceItem]
subscriptionSchedulePhaseConfigurationAddInvoiceItems = [SubscriptionScheduleAddInvoiceItem]
subscriptionSchedulePhaseConfigurationAddInvoiceItems,
subscriptionSchedulePhaseConfigurationApplicationFeePercent :: Maybe Double
subscriptionSchedulePhaseConfigurationApplicationFeePercent = Maybe Double
forall a. Maybe a
GHC.Maybe.Nothing,
subscriptionSchedulePhaseConfigurationAutomaticTax :: Maybe SchedulesPhaseAutomaticTax
subscriptionSchedulePhaseConfigurationAutomaticTax = Maybe SchedulesPhaseAutomaticTax
forall a. Maybe a
GHC.Maybe.Nothing,
subscriptionSchedulePhaseConfigurationBillingCycleAnchor :: Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
subscriptionSchedulePhaseConfigurationBillingCycleAnchor = Maybe SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
forall a. Maybe a
GHC.Maybe.Nothing,
subscriptionSchedulePhaseConfigurationBillingThresholds :: Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
subscriptionSchedulePhaseConfigurationBillingThresholds = Maybe SubscriptionSchedulePhaseConfigurationBillingThresholds'
forall a. Maybe a
GHC.Maybe.Nothing,
subscriptionSchedulePhaseConfigurationCollectionMethod :: Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
subscriptionSchedulePhaseConfigurationCollectionMethod = Maybe SubscriptionSchedulePhaseConfigurationCollectionMethod'
forall a. Maybe a
GHC.Maybe.Nothing,
subscriptionSchedulePhaseConfigurationCoupon :: Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
subscriptionSchedulePhaseConfigurationCoupon = Maybe SubscriptionSchedulePhaseConfigurationCoupon'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
subscriptionSchedulePhaseConfigurationDefaultPaymentMethod :: Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
subscriptionSchedulePhaseConfigurationDefaultPaymentMethod = Maybe
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
subscriptionSchedulePhaseConfigurationDefaultTaxRates :: Maybe [TaxRate]
subscriptionSchedulePhaseConfigurationDefaultTaxRates = Maybe [TaxRate]
forall a. Maybe a
GHC.Maybe.Nothing,
subscriptionSchedulePhaseConfigurationEndDate :: Int
subscriptionSchedulePhaseConfigurationEndDate = Int
subscriptionSchedulePhaseConfigurationEndDate,
subscriptionSchedulePhaseConfigurationInvoiceSettings :: Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
subscriptionSchedulePhaseConfigurationInvoiceSettings = Maybe SubscriptionSchedulePhaseConfigurationInvoiceSettings'
forall a. Maybe a
GHC.Maybe.Nothing,
subscriptionSchedulePhaseConfigurationItems :: [SubscriptionScheduleConfigurationItem]
subscriptionSchedulePhaseConfigurationItems = [SubscriptionScheduleConfigurationItem]
subscriptionSchedulePhaseConfigurationItems,
subscriptionSchedulePhaseConfigurationProrationBehavior :: SubscriptionSchedulePhaseConfigurationProrationBehavior'
subscriptionSchedulePhaseConfigurationProrationBehavior = SubscriptionSchedulePhaseConfigurationProrationBehavior'
subscriptionSchedulePhaseConfigurationProrationBehavior,
subscriptionSchedulePhaseConfigurationStartDate :: Int
subscriptionSchedulePhaseConfigurationStartDate = Int
subscriptionSchedulePhaseConfigurationStartDate,
subscriptionSchedulePhaseConfigurationTransferData :: Maybe SubscriptionSchedulePhaseConfigurationTransferData'
subscriptionSchedulePhaseConfigurationTransferData = Maybe SubscriptionSchedulePhaseConfigurationTransferData'
forall a. Maybe a
GHC.Maybe.Nothing,
subscriptionSchedulePhaseConfigurationTrialEnd :: Maybe Int
subscriptionSchedulePhaseConfigurationTrialEnd = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
}
data SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
=
SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'Other Data.Aeson.Types.Internal.Value
|
SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'Typed Data.Text.Internal.Text
|
SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'EnumAutomatic
|
SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'EnumPhaseStart
deriving (Int
-> SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> ShowS
[SubscriptionSchedulePhaseConfigurationBillingCycleAnchor']
-> ShowS
SubscriptionSchedulePhaseConfigurationBillingCycleAnchor' -> String
(Int
-> SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> ShowS)
-> (SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> String)
-> ([SubscriptionSchedulePhaseConfigurationBillingCycleAnchor']
-> ShowS)
-> Show SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionSchedulePhaseConfigurationBillingCycleAnchor']
-> ShowS
$cshowList :: [SubscriptionSchedulePhaseConfigurationBillingCycleAnchor']
-> ShowS
show :: SubscriptionSchedulePhaseConfigurationBillingCycleAnchor' -> String
$cshow :: SubscriptionSchedulePhaseConfigurationBillingCycleAnchor' -> String
showsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> ShowS
$cshowsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> ShowS
GHC.Show.Show, SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Bool
(SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Bool)
-> (SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Bool)
-> Eq SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Bool
$c/= :: SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Bool
== :: SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Bool
$c== :: SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionSchedulePhaseConfigurationBillingCycleAnchor' where
toJSON :: SubscriptionSchedulePhaseConfigurationBillingCycleAnchor' -> Value
toJSON (SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'Other Value
val) = Value
val
toJSON (SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'EnumAutomatic) = Value
"automatic"
toJSON (SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'EnumPhaseStart) = Value
"phase_start"
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionSchedulePhaseConfigurationBillingCycleAnchor' where
parseJSON :: Value
-> Parser SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
parseJSON Value
val =
SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
-> Parser SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
( if
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"automatic" -> SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'EnumAutomatic
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"phase_start" -> SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'EnumPhaseStart
| Bool
GHC.Base.otherwise -> Value -> SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'
SubscriptionSchedulePhaseConfigurationBillingCycleAnchor'Other Value
val
)
data SubscriptionSchedulePhaseConfigurationBillingThresholds' = SubscriptionSchedulePhaseConfigurationBillingThresholds'
{
SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe Int
subscriptionSchedulePhaseConfigurationBillingThresholds'AmountGte :: (GHC.Maybe.Maybe GHC.Types.Int),
SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe Bool
subscriptionSchedulePhaseConfigurationBillingThresholds'ResetBillingCycleAnchor :: (GHC.Maybe.Maybe GHC.Types.Bool)
}
deriving
( Int
-> SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> ShowS
[SubscriptionSchedulePhaseConfigurationBillingThresholds'] -> ShowS
SubscriptionSchedulePhaseConfigurationBillingThresholds' -> String
(Int
-> SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> ShowS)
-> (SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> String)
-> ([SubscriptionSchedulePhaseConfigurationBillingThresholds']
-> ShowS)
-> Show SubscriptionSchedulePhaseConfigurationBillingThresholds'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionSchedulePhaseConfigurationBillingThresholds'] -> ShowS
$cshowList :: [SubscriptionSchedulePhaseConfigurationBillingThresholds'] -> ShowS
show :: SubscriptionSchedulePhaseConfigurationBillingThresholds' -> String
$cshow :: SubscriptionSchedulePhaseConfigurationBillingThresholds' -> String
showsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> ShowS
$cshowsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> ShowS
GHC.Show.Show,
SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> SubscriptionSchedulePhaseConfigurationBillingThresholds' -> Bool
(SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Bool)
-> (SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Bool)
-> Eq SubscriptionSchedulePhaseConfigurationBillingThresholds'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> SubscriptionSchedulePhaseConfigurationBillingThresholds' -> Bool
$c/= :: SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> SubscriptionSchedulePhaseConfigurationBillingThresholds' -> Bool
== :: SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> SubscriptionSchedulePhaseConfigurationBillingThresholds' -> Bool
$c== :: SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> SubscriptionSchedulePhaseConfigurationBillingThresholds' -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionSchedulePhaseConfigurationBillingThresholds' where
toJSON :: SubscriptionSchedulePhaseConfigurationBillingThresholds' -> Value
toJSON SubscriptionSchedulePhaseConfigurationBillingThresholds'
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..= SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe Int
subscriptionSchedulePhaseConfigurationBillingThresholds'AmountGte SubscriptionSchedulePhaseConfigurationBillingThresholds'
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..= SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe Bool
subscriptionSchedulePhaseConfigurationBillingThresholds'ResetBillingCycleAnchor SubscriptionSchedulePhaseConfigurationBillingThresholds'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
toEncoding :: SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Encoding
toEncoding SubscriptionSchedulePhaseConfigurationBillingThresholds'
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..= SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe Int
subscriptionSchedulePhaseConfigurationBillingThresholds'AmountGte SubscriptionSchedulePhaseConfigurationBillingThresholds'
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..= SubscriptionSchedulePhaseConfigurationBillingThresholds'
-> Maybe Bool
subscriptionSchedulePhaseConfigurationBillingThresholds'ResetBillingCycleAnchor SubscriptionSchedulePhaseConfigurationBillingThresholds'
obj))
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionSchedulePhaseConfigurationBillingThresholds' where
parseJSON :: Value
-> Parser SubscriptionSchedulePhaseConfigurationBillingThresholds'
parseJSON = String
-> (Object
-> Parser SubscriptionSchedulePhaseConfigurationBillingThresholds')
-> Value
-> Parser SubscriptionSchedulePhaseConfigurationBillingThresholds'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"SubscriptionSchedulePhaseConfigurationBillingThresholds'" (\Object
obj -> ((Maybe Int
-> Maybe Bool
-> SubscriptionSchedulePhaseConfigurationBillingThresholds')
-> Parser
(Maybe Int
-> Maybe Bool
-> SubscriptionSchedulePhaseConfigurationBillingThresholds')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Int
-> Maybe Bool
-> SubscriptionSchedulePhaseConfigurationBillingThresholds'
SubscriptionSchedulePhaseConfigurationBillingThresholds' Parser
(Maybe Int
-> Maybe Bool
-> SubscriptionSchedulePhaseConfigurationBillingThresholds')
-> Parser (Maybe Int)
-> Parser
(Maybe Bool
-> SubscriptionSchedulePhaseConfigurationBillingThresholds')
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
-> SubscriptionSchedulePhaseConfigurationBillingThresholds')
-> Parser (Maybe Bool)
-> Parser SubscriptionSchedulePhaseConfigurationBillingThresholds'
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"))
mkSubscriptionSchedulePhaseConfigurationBillingThresholds' :: SubscriptionSchedulePhaseConfigurationBillingThresholds'
mkSubscriptionSchedulePhaseConfigurationBillingThresholds' :: SubscriptionSchedulePhaseConfigurationBillingThresholds'
mkSubscriptionSchedulePhaseConfigurationBillingThresholds' =
SubscriptionSchedulePhaseConfigurationBillingThresholds' :: Maybe Int
-> Maybe Bool
-> SubscriptionSchedulePhaseConfigurationBillingThresholds'
SubscriptionSchedulePhaseConfigurationBillingThresholds'
{ subscriptionSchedulePhaseConfigurationBillingThresholds'AmountGte :: Maybe Int
subscriptionSchedulePhaseConfigurationBillingThresholds'AmountGte = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
subscriptionSchedulePhaseConfigurationBillingThresholds'ResetBillingCycleAnchor :: Maybe Bool
subscriptionSchedulePhaseConfigurationBillingThresholds'ResetBillingCycleAnchor = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
}
data SubscriptionSchedulePhaseConfigurationCollectionMethod'
=
SubscriptionSchedulePhaseConfigurationCollectionMethod'Other Data.Aeson.Types.Internal.Value
|
SubscriptionSchedulePhaseConfigurationCollectionMethod'Typed Data.Text.Internal.Text
|
SubscriptionSchedulePhaseConfigurationCollectionMethod'EnumChargeAutomatically
|
SubscriptionSchedulePhaseConfigurationCollectionMethod'EnumSendInvoice
deriving (Int
-> SubscriptionSchedulePhaseConfigurationCollectionMethod' -> ShowS
[SubscriptionSchedulePhaseConfigurationCollectionMethod'] -> ShowS
SubscriptionSchedulePhaseConfigurationCollectionMethod' -> String
(Int
-> SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> ShowS)
-> (SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> String)
-> ([SubscriptionSchedulePhaseConfigurationCollectionMethod']
-> ShowS)
-> Show SubscriptionSchedulePhaseConfigurationCollectionMethod'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionSchedulePhaseConfigurationCollectionMethod'] -> ShowS
$cshowList :: [SubscriptionSchedulePhaseConfigurationCollectionMethod'] -> ShowS
show :: SubscriptionSchedulePhaseConfigurationCollectionMethod' -> String
$cshow :: SubscriptionSchedulePhaseConfigurationCollectionMethod' -> String
showsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationCollectionMethod' -> ShowS
$cshowsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationCollectionMethod' -> ShowS
GHC.Show.Show, SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> SubscriptionSchedulePhaseConfigurationCollectionMethod' -> Bool
(SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> SubscriptionSchedulePhaseConfigurationCollectionMethod' -> Bool)
-> (SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> SubscriptionSchedulePhaseConfigurationCollectionMethod' -> Bool)
-> Eq SubscriptionSchedulePhaseConfigurationCollectionMethod'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> SubscriptionSchedulePhaseConfigurationCollectionMethod' -> Bool
$c/= :: SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> SubscriptionSchedulePhaseConfigurationCollectionMethod' -> Bool
== :: SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> SubscriptionSchedulePhaseConfigurationCollectionMethod' -> Bool
$c== :: SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> SubscriptionSchedulePhaseConfigurationCollectionMethod' -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionSchedulePhaseConfigurationCollectionMethod' where
toJSON :: SubscriptionSchedulePhaseConfigurationCollectionMethod' -> Value
toJSON (SubscriptionSchedulePhaseConfigurationCollectionMethod'Other Value
val) = Value
val
toJSON (SubscriptionSchedulePhaseConfigurationCollectionMethod'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (SubscriptionSchedulePhaseConfigurationCollectionMethod'
SubscriptionSchedulePhaseConfigurationCollectionMethod'EnumChargeAutomatically) = Value
"charge_automatically"
toJSON (SubscriptionSchedulePhaseConfigurationCollectionMethod'
SubscriptionSchedulePhaseConfigurationCollectionMethod'EnumSendInvoice) = Value
"send_invoice"
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionSchedulePhaseConfigurationCollectionMethod' where
parseJSON :: Value
-> Parser SubscriptionSchedulePhaseConfigurationCollectionMethod'
parseJSON Value
val =
SubscriptionSchedulePhaseConfigurationCollectionMethod'
-> Parser SubscriptionSchedulePhaseConfigurationCollectionMethod'
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" -> SubscriptionSchedulePhaseConfigurationCollectionMethod'
SubscriptionSchedulePhaseConfigurationCollectionMethod'EnumChargeAutomatically
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"send_invoice" -> SubscriptionSchedulePhaseConfigurationCollectionMethod'
SubscriptionSchedulePhaseConfigurationCollectionMethod'EnumSendInvoice
| Bool
GHC.Base.otherwise -> Value -> SubscriptionSchedulePhaseConfigurationCollectionMethod'
SubscriptionSchedulePhaseConfigurationCollectionMethod'Other Value
val
)
data SubscriptionSchedulePhaseConfigurationCoupon'Variants
= SubscriptionSchedulePhaseConfigurationCoupon'Text Data.Text.Internal.Text
| SubscriptionSchedulePhaseConfigurationCoupon'Coupon Coupon
| SubscriptionSchedulePhaseConfigurationCoupon'DeletedCoupon DeletedCoupon
deriving (Int
-> SubscriptionSchedulePhaseConfigurationCoupon'Variants -> ShowS
[SubscriptionSchedulePhaseConfigurationCoupon'Variants] -> ShowS
SubscriptionSchedulePhaseConfigurationCoupon'Variants -> String
(Int
-> SubscriptionSchedulePhaseConfigurationCoupon'Variants -> ShowS)
-> (SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> String)
-> ([SubscriptionSchedulePhaseConfigurationCoupon'Variants]
-> ShowS)
-> Show SubscriptionSchedulePhaseConfigurationCoupon'Variants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionSchedulePhaseConfigurationCoupon'Variants] -> ShowS
$cshowList :: [SubscriptionSchedulePhaseConfigurationCoupon'Variants] -> ShowS
show :: SubscriptionSchedulePhaseConfigurationCoupon'Variants -> String
$cshow :: SubscriptionSchedulePhaseConfigurationCoupon'Variants -> String
showsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationCoupon'Variants -> ShowS
$cshowsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationCoupon'Variants -> ShowS
GHC.Show.Show, SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> SubscriptionSchedulePhaseConfigurationCoupon'Variants -> Bool
(SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> SubscriptionSchedulePhaseConfigurationCoupon'Variants -> Bool)
-> (SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> SubscriptionSchedulePhaseConfigurationCoupon'Variants -> Bool)
-> Eq SubscriptionSchedulePhaseConfigurationCoupon'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> SubscriptionSchedulePhaseConfigurationCoupon'Variants -> Bool
$c/= :: SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> SubscriptionSchedulePhaseConfigurationCoupon'Variants -> Bool
== :: SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> SubscriptionSchedulePhaseConfigurationCoupon'Variants -> Bool
$c== :: SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> SubscriptionSchedulePhaseConfigurationCoupon'Variants -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionSchedulePhaseConfigurationCoupon'Variants where
toJSON :: SubscriptionSchedulePhaseConfigurationCoupon'Variants -> Value
toJSON (SubscriptionSchedulePhaseConfigurationCoupon'Text Text
a) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
a
toJSON (SubscriptionSchedulePhaseConfigurationCoupon'Coupon Coupon
a) = Coupon -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Coupon
a
toJSON (SubscriptionSchedulePhaseConfigurationCoupon'DeletedCoupon DeletedCoupon
a) = DeletedCoupon -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON DeletedCoupon
a
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionSchedulePhaseConfigurationCoupon'Variants where
parseJSON :: Value
-> Parser SubscriptionSchedulePhaseConfigurationCoupon'Variants
parseJSON Value
val = case (Text -> SubscriptionSchedulePhaseConfigurationCoupon'Variants
SubscriptionSchedulePhaseConfigurationCoupon'Text (Text -> SubscriptionSchedulePhaseConfigurationCoupon'Variants)
-> Result Text
-> Result SubscriptionSchedulePhaseConfigurationCoupon'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 SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Result SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Result SubscriptionSchedulePhaseConfigurationCoupon'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((Coupon -> SubscriptionSchedulePhaseConfigurationCoupon'Variants
SubscriptionSchedulePhaseConfigurationCoupon'Coupon (Coupon -> SubscriptionSchedulePhaseConfigurationCoupon'Variants)
-> Result Coupon
-> Result SubscriptionSchedulePhaseConfigurationCoupon'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Coupon
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Result SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Result SubscriptionSchedulePhaseConfigurationCoupon'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((DeletedCoupon
-> SubscriptionSchedulePhaseConfigurationCoupon'Variants
SubscriptionSchedulePhaseConfigurationCoupon'DeletedCoupon (DeletedCoupon
-> SubscriptionSchedulePhaseConfigurationCoupon'Variants)
-> Result DeletedCoupon
-> Result SubscriptionSchedulePhaseConfigurationCoupon'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result DeletedCoupon
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Result SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Result SubscriptionSchedulePhaseConfigurationCoupon'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result SubscriptionSchedulePhaseConfigurationCoupon'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched")) of
Data.Aeson.Types.Internal.Success SubscriptionSchedulePhaseConfigurationCoupon'Variants
a -> SubscriptionSchedulePhaseConfigurationCoupon'Variants
-> Parser SubscriptionSchedulePhaseConfigurationCoupon'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure SubscriptionSchedulePhaseConfigurationCoupon'Variants
a
Data.Aeson.Types.Internal.Error String
a -> String
-> Parser SubscriptionSchedulePhaseConfigurationCoupon'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a
data SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
= SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Text Data.Text.Internal.Text
| SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'PaymentMethod PaymentMethod
deriving (Int
-> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> ShowS
[SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants]
-> ShowS
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> String
(Int
-> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> ShowS)
-> (SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> String)
-> ([SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants]
-> ShowS)
-> Show
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants]
-> ShowS
$cshowList :: [SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants]
-> ShowS
show :: SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> String
$cshow :: SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> String
showsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> ShowS
$cshowsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> ShowS
GHC.Show.Show, SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Bool
(SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Bool)
-> (SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Bool)
-> Eq
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Bool
$c/= :: SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Bool
== :: SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Bool
$c== :: SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants where
toJSON :: SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Value
toJSON (SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Text Text
a) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
a
toJSON (SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'PaymentMethod PaymentMethod
a) = PaymentMethod -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON PaymentMethod
a
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants where
parseJSON :: Value
-> Parser
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
parseJSON Value
val = case (Text
-> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Text (Text
-> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants)
-> Result Text
-> Result
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'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
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Result
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Result
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((PaymentMethod
-> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'PaymentMethod (PaymentMethod
-> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants)
-> Result PaymentMethod
-> Result
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result PaymentMethod
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Result
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Result
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched") of
Data.Aeson.Types.Internal.Success SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
a -> SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
-> Parser
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
a
Data.Aeson.Types.Internal.Error String
a -> String
-> Parser
SubscriptionSchedulePhaseConfigurationDefaultPaymentMethod'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a
data SubscriptionSchedulePhaseConfigurationInvoiceSettings' = SubscriptionSchedulePhaseConfigurationInvoiceSettings'
{
SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> Maybe Int
subscriptionSchedulePhaseConfigurationInvoiceSettings'DaysUntilDue :: (GHC.Maybe.Maybe GHC.Types.Int)
}
deriving
( Int
-> SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> ShowS
[SubscriptionSchedulePhaseConfigurationInvoiceSettings'] -> ShowS
SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> String
(Int
-> SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> ShowS)
-> (SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> String)
-> ([SubscriptionSchedulePhaseConfigurationInvoiceSettings']
-> ShowS)
-> Show SubscriptionSchedulePhaseConfigurationInvoiceSettings'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionSchedulePhaseConfigurationInvoiceSettings'] -> ShowS
$cshowList :: [SubscriptionSchedulePhaseConfigurationInvoiceSettings'] -> ShowS
show :: SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> String
$cshow :: SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> String
showsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> ShowS
$cshowsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> ShowS
GHC.Show.Show,
SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> Bool
(SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> Bool)
-> (SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> Bool)
-> Eq SubscriptionSchedulePhaseConfigurationInvoiceSettings'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> Bool
$c/= :: SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> Bool
== :: SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> Bool
$c== :: SubscriptionSchedulePhaseConfigurationInvoiceSettings'
-> SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionSchedulePhaseConfigurationInvoiceSettings' where
toJSON :: SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> Value
toJSON SubscriptionSchedulePhaseConfigurationInvoiceSettings'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"days_until_due" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> Maybe Int
subscriptionSchedulePhaseConfigurationInvoiceSettings'DaysUntilDue SubscriptionSchedulePhaseConfigurationInvoiceSettings'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
toEncoding :: SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> Encoding
toEncoding SubscriptionSchedulePhaseConfigurationInvoiceSettings'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs (Text
"days_until_due" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfigurationInvoiceSettings' -> Maybe Int
subscriptionSchedulePhaseConfigurationInvoiceSettings'DaysUntilDue SubscriptionSchedulePhaseConfigurationInvoiceSettings'
obj)
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionSchedulePhaseConfigurationInvoiceSettings' where
parseJSON :: Value
-> Parser SubscriptionSchedulePhaseConfigurationInvoiceSettings'
parseJSON = String
-> (Object
-> Parser SubscriptionSchedulePhaseConfigurationInvoiceSettings')
-> Value
-> Parser SubscriptionSchedulePhaseConfigurationInvoiceSettings'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"SubscriptionSchedulePhaseConfigurationInvoiceSettings'" (\Object
obj -> (Maybe Int
-> SubscriptionSchedulePhaseConfigurationInvoiceSettings')
-> Parser
(Maybe Int
-> SubscriptionSchedulePhaseConfigurationInvoiceSettings')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Int -> SubscriptionSchedulePhaseConfigurationInvoiceSettings'
SubscriptionSchedulePhaseConfigurationInvoiceSettings' Parser
(Maybe Int
-> SubscriptionSchedulePhaseConfigurationInvoiceSettings')
-> Parser (Maybe Int)
-> Parser SubscriptionSchedulePhaseConfigurationInvoiceSettings'
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"))
mkSubscriptionSchedulePhaseConfigurationInvoiceSettings' :: SubscriptionSchedulePhaseConfigurationInvoiceSettings'
mkSubscriptionSchedulePhaseConfigurationInvoiceSettings' :: SubscriptionSchedulePhaseConfigurationInvoiceSettings'
mkSubscriptionSchedulePhaseConfigurationInvoiceSettings' = SubscriptionSchedulePhaseConfigurationInvoiceSettings' :: Maybe Int -> SubscriptionSchedulePhaseConfigurationInvoiceSettings'
SubscriptionSchedulePhaseConfigurationInvoiceSettings' {subscriptionSchedulePhaseConfigurationInvoiceSettings'DaysUntilDue :: Maybe Int
subscriptionSchedulePhaseConfigurationInvoiceSettings'DaysUntilDue = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing}
data SubscriptionSchedulePhaseConfigurationProrationBehavior'
=
SubscriptionSchedulePhaseConfigurationProrationBehavior'Other Data.Aeson.Types.Internal.Value
|
SubscriptionSchedulePhaseConfigurationProrationBehavior'Typed Data.Text.Internal.Text
|
SubscriptionSchedulePhaseConfigurationProrationBehavior'EnumAlwaysInvoice
|
SubscriptionSchedulePhaseConfigurationProrationBehavior'EnumCreateProrations
|
SubscriptionSchedulePhaseConfigurationProrationBehavior'EnumNone
deriving (Int
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> ShowS
[SubscriptionSchedulePhaseConfigurationProrationBehavior'] -> ShowS
SubscriptionSchedulePhaseConfigurationProrationBehavior' -> String
(Int
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> ShowS)
-> (SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> String)
-> ([SubscriptionSchedulePhaseConfigurationProrationBehavior']
-> ShowS)
-> Show SubscriptionSchedulePhaseConfigurationProrationBehavior'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionSchedulePhaseConfigurationProrationBehavior'] -> ShowS
$cshowList :: [SubscriptionSchedulePhaseConfigurationProrationBehavior'] -> ShowS
show :: SubscriptionSchedulePhaseConfigurationProrationBehavior' -> String
$cshow :: SubscriptionSchedulePhaseConfigurationProrationBehavior' -> String
showsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> ShowS
$cshowsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> ShowS
GHC.Show.Show, SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> SubscriptionSchedulePhaseConfigurationProrationBehavior' -> Bool
(SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Bool)
-> (SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Bool)
-> Eq SubscriptionSchedulePhaseConfigurationProrationBehavior'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> SubscriptionSchedulePhaseConfigurationProrationBehavior' -> Bool
$c/= :: SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> SubscriptionSchedulePhaseConfigurationProrationBehavior' -> Bool
== :: SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> SubscriptionSchedulePhaseConfigurationProrationBehavior' -> Bool
$c== :: SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> SubscriptionSchedulePhaseConfigurationProrationBehavior' -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionSchedulePhaseConfigurationProrationBehavior' where
toJSON :: SubscriptionSchedulePhaseConfigurationProrationBehavior' -> Value
toJSON (SubscriptionSchedulePhaseConfigurationProrationBehavior'Other Value
val) = Value
val
toJSON (SubscriptionSchedulePhaseConfigurationProrationBehavior'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (SubscriptionSchedulePhaseConfigurationProrationBehavior'
SubscriptionSchedulePhaseConfigurationProrationBehavior'EnumAlwaysInvoice) = Value
"always_invoice"
toJSON (SubscriptionSchedulePhaseConfigurationProrationBehavior'
SubscriptionSchedulePhaseConfigurationProrationBehavior'EnumCreateProrations) = Value
"create_prorations"
toJSON (SubscriptionSchedulePhaseConfigurationProrationBehavior'
SubscriptionSchedulePhaseConfigurationProrationBehavior'EnumNone) = Value
"none"
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionSchedulePhaseConfigurationProrationBehavior' where
parseJSON :: Value
-> Parser SubscriptionSchedulePhaseConfigurationProrationBehavior'
parseJSON Value
val =
SubscriptionSchedulePhaseConfigurationProrationBehavior'
-> Parser SubscriptionSchedulePhaseConfigurationProrationBehavior'
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" -> SubscriptionSchedulePhaseConfigurationProrationBehavior'
SubscriptionSchedulePhaseConfigurationProrationBehavior'EnumAlwaysInvoice
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"create_prorations" -> SubscriptionSchedulePhaseConfigurationProrationBehavior'
SubscriptionSchedulePhaseConfigurationProrationBehavior'EnumCreateProrations
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"none" -> SubscriptionSchedulePhaseConfigurationProrationBehavior'
SubscriptionSchedulePhaseConfigurationProrationBehavior'EnumNone
| Bool
GHC.Base.otherwise -> Value -> SubscriptionSchedulePhaseConfigurationProrationBehavior'
SubscriptionSchedulePhaseConfigurationProrationBehavior'Other Value
val
)
data SubscriptionSchedulePhaseConfigurationTransferData' = SubscriptionSchedulePhaseConfigurationTransferData'
{
SubscriptionSchedulePhaseConfigurationTransferData' -> Maybe Double
subscriptionSchedulePhaseConfigurationTransferData'AmountPercent :: (GHC.Maybe.Maybe GHC.Types.Double),
SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
subscriptionSchedulePhaseConfigurationTransferData'Destination :: (GHC.Maybe.Maybe SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants)
}
deriving
( Int -> SubscriptionSchedulePhaseConfigurationTransferData' -> ShowS
[SubscriptionSchedulePhaseConfigurationTransferData'] -> ShowS
SubscriptionSchedulePhaseConfigurationTransferData' -> String
(Int
-> SubscriptionSchedulePhaseConfigurationTransferData' -> ShowS)
-> (SubscriptionSchedulePhaseConfigurationTransferData' -> String)
-> ([SubscriptionSchedulePhaseConfigurationTransferData'] -> ShowS)
-> Show SubscriptionSchedulePhaseConfigurationTransferData'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionSchedulePhaseConfigurationTransferData'] -> ShowS
$cshowList :: [SubscriptionSchedulePhaseConfigurationTransferData'] -> ShowS
show :: SubscriptionSchedulePhaseConfigurationTransferData' -> String
$cshow :: SubscriptionSchedulePhaseConfigurationTransferData' -> String
showsPrec :: Int -> SubscriptionSchedulePhaseConfigurationTransferData' -> ShowS
$cshowsPrec :: Int -> SubscriptionSchedulePhaseConfigurationTransferData' -> ShowS
GHC.Show.Show,
SubscriptionSchedulePhaseConfigurationTransferData'
-> SubscriptionSchedulePhaseConfigurationTransferData' -> Bool
(SubscriptionSchedulePhaseConfigurationTransferData'
-> SubscriptionSchedulePhaseConfigurationTransferData' -> Bool)
-> (SubscriptionSchedulePhaseConfigurationTransferData'
-> SubscriptionSchedulePhaseConfigurationTransferData' -> Bool)
-> Eq SubscriptionSchedulePhaseConfigurationTransferData'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionSchedulePhaseConfigurationTransferData'
-> SubscriptionSchedulePhaseConfigurationTransferData' -> Bool
$c/= :: SubscriptionSchedulePhaseConfigurationTransferData'
-> SubscriptionSchedulePhaseConfigurationTransferData' -> Bool
== :: SubscriptionSchedulePhaseConfigurationTransferData'
-> SubscriptionSchedulePhaseConfigurationTransferData' -> Bool
$c== :: SubscriptionSchedulePhaseConfigurationTransferData'
-> SubscriptionSchedulePhaseConfigurationTransferData' -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionSchedulePhaseConfigurationTransferData' where
toJSON :: SubscriptionSchedulePhaseConfigurationTransferData' -> Value
toJSON SubscriptionSchedulePhaseConfigurationTransferData'
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..= SubscriptionSchedulePhaseConfigurationTransferData' -> Maybe Double
subscriptionSchedulePhaseConfigurationTransferData'AmountPercent SubscriptionSchedulePhaseConfigurationTransferData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"destination" Text
-> Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
subscriptionSchedulePhaseConfigurationTransferData'Destination SubscriptionSchedulePhaseConfigurationTransferData'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
toEncoding :: SubscriptionSchedulePhaseConfigurationTransferData' -> Encoding
toEncoding SubscriptionSchedulePhaseConfigurationTransferData'
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..= SubscriptionSchedulePhaseConfigurationTransferData' -> Maybe Double
subscriptionSchedulePhaseConfigurationTransferData'AmountPercent SubscriptionSchedulePhaseConfigurationTransferData'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"destination" Text
-> Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SubscriptionSchedulePhaseConfigurationTransferData'
-> Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
subscriptionSchedulePhaseConfigurationTransferData'Destination SubscriptionSchedulePhaseConfigurationTransferData'
obj))
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionSchedulePhaseConfigurationTransferData' where
parseJSON :: Value -> Parser SubscriptionSchedulePhaseConfigurationTransferData'
parseJSON = String
-> (Object
-> Parser SubscriptionSchedulePhaseConfigurationTransferData')
-> Value
-> Parser SubscriptionSchedulePhaseConfigurationTransferData'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"SubscriptionSchedulePhaseConfigurationTransferData'" (\Object
obj -> ((Maybe Double
-> Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> SubscriptionSchedulePhaseConfigurationTransferData')
-> Parser
(Maybe Double
-> Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> SubscriptionSchedulePhaseConfigurationTransferData')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Double
-> Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> SubscriptionSchedulePhaseConfigurationTransferData'
SubscriptionSchedulePhaseConfigurationTransferData' Parser
(Maybe Double
-> Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> SubscriptionSchedulePhaseConfigurationTransferData')
-> Parser (Maybe Double)
-> Parser
(Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> SubscriptionSchedulePhaseConfigurationTransferData')
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
(Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> SubscriptionSchedulePhaseConfigurationTransferData')
-> Parser
(Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants)
-> Parser SubscriptionSchedulePhaseConfigurationTransferData'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
(Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"destination"))
mkSubscriptionSchedulePhaseConfigurationTransferData' :: SubscriptionSchedulePhaseConfigurationTransferData'
mkSubscriptionSchedulePhaseConfigurationTransferData' :: SubscriptionSchedulePhaseConfigurationTransferData'
mkSubscriptionSchedulePhaseConfigurationTransferData' =
SubscriptionSchedulePhaseConfigurationTransferData' :: Maybe Double
-> Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> SubscriptionSchedulePhaseConfigurationTransferData'
SubscriptionSchedulePhaseConfigurationTransferData'
{ subscriptionSchedulePhaseConfigurationTransferData'AmountPercent :: Maybe Double
subscriptionSchedulePhaseConfigurationTransferData'AmountPercent = Maybe Double
forall a. Maybe a
GHC.Maybe.Nothing,
subscriptionSchedulePhaseConfigurationTransferData'Destination :: Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
subscriptionSchedulePhaseConfigurationTransferData'Destination = Maybe
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
forall a. Maybe a
GHC.Maybe.Nothing
}
data SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
= SubscriptionSchedulePhaseConfigurationTransferData'Destination'Text Data.Text.Internal.Text
| SubscriptionSchedulePhaseConfigurationTransferData'Destination'Account Account
deriving (Int
-> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> ShowS
[SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants]
-> ShowS
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> String
(Int
-> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> ShowS)
-> (SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> String)
-> ([SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants]
-> ShowS)
-> Show
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants]
-> ShowS
$cshowList :: [SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants]
-> ShowS
show :: SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> String
$cshow :: SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> String
showsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> ShowS
$cshowsPrec :: Int
-> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> ShowS
GHC.Show.Show, SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> Bool
(SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> Bool)
-> (SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> Bool)
-> Eq
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> Bool
$c/= :: SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> Bool
== :: SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> Bool
$c== :: SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants where
toJSON :: SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> Value
toJSON (SubscriptionSchedulePhaseConfigurationTransferData'Destination'Text Text
a) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
a
toJSON (SubscriptionSchedulePhaseConfigurationTransferData'Destination'Account Account
a) = Account -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Account
a
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants where
parseJSON :: Value
-> Parser
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
parseJSON Value
val = case (Text
-> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Text (Text
-> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants)
-> Result Text
-> Result
SubscriptionSchedulePhaseConfigurationTransferData'Destination'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
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> Result
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> Result
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((Account
-> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Account (Account
-> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants)
-> Result Account
-> Result
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Account
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> Result
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> Result
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched") of
Data.Aeson.Types.Internal.Success SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
a -> SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
-> Parser
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
a
Data.Aeson.Types.Internal.Error String
a -> String
-> Parser
SubscriptionSchedulePhaseConfigurationTransferData'Destination'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a