{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module RecurlyClient.Types.PlanUpdate where
import qualified Control.Monad.Fail
import qualified Data.Aeson
import qualified Data.Aeson as Data.Aeson.Encoding.Internal
import qualified Data.Aeson as Data.Aeson.Types
import qualified Data.Aeson as Data.Aeson.Types.FromJSON
import qualified Data.Aeson as Data.Aeson.Types.Internal
import qualified Data.Aeson as Data.Aeson.Types.ToJSON
import qualified Data.ByteString
import qualified Data.ByteString as Data.ByteString.Internal
import qualified Data.Foldable
import qualified Data.Functor
import qualified Data.Maybe
import qualified Data.Scientific
import qualified Data.Text
import qualified Data.Text as Data.Text.Internal
import qualified Data.Time.Calendar as Data.Time.Calendar.Days
import qualified Data.Time.LocalTime as Data.Time.LocalTime.Internal.ZonedTime
import qualified GHC.Base
import qualified GHC.Classes
import qualified GHC.Int
import qualified GHC.Show
import qualified GHC.Types
import qualified RecurlyClient.Common
import RecurlyClient.TypeAlias
import {-# SOURCE #-} RecurlyClient.Types.PlanHostedPages
import {-# SOURCE #-} RecurlyClient.Types.PlanPricing
import {-# SOURCE #-} RecurlyClient.Types.PlanRampInterval
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe
data PlanUpdate = PlanUpdate
{ PlanUpdate -> Maybe Text
planUpdateAccounting_code :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, PlanUpdate -> Maybe Bool
planUpdateAllow_any_item_on_subscriptions :: (GHC.Maybe.Maybe GHC.Types.Bool)
, PlanUpdate -> Maybe Bool
planUpdateAuto_renew :: (GHC.Maybe.Maybe GHC.Types.Bool)
, PlanUpdate -> Maybe Int
planUpdateAvalara_service_type :: (GHC.Maybe.Maybe GHC.Types.Int)
, PlanUpdate -> Maybe Int
planUpdateAvalara_transaction_type :: (GHC.Maybe.Maybe GHC.Types.Int)
, PlanUpdate -> Maybe Text
planUpdateCode :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, PlanUpdate -> Maybe (NonEmpty PlanPricing)
planUpdateCurrencies :: (GHC.Maybe.Maybe (GHC.Base.NonEmpty PlanPricing))
, PlanUpdate -> Maybe CustomFields
planUpdateCustom_fields :: (GHC.Maybe.Maybe CustomFields)
, PlanUpdate -> Maybe Text
planUpdateDescription :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, PlanUpdate -> Maybe Text
planUpdateDunning_campaign_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, PlanUpdate -> Maybe PlanHostedPages
planUpdateHosted_pages :: (GHC.Maybe.Maybe PlanHostedPages)
, PlanUpdate -> Maybe Text
planUpdateId :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, PlanUpdate -> Maybe Text
planUpdateLiability_gl_account_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, PlanUpdate -> Maybe Text
planUpdateName :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, PlanUpdate -> Maybe Text
planUpdatePerformance_obligation_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, PlanUpdate -> Maybe [PlanRampInterval]
planUpdateRamp_intervals :: (GHC.Maybe.Maybe [PlanRampInterval])
, PlanUpdate -> Maybe Text
planUpdateRevenue_gl_account_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, PlanUpdate -> Maybe PlanUpdateRevenue_schedule_type
planUpdateRevenue_schedule_type :: (GHC.Maybe.Maybe PlanUpdateRevenue_schedule_type)
, PlanUpdate -> Maybe Text
planUpdateSetup_fee_accounting_code :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, PlanUpdate -> Maybe Text
planUpdateSetup_fee_liability_gl_account_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, PlanUpdate -> Maybe Text
planUpdateSetup_fee_performance_obligation_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, PlanUpdate -> Maybe Text
planUpdateSetup_fee_revenue_gl_account_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, PlanUpdate -> Maybe PlanUpdateSetup_fee_revenue_schedule_type
planUpdateSetup_fee_revenue_schedule_type :: (GHC.Maybe.Maybe PlanUpdateSetup_fee_revenue_schedule_type)
, PlanUpdate -> Maybe Text
planUpdateTax_code :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, PlanUpdate -> Maybe Bool
planUpdateTax_exempt :: (GHC.Maybe.Maybe GHC.Types.Bool)
, PlanUpdate -> Maybe Int
planUpdateTotal_billing_cycles :: (GHC.Maybe.Maybe GHC.Types.Int)
, PlanUpdate -> Maybe Int
planUpdateTrial_length :: (GHC.Maybe.Maybe GHC.Types.Int)
, PlanUpdate -> Maybe Bool
planUpdateTrial_requires_billing_info :: (GHC.Maybe.Maybe GHC.Types.Bool)
, PlanUpdate -> Maybe PlanUpdateTrial_unit
planUpdateTrial_unit :: (GHC.Maybe.Maybe PlanUpdateTrial_unit)
, PlanUpdate -> Maybe Text
planUpdateVertex_transaction_type :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
}
deriving
( Int -> PlanUpdate -> ShowS
[PlanUpdate] -> ShowS
PlanUpdate -> String
(Int -> PlanUpdate -> ShowS)
-> (PlanUpdate -> String)
-> ([PlanUpdate] -> ShowS)
-> Show PlanUpdate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PlanUpdate -> ShowS
showsPrec :: Int -> PlanUpdate -> ShowS
$cshow :: PlanUpdate -> String
show :: PlanUpdate -> String
$cshowList :: [PlanUpdate] -> ShowS
showList :: [PlanUpdate] -> ShowS
GHC.Show.Show
, PlanUpdate -> PlanUpdate -> Bool
(PlanUpdate -> PlanUpdate -> Bool)
-> (PlanUpdate -> PlanUpdate -> Bool) -> Eq PlanUpdate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PlanUpdate -> PlanUpdate -> Bool
== :: PlanUpdate -> PlanUpdate -> Bool
$c/= :: PlanUpdate -> PlanUpdate -> Bool
/= :: PlanUpdate -> PlanUpdate -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON PlanUpdate where
toJSON :: PlanUpdate -> Value
toJSON PlanUpdate
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object ([[Pair]] -> [Pair]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"accounting_code" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateAccounting_code PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Bool -> [Pair]) -> Maybe Bool -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Bool -> Pair) -> Bool -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"allow_any_item_on_subscriptions" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Bool
planUpdateAllow_any_item_on_subscriptions PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Bool -> [Pair]) -> Maybe Bool -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Bool -> Pair) -> Bool -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"auto_renew" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Bool
planUpdateAuto_renew PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Int -> [Pair]) -> Maybe Int -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Int -> Pair) -> Int -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"avalara_service_type" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Int
planUpdateAvalara_service_type PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Int -> [Pair]) -> Maybe Int -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Int -> Pair) -> Int -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"avalara_transaction_type" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Int
planUpdateAvalara_transaction_type PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"code" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateCode PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (NonEmpty PlanPricing -> [Pair])
-> Maybe (NonEmpty PlanPricing)
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (NonEmpty PlanPricing -> Pair) -> NonEmpty PlanPricing -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"currencies" Key -> NonEmpty PlanPricing -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe (NonEmpty PlanPricing)
planUpdateCurrencies PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (CustomFields -> [Pair]) -> Maybe CustomFields -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (CustomFields -> Pair) -> CustomFields -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"custom_fields" Key -> CustomFields -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe CustomFields
planUpdateCustom_fields PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"description" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateDescription PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"dunning_campaign_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateDunning_campaign_id PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (PlanHostedPages -> [Pair]) -> Maybe PlanHostedPages -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (PlanHostedPages -> Pair) -> PlanHostedPages -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"hosted_pages" Key -> PlanHostedPages -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe PlanHostedPages
planUpdateHosted_pages PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateId PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"liability_gl_account_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateLiability_gl_account_id PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"name" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateName PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"performance_obligation_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdatePerformance_obligation_id PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> ([PlanRampInterval] -> [Pair])
-> Maybe [PlanRampInterval]
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> ([PlanRampInterval] -> Pair) -> [PlanRampInterval] -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"ramp_intervals" Key -> [PlanRampInterval] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe [PlanRampInterval]
planUpdateRamp_intervals PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"revenue_gl_account_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateRevenue_gl_account_id PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (PlanUpdateRevenue_schedule_type -> [Pair])
-> Maybe PlanUpdateRevenue_schedule_type
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (PlanUpdateRevenue_schedule_type -> Pair)
-> PlanUpdateRevenue_schedule_type
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"revenue_schedule_type" Key -> PlanUpdateRevenue_schedule_type -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe PlanUpdateRevenue_schedule_type
planUpdateRevenue_schedule_type PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"setup_fee_accounting_code" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateSetup_fee_accounting_code PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"setup_fee_liability_gl_account_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateSetup_fee_liability_gl_account_id PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"setup_fee_performance_obligation_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateSetup_fee_performance_obligation_id PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"setup_fee_revenue_gl_account_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateSetup_fee_revenue_gl_account_id PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (PlanUpdateSetup_fee_revenue_schedule_type -> [Pair])
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (PlanUpdateSetup_fee_revenue_schedule_type -> Pair)
-> PlanUpdateSetup_fee_revenue_schedule_type
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"setup_fee_revenue_schedule_type" Key -> PlanUpdateSetup_fee_revenue_schedule_type -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe PlanUpdateSetup_fee_revenue_schedule_type
planUpdateSetup_fee_revenue_schedule_type PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"tax_code" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateTax_code PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Bool -> [Pair]) -> Maybe Bool -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Bool -> Pair) -> Bool -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"tax_exempt" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Bool
planUpdateTax_exempt PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Int -> [Pair]) -> Maybe Int -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Int -> Pair) -> Int -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"total_billing_cycles" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Int
planUpdateTotal_billing_cycles PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Int -> [Pair]) -> Maybe Int -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Int -> Pair) -> Int -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"trial_length" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Int
planUpdateTrial_length PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Bool -> [Pair]) -> Maybe Bool -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Bool -> Pair) -> Bool -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"trial_requires_billing_info" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Bool
planUpdateTrial_requires_billing_info PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (PlanUpdateTrial_unit -> [Pair])
-> Maybe PlanUpdateTrial_unit
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (PlanUpdateTrial_unit -> Pair) -> PlanUpdateTrial_unit -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"trial_unit" Key -> PlanUpdateTrial_unit -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe PlanUpdateTrial_unit
planUpdateTrial_unit PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"vertex_transaction_type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateVertex_transaction_type PlanUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [[Pair]]
forall a. Monoid a => a
GHC.Base.mempty))
toEncoding :: PlanUpdate -> Encoding
toEncoding PlanUpdate
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ([Series] -> Series
forall a. Monoid a => [a] -> a
GHC.Base.mconcat ([[Series]] -> [Series]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"accounting_code" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateAccounting_code PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Bool -> [Series]) -> Maybe Bool -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Bool -> Series) -> Bool -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"allow_any_item_on_subscriptions" Key -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Bool
planUpdateAllow_any_item_on_subscriptions PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Bool -> [Series]) -> Maybe Bool -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Bool -> Series) -> Bool -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"auto_renew" Key -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Bool
planUpdateAuto_renew PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Int -> [Series]) -> Maybe Int -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Int -> Series) -> Int -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"avalara_service_type" Key -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Int
planUpdateAvalara_service_type PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Int -> [Series]) -> Maybe Int -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Int -> Series) -> Int -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"avalara_transaction_type" Key -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Int
planUpdateAvalara_transaction_type PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"code" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateCode PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (NonEmpty PlanPricing -> [Series])
-> Maybe (NonEmpty PlanPricing)
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (NonEmpty PlanPricing -> Series)
-> NonEmpty PlanPricing
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"currencies" Key -> NonEmpty PlanPricing -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe (NonEmpty PlanPricing)
planUpdateCurrencies PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (CustomFields -> [Series]) -> Maybe CustomFields -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (CustomFields -> Series) -> CustomFields -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"custom_fields" Key -> CustomFields -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe CustomFields
planUpdateCustom_fields PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"description" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateDescription PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"dunning_campaign_id" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateDunning_campaign_id PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (PlanHostedPages -> [Series])
-> Maybe PlanHostedPages
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (PlanHostedPages -> Series) -> PlanHostedPages -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"hosted_pages" Key -> PlanHostedPages -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe PlanHostedPages
planUpdateHosted_pages PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"id" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateId PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"liability_gl_account_id" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateLiability_gl_account_id PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"name" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateName PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"performance_obligation_id" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdatePerformance_obligation_id PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> ([PlanRampInterval] -> [Series])
-> Maybe [PlanRampInterval]
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> ([PlanRampInterval] -> Series) -> [PlanRampInterval] -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"ramp_intervals" Key -> [PlanRampInterval] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe [PlanRampInterval]
planUpdateRamp_intervals PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"revenue_gl_account_id" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateRevenue_gl_account_id PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (PlanUpdateRevenue_schedule_type -> [Series])
-> Maybe PlanUpdateRevenue_schedule_type
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (PlanUpdateRevenue_schedule_type -> Series)
-> PlanUpdateRevenue_schedule_type
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"revenue_schedule_type" Key -> PlanUpdateRevenue_schedule_type -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe PlanUpdateRevenue_schedule_type
planUpdateRevenue_schedule_type PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"setup_fee_accounting_code" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateSetup_fee_accounting_code PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"setup_fee_liability_gl_account_id" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateSetup_fee_liability_gl_account_id PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"setup_fee_performance_obligation_id" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateSetup_fee_performance_obligation_id PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"setup_fee_revenue_gl_account_id" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateSetup_fee_revenue_gl_account_id PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (PlanUpdateSetup_fee_revenue_schedule_type -> [Series])
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (PlanUpdateSetup_fee_revenue_schedule_type -> Series)
-> PlanUpdateSetup_fee_revenue_schedule_type
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"setup_fee_revenue_schedule_type" Key -> PlanUpdateSetup_fee_revenue_schedule_type -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe PlanUpdateSetup_fee_revenue_schedule_type
planUpdateSetup_fee_revenue_schedule_type PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"tax_code" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateTax_code PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Bool -> [Series]) -> Maybe Bool -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Bool -> Series) -> Bool -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"tax_exempt" Key -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Bool
planUpdateTax_exempt PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Int -> [Series]) -> Maybe Int -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Int -> Series) -> Int -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"total_billing_cycles" Key -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Int
planUpdateTotal_billing_cycles PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Int -> [Series]) -> Maybe Int -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Int -> Series) -> Int -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"trial_length" Key -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Int
planUpdateTrial_length PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Bool -> [Series]) -> Maybe Bool -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Bool -> Series) -> Bool -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"trial_requires_billing_info" Key -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Bool
planUpdateTrial_requires_billing_info PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (PlanUpdateTrial_unit -> [Series])
-> Maybe PlanUpdateTrial_unit
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (PlanUpdateTrial_unit -> Series)
-> PlanUpdateTrial_unit
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"trial_unit" Key -> PlanUpdateTrial_unit -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe PlanUpdateTrial_unit
planUpdateTrial_unit PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"vertex_transaction_type" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (PlanUpdate -> Maybe Text
planUpdateVertex_transaction_type PlanUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [[Series]]
forall a. Monoid a => a
GHC.Base.mempty)))
instance Data.Aeson.Types.FromJSON.FromJSON PlanUpdate where
parseJSON :: Value -> Parser PlanUpdate
parseJSON = String
-> (Object -> Parser PlanUpdate) -> Value -> Parser PlanUpdate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PlanUpdate" (\Object
obj -> ((((((((((((((((((((((((((((((Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser
(Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate
PlanUpdate Parser
(Maybe Text
-> Maybe Bool
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe Bool
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"accounting_code")) Parser
(Maybe Bool
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Bool)
-> Parser
(Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"allow_any_item_on_subscriptions")) Parser
(Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Bool)
-> Parser
(Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"auto_renew")) Parser
(Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Int)
-> Parser
(Maybe Int
-> Maybe Text
-> Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"avalara_service_type")) Parser
(Maybe Int
-> Maybe Text
-> Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Int)
-> Parser
(Maybe Text
-> Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"avalara_transaction_type")) Parser
(Maybe Text
-> Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"code")) Parser
(Maybe (NonEmpty PlanPricing)
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe (NonEmpty PlanPricing))
-> Parser
(Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe (NonEmpty PlanPricing))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"currencies")) Parser
(Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe CustomFields)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe CustomFields)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"custom_fields")) Parser
(Maybe Text
-> Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"description")) Parser
(Maybe Text
-> Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"dunning_campaign_id")) Parser
(Maybe PlanHostedPages
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe PlanHostedPages)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe PlanHostedPages)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"hosted_pages")) Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"id")) Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"liability_gl_account_id")) Parser
(Maybe Text
-> Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"name")) Parser
(Maybe Text
-> Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"performance_obligation_id")) Parser
(Maybe [PlanRampInterval]
-> Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe [PlanRampInterval])
-> Parser
(Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe [PlanRampInterval])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"ramp_intervals")) Parser
(Maybe Text
-> Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"revenue_gl_account_id")) Parser
(Maybe PlanUpdateRevenue_schedule_type
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe PlanUpdateRevenue_schedule_type)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe PlanUpdateRevenue_schedule_type)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"revenue_schedule_type")) Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"setup_fee_accounting_code")) Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"setup_fee_liability_gl_account_id")) Parser
(Maybe Text
-> Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"setup_fee_performance_obligation_id")) Parser
(Maybe Text
-> Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"setup_fee_revenue_gl_account_id")) Parser
(Maybe PlanUpdateSetup_fee_revenue_schedule_type
-> Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe PlanUpdateSetup_fee_revenue_schedule_type)
-> Parser
(Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Key -> Parser (Maybe PlanUpdateSetup_fee_revenue_schedule_type)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"setup_fee_revenue_schedule_type")) Parser
(Maybe Text
-> Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"tax_code")) Parser
(Maybe Bool
-> Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Bool)
-> Parser
(Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"tax_exempt")) Parser
(Maybe Int
-> Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Int)
-> Parser
(Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"total_billing_cycles")) Parser
(Maybe Int
-> Maybe Bool
-> Maybe PlanUpdateTrial_unit
-> Maybe Text
-> PlanUpdate)
-> Parser (Maybe Int)
-> Parser
(Maybe Bool
-> Maybe PlanUpdateTrial_unit -> Maybe Text -> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"trial_length")) Parser
(Maybe Bool
-> Maybe PlanUpdateTrial_unit -> Maybe Text -> PlanUpdate)
-> Parser (Maybe Bool)
-> Parser (Maybe PlanUpdateTrial_unit -> Maybe Text -> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"trial_requires_billing_info")) Parser (Maybe PlanUpdateTrial_unit -> Maybe Text -> PlanUpdate)
-> Parser (Maybe PlanUpdateTrial_unit)
-> Parser (Maybe Text -> PlanUpdate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe PlanUpdateTrial_unit)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"trial_unit")) Parser (Maybe Text -> PlanUpdate)
-> Parser (Maybe Text) -> Parser PlanUpdate
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"vertex_transaction_type"))
mkPlanUpdate :: PlanUpdate
mkPlanUpdate :: PlanUpdate
mkPlanUpdate =
PlanUpdate
{ planUpdateAccounting_code :: Maybe Text
planUpdateAccounting_code = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateAllow_any_item_on_subscriptions :: Maybe Bool
planUpdateAllow_any_item_on_subscriptions = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateAuto_renew :: Maybe Bool
planUpdateAuto_renew = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateAvalara_service_type :: Maybe Int
planUpdateAvalara_service_type = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateAvalara_transaction_type :: Maybe Int
planUpdateAvalara_transaction_type = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateCode :: Maybe Text
planUpdateCode = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateCurrencies :: Maybe (NonEmpty PlanPricing)
planUpdateCurrencies = Maybe (NonEmpty PlanPricing)
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateCustom_fields :: Maybe CustomFields
planUpdateCustom_fields = Maybe CustomFields
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateDescription :: Maybe Text
planUpdateDescription = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateDunning_campaign_id :: Maybe Text
planUpdateDunning_campaign_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateHosted_pages :: Maybe PlanHostedPages
planUpdateHosted_pages = Maybe PlanHostedPages
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateId :: Maybe Text
planUpdateId = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateLiability_gl_account_id :: Maybe Text
planUpdateLiability_gl_account_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateName :: Maybe Text
planUpdateName = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdatePerformance_obligation_id :: Maybe Text
planUpdatePerformance_obligation_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateRamp_intervals :: Maybe [PlanRampInterval]
planUpdateRamp_intervals = Maybe [PlanRampInterval]
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateRevenue_gl_account_id :: Maybe Text
planUpdateRevenue_gl_account_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateRevenue_schedule_type :: Maybe PlanUpdateRevenue_schedule_type
planUpdateRevenue_schedule_type = Maybe PlanUpdateRevenue_schedule_type
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateSetup_fee_accounting_code :: Maybe Text
planUpdateSetup_fee_accounting_code = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateSetup_fee_liability_gl_account_id :: Maybe Text
planUpdateSetup_fee_liability_gl_account_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateSetup_fee_performance_obligation_id :: Maybe Text
planUpdateSetup_fee_performance_obligation_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateSetup_fee_revenue_gl_account_id :: Maybe Text
planUpdateSetup_fee_revenue_gl_account_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateSetup_fee_revenue_schedule_type :: Maybe PlanUpdateSetup_fee_revenue_schedule_type
planUpdateSetup_fee_revenue_schedule_type = Maybe PlanUpdateSetup_fee_revenue_schedule_type
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateTax_code :: Maybe Text
planUpdateTax_code = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateTax_exempt :: Maybe Bool
planUpdateTax_exempt = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateTotal_billing_cycles :: Maybe Int
planUpdateTotal_billing_cycles = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateTrial_length :: Maybe Int
planUpdateTrial_length = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateTrial_requires_billing_info :: Maybe Bool
planUpdateTrial_requires_billing_info = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateTrial_unit :: Maybe PlanUpdateTrial_unit
planUpdateTrial_unit = Maybe PlanUpdateTrial_unit
forall a. Maybe a
GHC.Maybe.Nothing
, planUpdateVertex_transaction_type :: Maybe Text
planUpdateVertex_transaction_type = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
}
data PlanUpdateRevenue_schedule_type
=
PlanUpdateRevenue_schedule_typeOther Data.Aeson.Types.Internal.Value
|
PlanUpdateRevenue_schedule_typeTyped Data.Text.Internal.Text
|
PlanUpdateRevenue_schedule_typeEnumAt_range_end
|
PlanUpdateRevenue_schedule_typeEnumAt_range_start
|
PlanUpdateRevenue_schedule_typeEnumEvenly
|
PlanUpdateRevenue_schedule_typeEnumNever
deriving (Int -> PlanUpdateRevenue_schedule_type -> ShowS
[PlanUpdateRevenue_schedule_type] -> ShowS
PlanUpdateRevenue_schedule_type -> String
(Int -> PlanUpdateRevenue_schedule_type -> ShowS)
-> (PlanUpdateRevenue_schedule_type -> String)
-> ([PlanUpdateRevenue_schedule_type] -> ShowS)
-> Show PlanUpdateRevenue_schedule_type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PlanUpdateRevenue_schedule_type -> ShowS
showsPrec :: Int -> PlanUpdateRevenue_schedule_type -> ShowS
$cshow :: PlanUpdateRevenue_schedule_type -> String
show :: PlanUpdateRevenue_schedule_type -> String
$cshowList :: [PlanUpdateRevenue_schedule_type] -> ShowS
showList :: [PlanUpdateRevenue_schedule_type] -> ShowS
GHC.Show.Show, PlanUpdateRevenue_schedule_type
-> PlanUpdateRevenue_schedule_type -> Bool
(PlanUpdateRevenue_schedule_type
-> PlanUpdateRevenue_schedule_type -> Bool)
-> (PlanUpdateRevenue_schedule_type
-> PlanUpdateRevenue_schedule_type -> Bool)
-> Eq PlanUpdateRevenue_schedule_type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PlanUpdateRevenue_schedule_type
-> PlanUpdateRevenue_schedule_type -> Bool
== :: PlanUpdateRevenue_schedule_type
-> PlanUpdateRevenue_schedule_type -> Bool
$c/= :: PlanUpdateRevenue_schedule_type
-> PlanUpdateRevenue_schedule_type -> Bool
/= :: PlanUpdateRevenue_schedule_type
-> PlanUpdateRevenue_schedule_type -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PlanUpdateRevenue_schedule_type where
toJSON :: PlanUpdateRevenue_schedule_type -> Value
toJSON (PlanUpdateRevenue_schedule_typeOther Value
val) = Value
val
toJSON (PlanUpdateRevenue_schedule_typeTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (PlanUpdateRevenue_schedule_type
PlanUpdateRevenue_schedule_typeEnumAt_range_end) = Value
"at_range_end"
toJSON (PlanUpdateRevenue_schedule_type
PlanUpdateRevenue_schedule_typeEnumAt_range_start) = Value
"at_range_start"
toJSON (PlanUpdateRevenue_schedule_type
PlanUpdateRevenue_schedule_typeEnumEvenly) = Value
"evenly"
toJSON (PlanUpdateRevenue_schedule_type
PlanUpdateRevenue_schedule_typeEnumNever) = Value
"never"
instance Data.Aeson.Types.FromJSON.FromJSON PlanUpdateRevenue_schedule_type where
parseJSON :: Value -> Parser PlanUpdateRevenue_schedule_type
parseJSON Value
val =
PlanUpdateRevenue_schedule_type
-> Parser PlanUpdateRevenue_schedule_type
forall a. a -> Parser a
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
"at_range_end" -> PlanUpdateRevenue_schedule_type
PlanUpdateRevenue_schedule_typeEnumAt_range_end
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"at_range_start" -> PlanUpdateRevenue_schedule_type
PlanUpdateRevenue_schedule_typeEnumAt_range_start
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"evenly" -> PlanUpdateRevenue_schedule_type
PlanUpdateRevenue_schedule_typeEnumEvenly
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"never" -> PlanUpdateRevenue_schedule_type
PlanUpdateRevenue_schedule_typeEnumNever
| Bool
GHC.Base.otherwise -> Value -> PlanUpdateRevenue_schedule_type
PlanUpdateRevenue_schedule_typeOther Value
val
)
data PlanUpdateSetup_fee_revenue_schedule_type
=
PlanUpdateSetup_fee_revenue_schedule_typeOther Data.Aeson.Types.Internal.Value
|
PlanUpdateSetup_fee_revenue_schedule_typeTyped Data.Text.Internal.Text
|
PlanUpdateSetup_fee_revenue_schedule_typeEnumAt_range_end
|
PlanUpdateSetup_fee_revenue_schedule_typeEnumAt_range_start
|
PlanUpdateSetup_fee_revenue_schedule_typeEnumEvenly
|
PlanUpdateSetup_fee_revenue_schedule_typeEnumNever
deriving (Int -> PlanUpdateSetup_fee_revenue_schedule_type -> ShowS
[PlanUpdateSetup_fee_revenue_schedule_type] -> ShowS
PlanUpdateSetup_fee_revenue_schedule_type -> String
(Int -> PlanUpdateSetup_fee_revenue_schedule_type -> ShowS)
-> (PlanUpdateSetup_fee_revenue_schedule_type -> String)
-> ([PlanUpdateSetup_fee_revenue_schedule_type] -> ShowS)
-> Show PlanUpdateSetup_fee_revenue_schedule_type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PlanUpdateSetup_fee_revenue_schedule_type -> ShowS
showsPrec :: Int -> PlanUpdateSetup_fee_revenue_schedule_type -> ShowS
$cshow :: PlanUpdateSetup_fee_revenue_schedule_type -> String
show :: PlanUpdateSetup_fee_revenue_schedule_type -> String
$cshowList :: [PlanUpdateSetup_fee_revenue_schedule_type] -> ShowS
showList :: [PlanUpdateSetup_fee_revenue_schedule_type] -> ShowS
GHC.Show.Show, PlanUpdateSetup_fee_revenue_schedule_type
-> PlanUpdateSetup_fee_revenue_schedule_type -> Bool
(PlanUpdateSetup_fee_revenue_schedule_type
-> PlanUpdateSetup_fee_revenue_schedule_type -> Bool)
-> (PlanUpdateSetup_fee_revenue_schedule_type
-> PlanUpdateSetup_fee_revenue_schedule_type -> Bool)
-> Eq PlanUpdateSetup_fee_revenue_schedule_type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PlanUpdateSetup_fee_revenue_schedule_type
-> PlanUpdateSetup_fee_revenue_schedule_type -> Bool
== :: PlanUpdateSetup_fee_revenue_schedule_type
-> PlanUpdateSetup_fee_revenue_schedule_type -> Bool
$c/= :: PlanUpdateSetup_fee_revenue_schedule_type
-> PlanUpdateSetup_fee_revenue_schedule_type -> Bool
/= :: PlanUpdateSetup_fee_revenue_schedule_type
-> PlanUpdateSetup_fee_revenue_schedule_type -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PlanUpdateSetup_fee_revenue_schedule_type where
toJSON :: PlanUpdateSetup_fee_revenue_schedule_type -> Value
toJSON (PlanUpdateSetup_fee_revenue_schedule_typeOther Value
val) = Value
val
toJSON (PlanUpdateSetup_fee_revenue_schedule_typeTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (PlanUpdateSetup_fee_revenue_schedule_type
PlanUpdateSetup_fee_revenue_schedule_typeEnumAt_range_end) = Value
"at_range_end"
toJSON (PlanUpdateSetup_fee_revenue_schedule_type
PlanUpdateSetup_fee_revenue_schedule_typeEnumAt_range_start) = Value
"at_range_start"
toJSON (PlanUpdateSetup_fee_revenue_schedule_type
PlanUpdateSetup_fee_revenue_schedule_typeEnumEvenly) = Value
"evenly"
toJSON (PlanUpdateSetup_fee_revenue_schedule_type
PlanUpdateSetup_fee_revenue_schedule_typeEnumNever) = Value
"never"
instance Data.Aeson.Types.FromJSON.FromJSON PlanUpdateSetup_fee_revenue_schedule_type where
parseJSON :: Value -> Parser PlanUpdateSetup_fee_revenue_schedule_type
parseJSON Value
val =
PlanUpdateSetup_fee_revenue_schedule_type
-> Parser PlanUpdateSetup_fee_revenue_schedule_type
forall a. a -> Parser a
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
"at_range_end" -> PlanUpdateSetup_fee_revenue_schedule_type
PlanUpdateSetup_fee_revenue_schedule_typeEnumAt_range_end
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"at_range_start" -> PlanUpdateSetup_fee_revenue_schedule_type
PlanUpdateSetup_fee_revenue_schedule_typeEnumAt_range_start
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"evenly" -> PlanUpdateSetup_fee_revenue_schedule_type
PlanUpdateSetup_fee_revenue_schedule_typeEnumEvenly
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"never" -> PlanUpdateSetup_fee_revenue_schedule_type
PlanUpdateSetup_fee_revenue_schedule_typeEnumNever
| Bool
GHC.Base.otherwise -> Value -> PlanUpdateSetup_fee_revenue_schedule_type
PlanUpdateSetup_fee_revenue_schedule_typeOther Value
val
)
data PlanUpdateTrial_unit
=
PlanUpdateTrial_unitOther Data.Aeson.Types.Internal.Value
|
PlanUpdateTrial_unitTyped Data.Text.Internal.Text
|
PlanUpdateTrial_unitEnumDays
|
PlanUpdateTrial_unitEnumMonths
deriving (Int -> PlanUpdateTrial_unit -> ShowS
[PlanUpdateTrial_unit] -> ShowS
PlanUpdateTrial_unit -> String
(Int -> PlanUpdateTrial_unit -> ShowS)
-> (PlanUpdateTrial_unit -> String)
-> ([PlanUpdateTrial_unit] -> ShowS)
-> Show PlanUpdateTrial_unit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PlanUpdateTrial_unit -> ShowS
showsPrec :: Int -> PlanUpdateTrial_unit -> ShowS
$cshow :: PlanUpdateTrial_unit -> String
show :: PlanUpdateTrial_unit -> String
$cshowList :: [PlanUpdateTrial_unit] -> ShowS
showList :: [PlanUpdateTrial_unit] -> ShowS
GHC.Show.Show, PlanUpdateTrial_unit -> PlanUpdateTrial_unit -> Bool
(PlanUpdateTrial_unit -> PlanUpdateTrial_unit -> Bool)
-> (PlanUpdateTrial_unit -> PlanUpdateTrial_unit -> Bool)
-> Eq PlanUpdateTrial_unit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PlanUpdateTrial_unit -> PlanUpdateTrial_unit -> Bool
== :: PlanUpdateTrial_unit -> PlanUpdateTrial_unit -> Bool
$c/= :: PlanUpdateTrial_unit -> PlanUpdateTrial_unit -> Bool
/= :: PlanUpdateTrial_unit -> PlanUpdateTrial_unit -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON PlanUpdateTrial_unit where
toJSON :: PlanUpdateTrial_unit -> Value
toJSON (PlanUpdateTrial_unitOther Value
val) = Value
val
toJSON (PlanUpdateTrial_unitTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (PlanUpdateTrial_unit
PlanUpdateTrial_unitEnumDays) = Value
"days"
toJSON (PlanUpdateTrial_unit
PlanUpdateTrial_unitEnumMonths) = Value
"months"
instance Data.Aeson.Types.FromJSON.FromJSON PlanUpdateTrial_unit where
parseJSON :: Value -> Parser PlanUpdateTrial_unit
parseJSON Value
val =
PlanUpdateTrial_unit -> Parser PlanUpdateTrial_unit
forall a. a -> Parser a
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
"days" -> PlanUpdateTrial_unit
PlanUpdateTrial_unitEnumDays
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"months" -> PlanUpdateTrial_unit
PlanUpdateTrial_unitEnumMonths
| Bool
GHC.Base.otherwise -> Value -> PlanUpdateTrial_unit
PlanUpdateTrial_unitOther Value
val
)