{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module RecurlyClient.Types.SubscriptionAddOnUpdate 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.SubscriptionAddOnPercentageTier
import {-# SOURCE #-} RecurlyClient.Types.SubscriptionAddOnTier
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe
data SubscriptionAddOnUpdate = SubscriptionAddOnUpdate
{ SubscriptionAddOnUpdate
-> Maybe SubscriptionAddOnUpdateAdd_on_source
subscriptionAddOnUpdateAdd_on_source :: (GHC.Maybe.Maybe SubscriptionAddOnUpdateAdd_on_source)
, SubscriptionAddOnUpdate -> Maybe Text
subscriptionAddOnUpdateCode :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, SubscriptionAddOnUpdate -> Maybe Text
subscriptionAddOnUpdateId :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, SubscriptionAddOnUpdate
-> Maybe (NonEmpty SubscriptionAddOnPercentageTier)
subscriptionAddOnUpdatePercentage_tiers :: (GHC.Maybe.Maybe (GHC.Base.NonEmpty SubscriptionAddOnPercentageTier))
, SubscriptionAddOnUpdate -> Maybe Int
subscriptionAddOnUpdateQuantity :: (GHC.Maybe.Maybe GHC.Types.Int)
, SubscriptionAddOnUpdate
-> Maybe SubscriptionAddOnUpdateRevenue_schedule_type
subscriptionAddOnUpdateRevenue_schedule_type :: (GHC.Maybe.Maybe SubscriptionAddOnUpdateRevenue_schedule_type)
, SubscriptionAddOnUpdate -> Maybe (NonEmpty SubscriptionAddOnTier)
subscriptionAddOnUpdateTiers :: (GHC.Maybe.Maybe (GHC.Base.NonEmpty SubscriptionAddOnTier))
, SubscriptionAddOnUpdate -> Maybe Float
subscriptionAddOnUpdateUnit_amount :: (GHC.Maybe.Maybe GHC.Types.Float)
, SubscriptionAddOnUpdate -> Maybe Text
subscriptionAddOnUpdateUnit_amount_decimal :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, SubscriptionAddOnUpdate -> Maybe Float
subscriptionAddOnUpdateUsage_percentage :: (GHC.Maybe.Maybe GHC.Types.Float)
}
deriving
( Int -> SubscriptionAddOnUpdate -> ShowS
[SubscriptionAddOnUpdate] -> ShowS
SubscriptionAddOnUpdate -> String
(Int -> SubscriptionAddOnUpdate -> ShowS)
-> (SubscriptionAddOnUpdate -> String)
-> ([SubscriptionAddOnUpdate] -> ShowS)
-> Show SubscriptionAddOnUpdate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionAddOnUpdate -> ShowS
showsPrec :: Int -> SubscriptionAddOnUpdate -> ShowS
$cshow :: SubscriptionAddOnUpdate -> String
show :: SubscriptionAddOnUpdate -> String
$cshowList :: [SubscriptionAddOnUpdate] -> ShowS
showList :: [SubscriptionAddOnUpdate] -> ShowS
GHC.Show.Show
, SubscriptionAddOnUpdate -> SubscriptionAddOnUpdate -> Bool
(SubscriptionAddOnUpdate -> SubscriptionAddOnUpdate -> Bool)
-> (SubscriptionAddOnUpdate -> SubscriptionAddOnUpdate -> Bool)
-> Eq SubscriptionAddOnUpdate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptionAddOnUpdate -> SubscriptionAddOnUpdate -> Bool
== :: SubscriptionAddOnUpdate -> SubscriptionAddOnUpdate -> Bool
$c/= :: SubscriptionAddOnUpdate -> SubscriptionAddOnUpdate -> Bool
/= :: SubscriptionAddOnUpdate -> SubscriptionAddOnUpdate -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionAddOnUpdate where
toJSON :: SubscriptionAddOnUpdate -> Value
toJSON SubscriptionAddOnUpdate
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object ([[Pair]] -> [Pair]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Pair]
-> (SubscriptionAddOnUpdateAdd_on_source -> [Pair])
-> Maybe SubscriptionAddOnUpdateAdd_on_source
-> [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])
-> (SubscriptionAddOnUpdateAdd_on_source -> Pair)
-> SubscriptionAddOnUpdateAdd_on_source
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"add_on_source" Key -> SubscriptionAddOnUpdateAdd_on_source -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate
-> Maybe SubscriptionAddOnUpdateAdd_on_source
subscriptionAddOnUpdateAdd_on_source SubscriptionAddOnUpdate
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..=)) (SubscriptionAddOnUpdate -> Maybe Text
subscriptionAddOnUpdateCode SubscriptionAddOnUpdate
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..=)) (SubscriptionAddOnUpdate -> Maybe Text
subscriptionAddOnUpdateId SubscriptionAddOnUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (NonEmpty SubscriptionAddOnPercentageTier -> [Pair])
-> Maybe (NonEmpty SubscriptionAddOnPercentageTier)
-> [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 SubscriptionAddOnPercentageTier -> Pair)
-> NonEmpty SubscriptionAddOnPercentageTier
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"percentage_tiers" Key -> NonEmpty SubscriptionAddOnPercentageTier -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate
-> Maybe (NonEmpty SubscriptionAddOnPercentageTier)
subscriptionAddOnUpdatePercentage_tiers SubscriptionAddOnUpdate
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
"quantity" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate -> Maybe Int
subscriptionAddOnUpdateQuantity SubscriptionAddOnUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (SubscriptionAddOnUpdateRevenue_schedule_type -> [Pair])
-> Maybe SubscriptionAddOnUpdateRevenue_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])
-> (SubscriptionAddOnUpdateRevenue_schedule_type -> Pair)
-> SubscriptionAddOnUpdateRevenue_schedule_type
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"revenue_schedule_type" Key -> SubscriptionAddOnUpdateRevenue_schedule_type -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate
-> Maybe SubscriptionAddOnUpdateRevenue_schedule_type
subscriptionAddOnUpdateRevenue_schedule_type SubscriptionAddOnUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (NonEmpty SubscriptionAddOnTier -> [Pair])
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> [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 SubscriptionAddOnTier -> Pair)
-> NonEmpty SubscriptionAddOnTier
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"tiers" Key -> NonEmpty SubscriptionAddOnTier -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate -> Maybe (NonEmpty SubscriptionAddOnTier)
subscriptionAddOnUpdateTiers SubscriptionAddOnUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Float -> [Pair]) -> Maybe Float -> [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]) -> (Float -> Pair) -> Float -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"unit_amount" Key -> Float -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate -> Maybe Float
subscriptionAddOnUpdateUnit_amount SubscriptionAddOnUpdate
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
"unit_amount_decimal" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate -> Maybe Text
subscriptionAddOnUpdateUnit_amount_decimal SubscriptionAddOnUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Float -> [Pair]) -> Maybe Float -> [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]) -> (Float -> Pair) -> Float -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"usage_percentage" Key -> Float -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate -> Maybe Float
subscriptionAddOnUpdateUsage_percentage SubscriptionAddOnUpdate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [[Pair]]
forall a. Monoid a => a
GHC.Base.mempty))
toEncoding :: SubscriptionAddOnUpdate -> Encoding
toEncoding SubscriptionAddOnUpdate
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]
-> (SubscriptionAddOnUpdateAdd_on_source -> [Series])
-> Maybe SubscriptionAddOnUpdateAdd_on_source
-> [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])
-> (SubscriptionAddOnUpdateAdd_on_source -> Series)
-> SubscriptionAddOnUpdateAdd_on_source
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"add_on_source" Key -> SubscriptionAddOnUpdateAdd_on_source -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate
-> Maybe SubscriptionAddOnUpdateAdd_on_source
subscriptionAddOnUpdateAdd_on_source SubscriptionAddOnUpdate
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..=)) (SubscriptionAddOnUpdate -> Maybe Text
subscriptionAddOnUpdateCode SubscriptionAddOnUpdate
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..=)) (SubscriptionAddOnUpdate -> Maybe Text
subscriptionAddOnUpdateId SubscriptionAddOnUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (NonEmpty SubscriptionAddOnPercentageTier -> [Series])
-> Maybe (NonEmpty SubscriptionAddOnPercentageTier)
-> [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 SubscriptionAddOnPercentageTier -> Series)
-> NonEmpty SubscriptionAddOnPercentageTier
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"percentage_tiers" Key -> NonEmpty SubscriptionAddOnPercentageTier -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate
-> Maybe (NonEmpty SubscriptionAddOnPercentageTier)
subscriptionAddOnUpdatePercentage_tiers SubscriptionAddOnUpdate
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
"quantity" Key -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate -> Maybe Int
subscriptionAddOnUpdateQuantity SubscriptionAddOnUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (SubscriptionAddOnUpdateRevenue_schedule_type -> [Series])
-> Maybe SubscriptionAddOnUpdateRevenue_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])
-> (SubscriptionAddOnUpdateRevenue_schedule_type -> Series)
-> SubscriptionAddOnUpdateRevenue_schedule_type
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"revenue_schedule_type" Key -> SubscriptionAddOnUpdateRevenue_schedule_type -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate
-> Maybe SubscriptionAddOnUpdateRevenue_schedule_type
subscriptionAddOnUpdateRevenue_schedule_type SubscriptionAddOnUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (NonEmpty SubscriptionAddOnTier -> [Series])
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> [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 SubscriptionAddOnTier -> Series)
-> NonEmpty SubscriptionAddOnTier
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"tiers" Key -> NonEmpty SubscriptionAddOnTier -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate -> Maybe (NonEmpty SubscriptionAddOnTier)
subscriptionAddOnUpdateTiers SubscriptionAddOnUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Float -> [Series]) -> Maybe Float -> [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]) -> (Float -> Series) -> Float -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"unit_amount" Key -> Float -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate -> Maybe Float
subscriptionAddOnUpdateUnit_amount SubscriptionAddOnUpdate
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
"unit_amount_decimal" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate -> Maybe Text
subscriptionAddOnUpdateUnit_amount_decimal SubscriptionAddOnUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Float -> [Series]) -> Maybe Float -> [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]) -> (Float -> Series) -> Float -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"usage_percentage" Key -> Float -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionAddOnUpdate -> Maybe Float
subscriptionAddOnUpdateUsage_percentage SubscriptionAddOnUpdate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [[Series]]
forall a. Monoid a => a
GHC.Base.mempty)))
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionAddOnUpdate where
parseJSON :: Value -> Parser SubscriptionAddOnUpdate
parseJSON = String
-> (Object -> Parser SubscriptionAddOnUpdate)
-> Value
-> Parser SubscriptionAddOnUpdate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"SubscriptionAddOnUpdate" (\Object
obj -> ((((((((((Maybe SubscriptionAddOnUpdateAdd_on_source
-> Maybe Text
-> Maybe Text
-> Maybe (NonEmpty SubscriptionAddOnPercentageTier)
-> Maybe Int
-> Maybe SubscriptionAddOnUpdateRevenue_schedule_type
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate)
-> Parser
(Maybe SubscriptionAddOnUpdateAdd_on_source
-> Maybe Text
-> Maybe Text
-> Maybe (NonEmpty SubscriptionAddOnPercentageTier)
-> Maybe Int
-> Maybe SubscriptionAddOnUpdateRevenue_schedule_type
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe SubscriptionAddOnUpdateAdd_on_source
-> Maybe Text
-> Maybe Text
-> Maybe (NonEmpty SubscriptionAddOnPercentageTier)
-> Maybe Int
-> Maybe SubscriptionAddOnUpdateRevenue_schedule_type
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate
SubscriptionAddOnUpdate Parser
(Maybe SubscriptionAddOnUpdateAdd_on_source
-> Maybe Text
-> Maybe Text
-> Maybe (NonEmpty SubscriptionAddOnPercentageTier)
-> Maybe Int
-> Maybe SubscriptionAddOnUpdateRevenue_schedule_type
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate)
-> Parser (Maybe SubscriptionAddOnUpdateAdd_on_source)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe (NonEmpty SubscriptionAddOnPercentageTier)
-> Maybe Int
-> Maybe SubscriptionAddOnUpdateRevenue_schedule_type
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate)
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 SubscriptionAddOnUpdateAdd_on_source)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"add_on_source")) Parser
(Maybe Text
-> Maybe Text
-> Maybe (NonEmpty SubscriptionAddOnPercentageTier)
-> Maybe Int
-> Maybe SubscriptionAddOnUpdateRevenue_schedule_type
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe (NonEmpty SubscriptionAddOnPercentageTier)
-> Maybe Int
-> Maybe SubscriptionAddOnUpdateRevenue_schedule_type
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate)
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 Text
-> Maybe (NonEmpty SubscriptionAddOnPercentageTier)
-> Maybe Int
-> Maybe SubscriptionAddOnUpdateRevenue_schedule_type
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate)
-> Parser (Maybe Text)
-> Parser
(Maybe (NonEmpty SubscriptionAddOnPercentageTier)
-> Maybe Int
-> Maybe SubscriptionAddOnUpdateRevenue_schedule_type
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate)
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 (NonEmpty SubscriptionAddOnPercentageTier)
-> Maybe Int
-> Maybe SubscriptionAddOnUpdateRevenue_schedule_type
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate)
-> Parser (Maybe (NonEmpty SubscriptionAddOnPercentageTier))
-> Parser
(Maybe Int
-> Maybe SubscriptionAddOnUpdateRevenue_schedule_type
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate)
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 SubscriptionAddOnPercentageTier))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"percentage_tiers")) Parser
(Maybe Int
-> Maybe SubscriptionAddOnUpdateRevenue_schedule_type
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate)
-> Parser (Maybe Int)
-> Parser
(Maybe SubscriptionAddOnUpdateRevenue_schedule_type
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate)
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
"quantity")) Parser
(Maybe SubscriptionAddOnUpdateRevenue_schedule_type
-> Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate)
-> Parser (Maybe SubscriptionAddOnUpdateRevenue_schedule_type)
-> Parser
(Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate)
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 SubscriptionAddOnUpdateRevenue_schedule_type)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"revenue_schedule_type")) Parser
(Maybe (NonEmpty SubscriptionAddOnTier)
-> Maybe Float
-> Maybe Text
-> Maybe Float
-> SubscriptionAddOnUpdate)
-> Parser (Maybe (NonEmpty SubscriptionAddOnTier))
-> Parser
(Maybe Float
-> Maybe Text -> Maybe Float -> SubscriptionAddOnUpdate)
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 SubscriptionAddOnTier))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"tiers")) Parser
(Maybe Float
-> Maybe Text -> Maybe Float -> SubscriptionAddOnUpdate)
-> Parser (Maybe Float)
-> Parser (Maybe Text -> Maybe Float -> SubscriptionAddOnUpdate)
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 Float)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"unit_amount")) Parser (Maybe Text -> Maybe Float -> SubscriptionAddOnUpdate)
-> Parser (Maybe Text)
-> Parser (Maybe Float -> SubscriptionAddOnUpdate)
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
"unit_amount_decimal")) Parser (Maybe Float -> SubscriptionAddOnUpdate)
-> Parser (Maybe Float) -> Parser SubscriptionAddOnUpdate
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 Float)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"usage_percentage"))
mkSubscriptionAddOnUpdate :: SubscriptionAddOnUpdate
mkSubscriptionAddOnUpdate :: SubscriptionAddOnUpdate
mkSubscriptionAddOnUpdate =
SubscriptionAddOnUpdate
{ subscriptionAddOnUpdateAdd_on_source :: Maybe SubscriptionAddOnUpdateAdd_on_source
subscriptionAddOnUpdateAdd_on_source = Maybe SubscriptionAddOnUpdateAdd_on_source
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionAddOnUpdateCode :: Maybe Text
subscriptionAddOnUpdateCode = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionAddOnUpdateId :: Maybe Text
subscriptionAddOnUpdateId = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionAddOnUpdatePercentage_tiers :: Maybe (NonEmpty SubscriptionAddOnPercentageTier)
subscriptionAddOnUpdatePercentage_tiers = Maybe (NonEmpty SubscriptionAddOnPercentageTier)
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionAddOnUpdateQuantity :: Maybe Int
subscriptionAddOnUpdateQuantity = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionAddOnUpdateRevenue_schedule_type :: Maybe SubscriptionAddOnUpdateRevenue_schedule_type
subscriptionAddOnUpdateRevenue_schedule_type = Maybe SubscriptionAddOnUpdateRevenue_schedule_type
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionAddOnUpdateTiers :: Maybe (NonEmpty SubscriptionAddOnTier)
subscriptionAddOnUpdateTiers = Maybe (NonEmpty SubscriptionAddOnTier)
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionAddOnUpdateUnit_amount :: Maybe Float
subscriptionAddOnUpdateUnit_amount = Maybe Float
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionAddOnUpdateUnit_amount_decimal :: Maybe Text
subscriptionAddOnUpdateUnit_amount_decimal = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionAddOnUpdateUsage_percentage :: Maybe Float
subscriptionAddOnUpdateUsage_percentage = Maybe Float
forall a. Maybe a
GHC.Maybe.Nothing
}
data SubscriptionAddOnUpdateAdd_on_source
=
SubscriptionAddOnUpdateAdd_on_sourceOther Data.Aeson.Types.Internal.Value
|
SubscriptionAddOnUpdateAdd_on_sourceTyped Data.Text.Internal.Text
|
SubscriptionAddOnUpdateAdd_on_sourceEnumPlan_add_on
|
SubscriptionAddOnUpdateAdd_on_sourceEnumItem
deriving (Int -> SubscriptionAddOnUpdateAdd_on_source -> ShowS
[SubscriptionAddOnUpdateAdd_on_source] -> ShowS
SubscriptionAddOnUpdateAdd_on_source -> String
(Int -> SubscriptionAddOnUpdateAdd_on_source -> ShowS)
-> (SubscriptionAddOnUpdateAdd_on_source -> String)
-> ([SubscriptionAddOnUpdateAdd_on_source] -> ShowS)
-> Show SubscriptionAddOnUpdateAdd_on_source
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionAddOnUpdateAdd_on_source -> ShowS
showsPrec :: Int -> SubscriptionAddOnUpdateAdd_on_source -> ShowS
$cshow :: SubscriptionAddOnUpdateAdd_on_source -> String
show :: SubscriptionAddOnUpdateAdd_on_source -> String
$cshowList :: [SubscriptionAddOnUpdateAdd_on_source] -> ShowS
showList :: [SubscriptionAddOnUpdateAdd_on_source] -> ShowS
GHC.Show.Show, SubscriptionAddOnUpdateAdd_on_source
-> SubscriptionAddOnUpdateAdd_on_source -> Bool
(SubscriptionAddOnUpdateAdd_on_source
-> SubscriptionAddOnUpdateAdd_on_source -> Bool)
-> (SubscriptionAddOnUpdateAdd_on_source
-> SubscriptionAddOnUpdateAdd_on_source -> Bool)
-> Eq SubscriptionAddOnUpdateAdd_on_source
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptionAddOnUpdateAdd_on_source
-> SubscriptionAddOnUpdateAdd_on_source -> Bool
== :: SubscriptionAddOnUpdateAdd_on_source
-> SubscriptionAddOnUpdateAdd_on_source -> Bool
$c/= :: SubscriptionAddOnUpdateAdd_on_source
-> SubscriptionAddOnUpdateAdd_on_source -> Bool
/= :: SubscriptionAddOnUpdateAdd_on_source
-> SubscriptionAddOnUpdateAdd_on_source -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionAddOnUpdateAdd_on_source where
toJSON :: SubscriptionAddOnUpdateAdd_on_source -> Value
toJSON (SubscriptionAddOnUpdateAdd_on_sourceOther Value
val) = Value
val
toJSON (SubscriptionAddOnUpdateAdd_on_sourceTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (SubscriptionAddOnUpdateAdd_on_source
SubscriptionAddOnUpdateAdd_on_sourceEnumPlan_add_on) = Value
"plan_add_on"
toJSON (SubscriptionAddOnUpdateAdd_on_source
SubscriptionAddOnUpdateAdd_on_sourceEnumItem) = Value
"item"
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionAddOnUpdateAdd_on_source where
parseJSON :: Value -> Parser SubscriptionAddOnUpdateAdd_on_source
parseJSON Value
val =
SubscriptionAddOnUpdateAdd_on_source
-> Parser SubscriptionAddOnUpdateAdd_on_source
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
"plan_add_on" -> SubscriptionAddOnUpdateAdd_on_source
SubscriptionAddOnUpdateAdd_on_sourceEnumPlan_add_on
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"item" -> SubscriptionAddOnUpdateAdd_on_source
SubscriptionAddOnUpdateAdd_on_sourceEnumItem
| Bool
GHC.Base.otherwise -> Value -> SubscriptionAddOnUpdateAdd_on_source
SubscriptionAddOnUpdateAdd_on_sourceOther Value
val
)
data SubscriptionAddOnUpdateRevenue_schedule_type
=
SubscriptionAddOnUpdateRevenue_schedule_typeOther Data.Aeson.Types.Internal.Value
|
SubscriptionAddOnUpdateRevenue_schedule_typeTyped Data.Text.Internal.Text
|
SubscriptionAddOnUpdateRevenue_schedule_typeEnumAt_range_end
|
SubscriptionAddOnUpdateRevenue_schedule_typeEnumAt_range_start
|
SubscriptionAddOnUpdateRevenue_schedule_typeEnumEvenly
|
SubscriptionAddOnUpdateRevenue_schedule_typeEnumNever
deriving (Int -> SubscriptionAddOnUpdateRevenue_schedule_type -> ShowS
[SubscriptionAddOnUpdateRevenue_schedule_type] -> ShowS
SubscriptionAddOnUpdateRevenue_schedule_type -> String
(Int -> SubscriptionAddOnUpdateRevenue_schedule_type -> ShowS)
-> (SubscriptionAddOnUpdateRevenue_schedule_type -> String)
-> ([SubscriptionAddOnUpdateRevenue_schedule_type] -> ShowS)
-> Show SubscriptionAddOnUpdateRevenue_schedule_type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionAddOnUpdateRevenue_schedule_type -> ShowS
showsPrec :: Int -> SubscriptionAddOnUpdateRevenue_schedule_type -> ShowS
$cshow :: SubscriptionAddOnUpdateRevenue_schedule_type -> String
show :: SubscriptionAddOnUpdateRevenue_schedule_type -> String
$cshowList :: [SubscriptionAddOnUpdateRevenue_schedule_type] -> ShowS
showList :: [SubscriptionAddOnUpdateRevenue_schedule_type] -> ShowS
GHC.Show.Show, SubscriptionAddOnUpdateRevenue_schedule_type
-> SubscriptionAddOnUpdateRevenue_schedule_type -> Bool
(SubscriptionAddOnUpdateRevenue_schedule_type
-> SubscriptionAddOnUpdateRevenue_schedule_type -> Bool)
-> (SubscriptionAddOnUpdateRevenue_schedule_type
-> SubscriptionAddOnUpdateRevenue_schedule_type -> Bool)
-> Eq SubscriptionAddOnUpdateRevenue_schedule_type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptionAddOnUpdateRevenue_schedule_type
-> SubscriptionAddOnUpdateRevenue_schedule_type -> Bool
== :: SubscriptionAddOnUpdateRevenue_schedule_type
-> SubscriptionAddOnUpdateRevenue_schedule_type -> Bool
$c/= :: SubscriptionAddOnUpdateRevenue_schedule_type
-> SubscriptionAddOnUpdateRevenue_schedule_type -> Bool
/= :: SubscriptionAddOnUpdateRevenue_schedule_type
-> SubscriptionAddOnUpdateRevenue_schedule_type -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionAddOnUpdateRevenue_schedule_type where
toJSON :: SubscriptionAddOnUpdateRevenue_schedule_type -> Value
toJSON (SubscriptionAddOnUpdateRevenue_schedule_typeOther Value
val) = Value
val
toJSON (SubscriptionAddOnUpdateRevenue_schedule_typeTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (SubscriptionAddOnUpdateRevenue_schedule_type
SubscriptionAddOnUpdateRevenue_schedule_typeEnumAt_range_end) = Value
"at_range_end"
toJSON (SubscriptionAddOnUpdateRevenue_schedule_type
SubscriptionAddOnUpdateRevenue_schedule_typeEnumAt_range_start) = Value
"at_range_start"
toJSON (SubscriptionAddOnUpdateRevenue_schedule_type
SubscriptionAddOnUpdateRevenue_schedule_typeEnumEvenly) = Value
"evenly"
toJSON (SubscriptionAddOnUpdateRevenue_schedule_type
SubscriptionAddOnUpdateRevenue_schedule_typeEnumNever) = Value
"never"
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionAddOnUpdateRevenue_schedule_type where
parseJSON :: Value -> Parser SubscriptionAddOnUpdateRevenue_schedule_type
parseJSON Value
val =
SubscriptionAddOnUpdateRevenue_schedule_type
-> Parser SubscriptionAddOnUpdateRevenue_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" -> SubscriptionAddOnUpdateRevenue_schedule_type
SubscriptionAddOnUpdateRevenue_schedule_typeEnumAt_range_end
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"at_range_start" -> SubscriptionAddOnUpdateRevenue_schedule_type
SubscriptionAddOnUpdateRevenue_schedule_typeEnumAt_range_start
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"evenly" -> SubscriptionAddOnUpdateRevenue_schedule_type
SubscriptionAddOnUpdateRevenue_schedule_typeEnumEvenly
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"never" -> SubscriptionAddOnUpdateRevenue_schedule_type
SubscriptionAddOnUpdateRevenue_schedule_typeEnumNever
| Bool
GHC.Base.otherwise -> Value -> SubscriptionAddOnUpdateRevenue_schedule_type
SubscriptionAddOnUpdateRevenue_schedule_typeOther Value
val
)