{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module RecurlyClient.Types.SubscriptionPurchase 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.SubscriptionAddOnCreate
import {-# SOURCE #-} RecurlyClient.Types.SubscriptionRampInterval
import {-# SOURCE #-} RecurlyClient.Types.SubscriptionShippingPurchase
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe
data SubscriptionPurchase = SubscriptionPurchase
{ SubscriptionPurchase -> Maybe [SubscriptionAddOnCreate]
subscriptionPurchaseAdd_ons :: (GHC.Maybe.Maybe [SubscriptionAddOnCreate])
, SubscriptionPurchase -> Maybe Bool
subscriptionPurchaseAuto_renew :: (GHC.Maybe.Maybe GHC.Types.Bool)
, SubscriptionPurchase -> Maybe Bool
subscriptionPurchaseBulk :: (GHC.Maybe.Maybe GHC.Types.Bool)
, SubscriptionPurchase -> Maybe CustomFields
subscriptionPurchaseCustom_fields :: (GHC.Maybe.Maybe CustomFields)
, SubscriptionPurchase -> Maybe JsonDateTime
subscriptionPurchaseNext_bill_date :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, SubscriptionPurchase -> Text
subscriptionPurchasePlan_code :: Data.Text.Internal.Text
, SubscriptionPurchase -> Maybe Text
subscriptionPurchasePlan_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, SubscriptionPurchase -> Maybe Int
subscriptionPurchaseQuantity :: (GHC.Maybe.Maybe GHC.Types.Int)
, SubscriptionPurchase -> Maybe [SubscriptionRampInterval]
subscriptionPurchaseRamp_intervals :: (GHC.Maybe.Maybe [SubscriptionRampInterval])
, SubscriptionPurchase -> Maybe Int
subscriptionPurchaseRenewal_billing_cycles :: (GHC.Maybe.Maybe GHC.Types.Int)
, SubscriptionPurchase
-> Maybe SubscriptionPurchaseRevenue_schedule_type
subscriptionPurchaseRevenue_schedule_type :: (GHC.Maybe.Maybe SubscriptionPurchaseRevenue_schedule_type)
, SubscriptionPurchase -> Maybe SubscriptionShippingPurchase
subscriptionPurchaseShipping :: (GHC.Maybe.Maybe SubscriptionShippingPurchase)
, SubscriptionPurchase -> Maybe JsonDateTime
subscriptionPurchaseStarts_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, SubscriptionPurchase -> Maybe Bool
subscriptionPurchaseTax_inclusive :: (GHC.Maybe.Maybe GHC.Types.Bool)
, SubscriptionPurchase -> Maybe Int
subscriptionPurchaseTotal_billing_cycles :: (GHC.Maybe.Maybe GHC.Types.Int)
, SubscriptionPurchase -> Maybe JsonDateTime
subscriptionPurchaseTrial_ends_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, SubscriptionPurchase -> Maybe Float
subscriptionPurchaseUnit_amount :: (GHC.Maybe.Maybe GHC.Types.Float)
}
deriving
( Int -> SubscriptionPurchase -> ShowS
[SubscriptionPurchase] -> ShowS
SubscriptionPurchase -> String
(Int -> SubscriptionPurchase -> ShowS)
-> (SubscriptionPurchase -> String)
-> ([SubscriptionPurchase] -> ShowS)
-> Show SubscriptionPurchase
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionPurchase -> ShowS
showsPrec :: Int -> SubscriptionPurchase -> ShowS
$cshow :: SubscriptionPurchase -> String
show :: SubscriptionPurchase -> String
$cshowList :: [SubscriptionPurchase] -> ShowS
showList :: [SubscriptionPurchase] -> ShowS
GHC.Show.Show
, SubscriptionPurchase -> SubscriptionPurchase -> Bool
(SubscriptionPurchase -> SubscriptionPurchase -> Bool)
-> (SubscriptionPurchase -> SubscriptionPurchase -> Bool)
-> Eq SubscriptionPurchase
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptionPurchase -> SubscriptionPurchase -> Bool
== :: SubscriptionPurchase -> SubscriptionPurchase -> Bool
$c/= :: SubscriptionPurchase -> SubscriptionPurchase -> Bool
/= :: SubscriptionPurchase -> SubscriptionPurchase -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionPurchase where
toJSON :: SubscriptionPurchase -> Value
toJSON SubscriptionPurchase
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object ([[Pair]] -> [Pair]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Pair]
-> ([SubscriptionAddOnCreate] -> [Pair])
-> Maybe [SubscriptionAddOnCreate]
-> [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])
-> ([SubscriptionAddOnCreate] -> Pair)
-> [SubscriptionAddOnCreate]
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"add_ons" Key -> [SubscriptionAddOnCreate] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe [SubscriptionAddOnCreate]
subscriptionPurchaseAdd_ons SubscriptionPurchase
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..=)) (SubscriptionPurchase -> Maybe Bool
subscriptionPurchaseAuto_renew SubscriptionPurchase
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
"bulk" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe Bool
subscriptionPurchaseBulk SubscriptionPurchase
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..=)) (SubscriptionPurchase -> Maybe CustomFields
subscriptionPurchaseCustom_fields SubscriptionPurchase
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (JsonDateTime -> [Pair]) -> Maybe JsonDateTime -> [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])
-> (JsonDateTime -> Pair) -> JsonDateTime -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"next_bill_date" Key -> JsonDateTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe JsonDateTime
subscriptionPurchaseNext_bill_date SubscriptionPurchase
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Key
"plan_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..= SubscriptionPurchase -> Text
subscriptionPurchasePlan_code SubscriptionPurchase
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
"plan_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..=)) (SubscriptionPurchase -> Maybe Text
subscriptionPurchasePlan_id SubscriptionPurchase
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..=)) (SubscriptionPurchase -> Maybe Int
subscriptionPurchaseQuantity SubscriptionPurchase
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> ([SubscriptionRampInterval] -> [Pair])
-> Maybe [SubscriptionRampInterval]
-> [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])
-> ([SubscriptionRampInterval] -> Pair)
-> [SubscriptionRampInterval]
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"ramp_intervals" Key -> [SubscriptionRampInterval] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe [SubscriptionRampInterval]
subscriptionPurchaseRamp_intervals SubscriptionPurchase
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
"renewal_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..=)) (SubscriptionPurchase -> Maybe Int
subscriptionPurchaseRenewal_billing_cycles SubscriptionPurchase
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (SubscriptionPurchaseRevenue_schedule_type -> [Pair])
-> Maybe SubscriptionPurchaseRevenue_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])
-> (SubscriptionPurchaseRevenue_schedule_type -> Pair)
-> SubscriptionPurchaseRevenue_schedule_type
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"revenue_schedule_type" Key -> SubscriptionPurchaseRevenue_schedule_type -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase
-> Maybe SubscriptionPurchaseRevenue_schedule_type
subscriptionPurchaseRevenue_schedule_type SubscriptionPurchase
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (SubscriptionShippingPurchase -> [Pair])
-> Maybe SubscriptionShippingPurchase
-> [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])
-> (SubscriptionShippingPurchase -> Pair)
-> SubscriptionShippingPurchase
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"shipping" Key -> SubscriptionShippingPurchase -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe SubscriptionShippingPurchase
subscriptionPurchaseShipping SubscriptionPurchase
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (JsonDateTime -> [Pair]) -> Maybe JsonDateTime -> [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])
-> (JsonDateTime -> Pair) -> JsonDateTime -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"starts_at" Key -> JsonDateTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe JsonDateTime
subscriptionPurchaseStarts_at SubscriptionPurchase
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_inclusive" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe Bool
subscriptionPurchaseTax_inclusive SubscriptionPurchase
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..=)) (SubscriptionPurchase -> Maybe Int
subscriptionPurchaseTotal_billing_cycles SubscriptionPurchase
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (JsonDateTime -> [Pair]) -> Maybe JsonDateTime -> [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])
-> (JsonDateTime -> Pair) -> JsonDateTime -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"trial_ends_at" Key -> JsonDateTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe JsonDateTime
subscriptionPurchaseTrial_ends_at SubscriptionPurchase
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..=)) (SubscriptionPurchase -> Maybe Float
subscriptionPurchaseUnit_amount SubscriptionPurchase
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [[Pair]]
forall a. Monoid a => a
GHC.Base.mempty))
toEncoding :: SubscriptionPurchase -> Encoding
toEncoding SubscriptionPurchase
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]
-> ([SubscriptionAddOnCreate] -> [Series])
-> Maybe [SubscriptionAddOnCreate]
-> [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])
-> ([SubscriptionAddOnCreate] -> Series)
-> [SubscriptionAddOnCreate]
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"add_ons" Key -> [SubscriptionAddOnCreate] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe [SubscriptionAddOnCreate]
subscriptionPurchaseAdd_ons SubscriptionPurchase
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..=)) (SubscriptionPurchase -> Maybe Bool
subscriptionPurchaseAuto_renew SubscriptionPurchase
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
"bulk" Key -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe Bool
subscriptionPurchaseBulk SubscriptionPurchase
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..=)) (SubscriptionPurchase -> Maybe CustomFields
subscriptionPurchaseCustom_fields SubscriptionPurchase
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (JsonDateTime -> [Series]) -> Maybe JsonDateTime -> [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])
-> (JsonDateTime -> Series) -> JsonDateTime -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"next_bill_date" Key -> JsonDateTime -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe JsonDateTime
subscriptionPurchaseNext_bill_date SubscriptionPurchase
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Key
"plan_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..= SubscriptionPurchase -> Text
subscriptionPurchasePlan_code SubscriptionPurchase
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
"plan_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..=)) (SubscriptionPurchase -> Maybe Text
subscriptionPurchasePlan_id SubscriptionPurchase
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..=)) (SubscriptionPurchase -> Maybe Int
subscriptionPurchaseQuantity SubscriptionPurchase
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> ([SubscriptionRampInterval] -> [Series])
-> Maybe [SubscriptionRampInterval]
-> [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])
-> ([SubscriptionRampInterval] -> Series)
-> [SubscriptionRampInterval]
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"ramp_intervals" Key -> [SubscriptionRampInterval] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe [SubscriptionRampInterval]
subscriptionPurchaseRamp_intervals SubscriptionPurchase
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
"renewal_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..=)) (SubscriptionPurchase -> Maybe Int
subscriptionPurchaseRenewal_billing_cycles SubscriptionPurchase
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (SubscriptionPurchaseRevenue_schedule_type -> [Series])
-> Maybe SubscriptionPurchaseRevenue_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])
-> (SubscriptionPurchaseRevenue_schedule_type -> Series)
-> SubscriptionPurchaseRevenue_schedule_type
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"revenue_schedule_type" Key -> SubscriptionPurchaseRevenue_schedule_type -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase
-> Maybe SubscriptionPurchaseRevenue_schedule_type
subscriptionPurchaseRevenue_schedule_type SubscriptionPurchase
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (SubscriptionShippingPurchase -> [Series])
-> Maybe SubscriptionShippingPurchase
-> [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])
-> (SubscriptionShippingPurchase -> Series)
-> SubscriptionShippingPurchase
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"shipping" Key -> SubscriptionShippingPurchase -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe SubscriptionShippingPurchase
subscriptionPurchaseShipping SubscriptionPurchase
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (JsonDateTime -> [Series]) -> Maybe JsonDateTime -> [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])
-> (JsonDateTime -> Series) -> JsonDateTime -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"starts_at" Key -> JsonDateTime -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe JsonDateTime
subscriptionPurchaseStarts_at SubscriptionPurchase
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_inclusive" Key -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe Bool
subscriptionPurchaseTax_inclusive SubscriptionPurchase
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..=)) (SubscriptionPurchase -> Maybe Int
subscriptionPurchaseTotal_billing_cycles SubscriptionPurchase
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (JsonDateTime -> [Series]) -> Maybe JsonDateTime -> [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])
-> (JsonDateTime -> Series) -> JsonDateTime -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"trial_ends_at" Key -> JsonDateTime -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionPurchase -> Maybe JsonDateTime
subscriptionPurchaseTrial_ends_at SubscriptionPurchase
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..=)) (SubscriptionPurchase -> Maybe Float
subscriptionPurchaseUnit_amount SubscriptionPurchase
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [[Series]]
forall a. Monoid a => a
GHC.Base.mempty)))
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionPurchase where
parseJSON :: Value -> Parser SubscriptionPurchase
parseJSON = String
-> (Object -> Parser SubscriptionPurchase)
-> Value
-> Parser SubscriptionPurchase
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"SubscriptionPurchase" (\Object
obj -> (((((((((((((((((Maybe [SubscriptionAddOnCreate]
-> Maybe Bool
-> Maybe Bool
-> Maybe CustomFields
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
-> Parser
(Maybe [SubscriptionAddOnCreate]
-> Maybe Bool
-> Maybe Bool
-> Maybe CustomFields
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe [SubscriptionAddOnCreate]
-> Maybe Bool
-> Maybe Bool
-> Maybe CustomFields
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase
SubscriptionPurchase Parser
(Maybe [SubscriptionAddOnCreate]
-> Maybe Bool
-> Maybe Bool
-> Maybe CustomFields
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
-> Parser (Maybe [SubscriptionAddOnCreate])
-> Parser
(Maybe Bool
-> Maybe Bool
-> Maybe CustomFields
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
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 [SubscriptionAddOnCreate])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"add_ons")) Parser
(Maybe Bool
-> Maybe Bool
-> Maybe CustomFields
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
-> Parser (Maybe Bool)
-> Parser
(Maybe Bool
-> Maybe CustomFields
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
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 Bool
-> Maybe CustomFields
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
-> Parser (Maybe Bool)
-> Parser
(Maybe CustomFields
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
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
"bulk")) Parser
(Maybe CustomFields
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
-> Parser (Maybe CustomFields)
-> Parser
(Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
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 JsonDateTime
-> Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
-> Parser (Maybe JsonDateTime)
-> Parser
(Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
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 JsonDateTime)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"next_bill_date")) Parser
(Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
-> Parser Text
-> Parser
(Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
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 Text
forall a. FromJSON a => Object -> Key -> Parser a
Data.Aeson.Types.FromJSON..: Key
"plan_code")) Parser
(Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
-> Parser (Maybe Text)
-> Parser
(Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
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
"plan_id")) Parser
(Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
-> Parser (Maybe Int)
-> Parser
(Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
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 [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
-> Parser (Maybe [SubscriptionRampInterval])
-> Parser
(Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
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 [SubscriptionRampInterval])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"ramp_intervals")) Parser
(Maybe Int
-> Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
-> Parser (Maybe Int)
-> Parser
(Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
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
"renewal_billing_cycles")) Parser
(Maybe SubscriptionPurchaseRevenue_schedule_type
-> Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
-> Parser (Maybe SubscriptionPurchaseRevenue_schedule_type)
-> Parser
(Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
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 SubscriptionPurchaseRevenue_schedule_type)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"revenue_schedule_type")) Parser
(Maybe SubscriptionShippingPurchase
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
-> Parser (Maybe SubscriptionShippingPurchase)
-> Parser
(Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
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 SubscriptionShippingPurchase)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"shipping")) Parser
(Maybe JsonDateTime
-> Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
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 JsonDateTime)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"starts_at")) Parser
(Maybe Bool
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionPurchase)
-> Parser (Maybe Bool)
-> Parser
(Maybe Int
-> Maybe JsonDateTime -> Maybe Float -> SubscriptionPurchase)
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_inclusive")) Parser
(Maybe Int
-> Maybe JsonDateTime -> Maybe Float -> SubscriptionPurchase)
-> Parser (Maybe Int)
-> Parser
(Maybe JsonDateTime -> Maybe Float -> SubscriptionPurchase)
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 JsonDateTime -> Maybe Float -> SubscriptionPurchase)
-> Parser (Maybe JsonDateTime)
-> Parser (Maybe Float -> SubscriptionPurchase)
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 JsonDateTime)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"trial_ends_at")) Parser (Maybe Float -> SubscriptionPurchase)
-> Parser (Maybe Float) -> Parser SubscriptionPurchase
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"))
mkSubscriptionPurchase ::
Data.Text.Internal.Text ->
SubscriptionPurchase
mkSubscriptionPurchase :: Text -> SubscriptionPurchase
mkSubscriptionPurchase Text
subscriptionPurchasePlan_code =
SubscriptionPurchase
{ subscriptionPurchaseAdd_ons :: Maybe [SubscriptionAddOnCreate]
subscriptionPurchaseAdd_ons = Maybe [SubscriptionAddOnCreate]
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPurchaseAuto_renew :: Maybe Bool
subscriptionPurchaseAuto_renew = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPurchaseBulk :: Maybe Bool
subscriptionPurchaseBulk = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPurchaseCustom_fields :: Maybe CustomFields
subscriptionPurchaseCustom_fields = Maybe CustomFields
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPurchaseNext_bill_date :: Maybe JsonDateTime
subscriptionPurchaseNext_bill_date = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPurchasePlan_code :: Text
subscriptionPurchasePlan_code = Text
subscriptionPurchasePlan_code
, subscriptionPurchasePlan_id :: Maybe Text
subscriptionPurchasePlan_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPurchaseQuantity :: Maybe Int
subscriptionPurchaseQuantity = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPurchaseRamp_intervals :: Maybe [SubscriptionRampInterval]
subscriptionPurchaseRamp_intervals = Maybe [SubscriptionRampInterval]
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPurchaseRenewal_billing_cycles :: Maybe Int
subscriptionPurchaseRenewal_billing_cycles = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPurchaseRevenue_schedule_type :: Maybe SubscriptionPurchaseRevenue_schedule_type
subscriptionPurchaseRevenue_schedule_type = Maybe SubscriptionPurchaseRevenue_schedule_type
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPurchaseShipping :: Maybe SubscriptionShippingPurchase
subscriptionPurchaseShipping = Maybe SubscriptionShippingPurchase
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPurchaseStarts_at :: Maybe JsonDateTime
subscriptionPurchaseStarts_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPurchaseTax_inclusive :: Maybe Bool
subscriptionPurchaseTax_inclusive = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPurchaseTotal_billing_cycles :: Maybe Int
subscriptionPurchaseTotal_billing_cycles = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPurchaseTrial_ends_at :: Maybe JsonDateTime
subscriptionPurchaseTrial_ends_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPurchaseUnit_amount :: Maybe Float
subscriptionPurchaseUnit_amount = Maybe Float
forall a. Maybe a
GHC.Maybe.Nothing
}
data SubscriptionPurchaseRevenue_schedule_type
=
SubscriptionPurchaseRevenue_schedule_typeOther Data.Aeson.Types.Internal.Value
|
SubscriptionPurchaseRevenue_schedule_typeTyped Data.Text.Internal.Text
|
SubscriptionPurchaseRevenue_schedule_typeEnumAt_range_end
|
SubscriptionPurchaseRevenue_schedule_typeEnumAt_range_start
|
SubscriptionPurchaseRevenue_schedule_typeEnumEvenly
|
SubscriptionPurchaseRevenue_schedule_typeEnumNever
deriving (Int -> SubscriptionPurchaseRevenue_schedule_type -> ShowS
[SubscriptionPurchaseRevenue_schedule_type] -> ShowS
SubscriptionPurchaseRevenue_schedule_type -> String
(Int -> SubscriptionPurchaseRevenue_schedule_type -> ShowS)
-> (SubscriptionPurchaseRevenue_schedule_type -> String)
-> ([SubscriptionPurchaseRevenue_schedule_type] -> ShowS)
-> Show SubscriptionPurchaseRevenue_schedule_type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionPurchaseRevenue_schedule_type -> ShowS
showsPrec :: Int -> SubscriptionPurchaseRevenue_schedule_type -> ShowS
$cshow :: SubscriptionPurchaseRevenue_schedule_type -> String
show :: SubscriptionPurchaseRevenue_schedule_type -> String
$cshowList :: [SubscriptionPurchaseRevenue_schedule_type] -> ShowS
showList :: [SubscriptionPurchaseRevenue_schedule_type] -> ShowS
GHC.Show.Show, SubscriptionPurchaseRevenue_schedule_type
-> SubscriptionPurchaseRevenue_schedule_type -> Bool
(SubscriptionPurchaseRevenue_schedule_type
-> SubscriptionPurchaseRevenue_schedule_type -> Bool)
-> (SubscriptionPurchaseRevenue_schedule_type
-> SubscriptionPurchaseRevenue_schedule_type -> Bool)
-> Eq SubscriptionPurchaseRevenue_schedule_type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptionPurchaseRevenue_schedule_type
-> SubscriptionPurchaseRevenue_schedule_type -> Bool
== :: SubscriptionPurchaseRevenue_schedule_type
-> SubscriptionPurchaseRevenue_schedule_type -> Bool
$c/= :: SubscriptionPurchaseRevenue_schedule_type
-> SubscriptionPurchaseRevenue_schedule_type -> Bool
/= :: SubscriptionPurchaseRevenue_schedule_type
-> SubscriptionPurchaseRevenue_schedule_type -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionPurchaseRevenue_schedule_type where
toJSON :: SubscriptionPurchaseRevenue_schedule_type -> Value
toJSON (SubscriptionPurchaseRevenue_schedule_typeOther Value
val) = Value
val
toJSON (SubscriptionPurchaseRevenue_schedule_typeTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (SubscriptionPurchaseRevenue_schedule_type
SubscriptionPurchaseRevenue_schedule_typeEnumAt_range_end) = Value
"at_range_end"
toJSON (SubscriptionPurchaseRevenue_schedule_type
SubscriptionPurchaseRevenue_schedule_typeEnumAt_range_start) = Value
"at_range_start"
toJSON (SubscriptionPurchaseRevenue_schedule_type
SubscriptionPurchaseRevenue_schedule_typeEnumEvenly) = Value
"evenly"
toJSON (SubscriptionPurchaseRevenue_schedule_type
SubscriptionPurchaseRevenue_schedule_typeEnumNever) = Value
"never"
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionPurchaseRevenue_schedule_type where
parseJSON :: Value -> Parser SubscriptionPurchaseRevenue_schedule_type
parseJSON Value
val =
SubscriptionPurchaseRevenue_schedule_type
-> Parser SubscriptionPurchaseRevenue_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" -> SubscriptionPurchaseRevenue_schedule_type
SubscriptionPurchaseRevenue_schedule_typeEnumAt_range_end
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"at_range_start" -> SubscriptionPurchaseRevenue_schedule_type
SubscriptionPurchaseRevenue_schedule_typeEnumAt_range_start
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"evenly" -> SubscriptionPurchaseRevenue_schedule_type
SubscriptionPurchaseRevenue_schedule_typeEnumEvenly
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"never" -> SubscriptionPurchaseRevenue_schedule_type
SubscriptionPurchaseRevenue_schedule_typeEnumNever
| Bool
GHC.Base.otherwise -> Value -> SubscriptionPurchaseRevenue_schedule_type
SubscriptionPurchaseRevenue_schedule_typeOther Value
val
)