{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module RecurlyClient.Types.Subscription 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.AccountMini
import {-# SOURCE #-} RecurlyClient.Types.CouponRedemptionMini
import {-# SOURCE #-} RecurlyClient.Types.PlanMini
import {-# SOURCE #-} RecurlyClient.Types.SubscriptionAddOn
import {-# SOURCE #-} RecurlyClient.Types.SubscriptionChange
import {-# SOURCE #-} RecurlyClient.Types.SubscriptionRampIntervalResponse
import {-# SOURCE #-} RecurlyClient.Types.SubscriptionShipping
import {-# SOURCE #-} RecurlyClient.Types.TaxInfo
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe
data Subscription = Subscription
{ Subscription -> Maybe AccountMini
subscriptionAccount :: (GHC.Maybe.Maybe AccountMini)
, Subscription -> Maybe Object
subscriptionAction_result :: (GHC.Maybe.Maybe Data.Aeson.Types.Internal.Object)
, Subscription -> Maybe JsonDateTime
subscriptionActivated_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, Subscription -> Maybe Text
subscriptionActive_invoice_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, Subscription -> Maybe [SubscriptionAddOn]
subscriptionAdd_ons :: (GHC.Maybe.Maybe [SubscriptionAddOn])
, Subscription -> Maybe Float
subscriptionAdd_ons_total :: (GHC.Maybe.Maybe GHC.Types.Float)
, Subscription -> Maybe Bool
subscriptionAuto_renew :: (GHC.Maybe.Maybe GHC.Types.Bool)
, Subscription -> Maybe JsonDateTime
subscriptionBank_account_authorized_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, Subscription -> Maybe Text
subscriptionBilling_info_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, Subscription -> Maybe Text
subscriptionBusiness_entity_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, Subscription -> Maybe JsonDateTime
subscriptionCanceled_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, Subscription -> Maybe SubscriptionCollection_method
subscriptionCollection_method :: (GHC.Maybe.Maybe SubscriptionCollection_method)
, Subscription -> Maybe JsonDateTime
subscriptionConverted_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, Subscription -> Maybe [CouponRedemptionMini]
subscriptionCoupon_redemptions :: (GHC.Maybe.Maybe [CouponRedemptionMini])
, Subscription -> Maybe JsonDateTime
subscriptionCreated_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, Subscription -> Maybe Text
subscriptionCurrency :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, Subscription -> Maybe JsonDateTime
subscriptionCurrent_period_ends_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, Subscription -> Maybe JsonDateTime
subscriptionCurrent_period_started_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, Subscription -> Maybe JsonDateTime
subscriptionCurrent_term_ends_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, Subscription -> Maybe JsonDateTime
subscriptionCurrent_term_started_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, Subscription -> Maybe CustomFields
subscriptionCustom_fields :: (GHC.Maybe.Maybe CustomFields)
, Subscription -> Maybe Text
subscriptionCustomer_notes :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, Subscription -> Maybe Text
subscriptionExpiration_reason :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, Subscription -> Maybe JsonDateTime
subscriptionExpires_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, Subscription -> Maybe Text
subscriptionGateway_code :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, Subscription -> Maybe Text
subscriptionId :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, Subscription -> Maybe Int
subscriptionNet_terms :: (GHC.Maybe.Maybe GHC.Types.Int)
, Subscription -> Maybe SubscriptionNet_terms_type
subscriptionNet_terms_type :: (GHC.Maybe.Maybe SubscriptionNet_terms_type)
, Subscription -> Maybe Text
subscriptionObject :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, Subscription -> Maybe JsonDateTime
subscriptionPaused_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, Subscription -> Maybe SubscriptionChange
subscriptionPending_change :: (GHC.Maybe.Maybe SubscriptionChange)
, Subscription -> Maybe PlanMini
subscriptionPlan :: (GHC.Maybe.Maybe PlanMini)
, Subscription -> Maybe Text
subscriptionPo_number :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, Subscription -> Maybe Int
subscriptionQuantity :: (GHC.Maybe.Maybe GHC.Types.Int)
, Subscription -> Maybe [SubscriptionRampIntervalResponse]
subscriptionRamp_intervals :: (GHC.Maybe.Maybe [SubscriptionRampIntervalResponse])
, Subscription -> Maybe Int
subscriptionRemaining_billing_cycles :: (GHC.Maybe.Maybe GHC.Types.Int)
, Subscription -> Maybe Int
subscriptionRemaining_pause_cycles :: (GHC.Maybe.Maybe GHC.Types.Int)
, Subscription -> Maybe Int
subscriptionRenewal_billing_cycles :: (GHC.Maybe.Maybe GHC.Types.Int)
, Subscription -> Maybe SubscriptionRevenue_schedule_type
subscriptionRevenue_schedule_type :: (GHC.Maybe.Maybe SubscriptionRevenue_schedule_type)
, Subscription -> Maybe SubscriptionShipping
subscriptionShipping :: (GHC.Maybe.Maybe SubscriptionShipping)
, Subscription -> Maybe Bool
subscriptionStarted_with_gift :: (GHC.Maybe.Maybe GHC.Types.Bool)
, Subscription -> Maybe SubscriptionState
subscriptionState :: (GHC.Maybe.Maybe SubscriptionState)
, Subscription -> Maybe Float
subscriptionSubtotal :: (GHC.Maybe.Maybe GHC.Types.Float)
, Subscription -> Maybe Float
subscriptionTax :: (GHC.Maybe.Maybe GHC.Types.Float)
, Subscription -> Maybe Bool
subscriptionTax_inclusive :: (GHC.Maybe.Maybe GHC.Types.Bool)
, Subscription -> Maybe TaxInfo
subscriptionTax_info :: (GHC.Maybe.Maybe TaxInfo)
, Subscription -> Maybe Text
subscriptionTerms_and_conditions :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, Subscription -> Maybe Float
subscriptionTotal :: (GHC.Maybe.Maybe GHC.Types.Float)
, Subscription -> Maybe Int
subscriptionTotal_billing_cycles :: (GHC.Maybe.Maybe GHC.Types.Int)
, Subscription -> Maybe JsonDateTime
subscriptionTrial_ends_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, Subscription -> Maybe JsonDateTime
subscriptionTrial_started_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, Subscription -> Maybe Float
subscriptionUnit_amount :: (GHC.Maybe.Maybe GHC.Types.Float)
, Subscription -> Maybe JsonDateTime
subscriptionUpdated_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, Subscription -> Maybe Text
subscriptionUuid :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
}
deriving
( Int -> Subscription -> ShowS
[Subscription] -> ShowS
Subscription -> String
(Int -> Subscription -> ShowS)
-> (Subscription -> String)
-> ([Subscription] -> ShowS)
-> Show Subscription
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Subscription -> ShowS
showsPrec :: Int -> Subscription -> ShowS
$cshow :: Subscription -> String
show :: Subscription -> String
$cshowList :: [Subscription] -> ShowS
showList :: [Subscription] -> ShowS
GHC.Show.Show
, Subscription -> Subscription -> Bool
(Subscription -> Subscription -> Bool)
-> (Subscription -> Subscription -> Bool) -> Eq Subscription
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Subscription -> Subscription -> Bool
== :: Subscription -> Subscription -> Bool
$c/= :: Subscription -> Subscription -> Bool
/= :: Subscription -> Subscription -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON Subscription where
toJSON :: Subscription -> Value
toJSON Subscription
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object ([[Pair]] -> [Pair]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Pair] -> (AccountMini -> [Pair]) -> Maybe AccountMini -> [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]) -> (AccountMini -> Pair) -> AccountMini -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"account" Key -> AccountMini -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe AccountMini
subscriptionAccount Subscription
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Object -> [Pair]) -> Maybe Object -> [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]) -> (Object -> Pair) -> Object -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"action_result" Key -> Object -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Object
subscriptionAction_result Subscription
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
"activated_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionActivated_at Subscription
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
"active_invoice_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..=)) (Subscription -> Maybe Text
subscriptionActive_invoice_id Subscription
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> ([SubscriptionAddOn] -> [Pair])
-> Maybe [SubscriptionAddOn]
-> [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])
-> ([SubscriptionAddOn] -> Pair) -> [SubscriptionAddOn] -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"add_ons" Key -> [SubscriptionAddOn] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe [SubscriptionAddOn]
subscriptionAdd_ons Subscription
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
"add_ons_total" Key -> Float -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Float
subscriptionAdd_ons_total Subscription
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..=)) (Subscription -> Maybe Bool
subscriptionAuto_renew Subscription
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
"bank_account_authorized_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionBank_account_authorized_at Subscription
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
"billing_info_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..=)) (Subscription -> Maybe Text
subscriptionBilling_info_id Subscription
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
"business_entity_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..=)) (Subscription -> Maybe Text
subscriptionBusiness_entity_id Subscription
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
"canceled_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionCanceled_at Subscription
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (SubscriptionCollection_method -> [Pair])
-> Maybe SubscriptionCollection_method
-> [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])
-> (SubscriptionCollection_method -> Pair)
-> SubscriptionCollection_method
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"collection_method" Key -> SubscriptionCollection_method -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe SubscriptionCollection_method
subscriptionCollection_method Subscription
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
"converted_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionConverted_at Subscription
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> ([CouponRedemptionMini] -> [Pair])
-> Maybe [CouponRedemptionMini]
-> [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])
-> ([CouponRedemptionMini] -> Pair)
-> [CouponRedemptionMini]
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"coupon_redemptions" Key -> [CouponRedemptionMini] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe [CouponRedemptionMini]
subscriptionCoupon_redemptions Subscription
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
"created_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionCreated_at Subscription
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
"currency" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Text
subscriptionCurrency Subscription
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
"current_period_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionCurrent_period_ends_at Subscription
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
"current_period_started_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionCurrent_period_started_at Subscription
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
"current_term_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionCurrent_term_ends_at Subscription
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
"current_term_started_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionCurrent_term_started_at Subscription
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..=)) (Subscription -> Maybe CustomFields
subscriptionCustom_fields Subscription
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
"customer_notes" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Text
subscriptionCustomer_notes Subscription
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
"expiration_reason" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Text
subscriptionExpiration_reason Subscription
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
"expires_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionExpires_at Subscription
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
"gateway_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..=)) (Subscription -> Maybe Text
subscriptionGateway_code Subscription
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..=)) (Subscription -> Maybe Text
subscriptionId Subscription
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
"net_terms" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Int
subscriptionNet_terms Subscription
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (SubscriptionNet_terms_type -> [Pair])
-> Maybe SubscriptionNet_terms_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])
-> (SubscriptionNet_terms_type -> Pair)
-> SubscriptionNet_terms_type
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"net_terms_type" Key -> SubscriptionNet_terms_type -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe SubscriptionNet_terms_type
subscriptionNet_terms_type Subscription
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
"object" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Text
subscriptionObject Subscription
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
"paused_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionPaused_at Subscription
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (SubscriptionChange -> [Pair])
-> Maybe SubscriptionChange
-> [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])
-> (SubscriptionChange -> Pair) -> SubscriptionChange -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"pending_change" Key -> SubscriptionChange -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe SubscriptionChange
subscriptionPending_change Subscription
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (PlanMini -> [Pair]) -> Maybe PlanMini -> [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]) -> (PlanMini -> Pair) -> PlanMini -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"plan" Key -> PlanMini -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe PlanMini
subscriptionPlan Subscription
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
"po_number" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Text
subscriptionPo_number Subscription
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..=)) (Subscription -> Maybe Int
subscriptionQuantity Subscription
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> ([SubscriptionRampIntervalResponse] -> [Pair])
-> Maybe [SubscriptionRampIntervalResponse]
-> [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])
-> ([SubscriptionRampIntervalResponse] -> Pair)
-> [SubscriptionRampIntervalResponse]
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"ramp_intervals" Key -> [SubscriptionRampIntervalResponse] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe [SubscriptionRampIntervalResponse]
subscriptionRamp_intervals Subscription
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
"remaining_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..=)) (Subscription -> Maybe Int
subscriptionRemaining_billing_cycles Subscription
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
"remaining_pause_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..=)) (Subscription -> Maybe Int
subscriptionRemaining_pause_cycles Subscription
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..=)) (Subscription -> Maybe Int
subscriptionRenewal_billing_cycles Subscription
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (SubscriptionRevenue_schedule_type -> [Pair])
-> Maybe SubscriptionRevenue_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])
-> (SubscriptionRevenue_schedule_type -> Pair)
-> SubscriptionRevenue_schedule_type
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"revenue_schedule_type" Key -> SubscriptionRevenue_schedule_type -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe SubscriptionRevenue_schedule_type
subscriptionRevenue_schedule_type Subscription
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (SubscriptionShipping -> [Pair])
-> Maybe SubscriptionShipping
-> [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])
-> (SubscriptionShipping -> Pair) -> SubscriptionShipping -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"shipping" Key -> SubscriptionShipping -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe SubscriptionShipping
subscriptionShipping Subscription
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
"started_with_gift" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Bool
subscriptionStarted_with_gift Subscription
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (SubscriptionState -> [Pair])
-> Maybe SubscriptionState
-> [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])
-> (SubscriptionState -> Pair) -> SubscriptionState -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"state" Key -> SubscriptionState -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe SubscriptionState
subscriptionState Subscription
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
"subtotal" Key -> Float -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Float
subscriptionSubtotal Subscription
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
"tax" Key -> Float -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Float
subscriptionTax Subscription
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..=)) (Subscription -> Maybe Bool
subscriptionTax_inclusive Subscription
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (TaxInfo -> [Pair]) -> Maybe TaxInfo -> [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]) -> (TaxInfo -> Pair) -> TaxInfo -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"tax_info" Key -> TaxInfo -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe TaxInfo
subscriptionTax_info Subscription
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
"terms_and_conditions" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Text
subscriptionTerms_and_conditions Subscription
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
"total" Key -> Float -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Float
subscriptionTotal Subscription
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..=)) (Subscription -> Maybe Int
subscriptionTotal_billing_cycles Subscription
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..=)) (Subscription -> Maybe JsonDateTime
subscriptionTrial_ends_at Subscription
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_started_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionTrial_started_at Subscription
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..=)) (Subscription -> Maybe Float
subscriptionUnit_amount Subscription
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
"updated_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionUpdated_at Subscription
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
"uuid" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Text
subscriptionUuid Subscription
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [[Pair]]
forall a. Monoid a => a
GHC.Base.mempty))
toEncoding :: Subscription -> Encoding
toEncoding Subscription
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]
-> (AccountMini -> [Series]) -> Maybe AccountMini -> [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])
-> (AccountMini -> Series) -> AccountMini -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"account" Key -> AccountMini -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe AccountMini
subscriptionAccount Subscription
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Object -> [Series]) -> Maybe Object -> [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]) -> (Object -> Series) -> Object -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"action_result" Key -> Object -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Object
subscriptionAction_result Subscription
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
"activated_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionActivated_at Subscription
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
"active_invoice_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..=)) (Subscription -> Maybe Text
subscriptionActive_invoice_id Subscription
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> ([SubscriptionAddOn] -> [Series])
-> Maybe [SubscriptionAddOn]
-> [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])
-> ([SubscriptionAddOn] -> Series)
-> [SubscriptionAddOn]
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"add_ons" Key -> [SubscriptionAddOn] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe [SubscriptionAddOn]
subscriptionAdd_ons Subscription
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
"add_ons_total" Key -> Float -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Float
subscriptionAdd_ons_total Subscription
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..=)) (Subscription -> Maybe Bool
subscriptionAuto_renew Subscription
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
"bank_account_authorized_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionBank_account_authorized_at Subscription
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
"billing_info_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..=)) (Subscription -> Maybe Text
subscriptionBilling_info_id Subscription
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
"business_entity_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..=)) (Subscription -> Maybe Text
subscriptionBusiness_entity_id Subscription
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
"canceled_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionCanceled_at Subscription
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (SubscriptionCollection_method -> [Series])
-> Maybe SubscriptionCollection_method
-> [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])
-> (SubscriptionCollection_method -> Series)
-> SubscriptionCollection_method
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"collection_method" Key -> SubscriptionCollection_method -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe SubscriptionCollection_method
subscriptionCollection_method Subscription
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
"converted_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionConverted_at Subscription
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> ([CouponRedemptionMini] -> [Series])
-> Maybe [CouponRedemptionMini]
-> [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])
-> ([CouponRedemptionMini] -> Series)
-> [CouponRedemptionMini]
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"coupon_redemptions" Key -> [CouponRedemptionMini] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe [CouponRedemptionMini]
subscriptionCoupon_redemptions Subscription
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
"created_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionCreated_at Subscription
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
"currency" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Text
subscriptionCurrency Subscription
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
"current_period_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionCurrent_period_ends_at Subscription
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
"current_period_started_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionCurrent_period_started_at Subscription
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
"current_term_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionCurrent_term_ends_at Subscription
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
"current_term_started_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionCurrent_term_started_at Subscription
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..=)) (Subscription -> Maybe CustomFields
subscriptionCustom_fields Subscription
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
"customer_notes" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Text
subscriptionCustomer_notes Subscription
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
"expiration_reason" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Text
subscriptionExpiration_reason Subscription
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
"expires_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionExpires_at Subscription
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
"gateway_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..=)) (Subscription -> Maybe Text
subscriptionGateway_code Subscription
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..=)) (Subscription -> Maybe Text
subscriptionId Subscription
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
"net_terms" Key -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Int
subscriptionNet_terms Subscription
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (SubscriptionNet_terms_type -> [Series])
-> Maybe SubscriptionNet_terms_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])
-> (SubscriptionNet_terms_type -> Series)
-> SubscriptionNet_terms_type
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"net_terms_type" Key -> SubscriptionNet_terms_type -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe SubscriptionNet_terms_type
subscriptionNet_terms_type Subscription
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
"object" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Text
subscriptionObject Subscription
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
"paused_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionPaused_at Subscription
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (SubscriptionChange -> [Series])
-> Maybe SubscriptionChange
-> [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])
-> (SubscriptionChange -> Series) -> SubscriptionChange -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"pending_change" Key -> SubscriptionChange -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe SubscriptionChange
subscriptionPending_change Subscription
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (PlanMini -> [Series]) -> Maybe PlanMini -> [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])
-> (PlanMini -> Series) -> PlanMini -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"plan" Key -> PlanMini -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe PlanMini
subscriptionPlan Subscription
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
"po_number" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Text
subscriptionPo_number Subscription
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..=)) (Subscription -> Maybe Int
subscriptionQuantity Subscription
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> ([SubscriptionRampIntervalResponse] -> [Series])
-> Maybe [SubscriptionRampIntervalResponse]
-> [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])
-> ([SubscriptionRampIntervalResponse] -> Series)
-> [SubscriptionRampIntervalResponse]
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"ramp_intervals" Key -> [SubscriptionRampIntervalResponse] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe [SubscriptionRampIntervalResponse]
subscriptionRamp_intervals Subscription
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
"remaining_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..=)) (Subscription -> Maybe Int
subscriptionRemaining_billing_cycles Subscription
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
"remaining_pause_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..=)) (Subscription -> Maybe Int
subscriptionRemaining_pause_cycles Subscription
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..=)) (Subscription -> Maybe Int
subscriptionRenewal_billing_cycles Subscription
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (SubscriptionRevenue_schedule_type -> [Series])
-> Maybe SubscriptionRevenue_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])
-> (SubscriptionRevenue_schedule_type -> Series)
-> SubscriptionRevenue_schedule_type
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"revenue_schedule_type" Key -> SubscriptionRevenue_schedule_type -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe SubscriptionRevenue_schedule_type
subscriptionRevenue_schedule_type Subscription
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (SubscriptionShipping -> [Series])
-> Maybe SubscriptionShipping
-> [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])
-> (SubscriptionShipping -> Series)
-> SubscriptionShipping
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"shipping" Key -> SubscriptionShipping -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe SubscriptionShipping
subscriptionShipping Subscription
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
"started_with_gift" Key -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Bool
subscriptionStarted_with_gift Subscription
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (SubscriptionState -> [Series])
-> Maybe SubscriptionState
-> [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])
-> (SubscriptionState -> Series) -> SubscriptionState -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"state" Key -> SubscriptionState -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe SubscriptionState
subscriptionState Subscription
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
"subtotal" Key -> Float -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Float
subscriptionSubtotal Subscription
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
"tax" Key -> Float -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Float
subscriptionTax Subscription
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..=)) (Subscription -> Maybe Bool
subscriptionTax_inclusive Subscription
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (TaxInfo -> [Series]) -> Maybe TaxInfo -> [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]) -> (TaxInfo -> Series) -> TaxInfo -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"tax_info" Key -> TaxInfo -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe TaxInfo
subscriptionTax_info Subscription
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
"terms_and_conditions" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Text
subscriptionTerms_and_conditions Subscription
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
"total" Key -> Float -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Float
subscriptionTotal Subscription
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..=)) (Subscription -> Maybe Int
subscriptionTotal_billing_cycles Subscription
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..=)) (Subscription -> Maybe JsonDateTime
subscriptionTrial_ends_at Subscription
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_started_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionTrial_started_at Subscription
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..=)) (Subscription -> Maybe Float
subscriptionUnit_amount Subscription
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
"updated_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..=)) (Subscription -> Maybe JsonDateTime
subscriptionUpdated_at Subscription
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
"uuid" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (Subscription -> Maybe Text
subscriptionUuid Subscription
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [[Series]]
forall a. Monoid a => a
GHC.Base.mempty)))
instance Data.Aeson.Types.FromJSON.FromJSON Subscription where
parseJSON :: Value -> Parser Subscription
parseJSON = String
-> (Object -> Parser Subscription) -> Value -> Parser Subscription
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"Subscription" (\Object
obj -> ((((((((((((((((((((((((((((((((((((((((((((((((((((((Maybe AccountMini
-> Maybe Object
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe [SubscriptionAddOn]
-> Maybe Float
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser
(Maybe AccountMini
-> Maybe Object
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe [SubscriptionAddOn]
-> Maybe Float
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe AccountMini
-> Maybe Object
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe [SubscriptionAddOn]
-> Maybe Float
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription
Subscription Parser
(Maybe AccountMini
-> Maybe Object
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe [SubscriptionAddOn]
-> Maybe Float
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe AccountMini)
-> Parser
(Maybe Object
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe [SubscriptionAddOn]
-> Maybe Float
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 AccountMini)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"account")) Parser
(Maybe Object
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe [SubscriptionAddOn]
-> Maybe Float
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Object)
-> Parser
(Maybe JsonDateTime
-> Maybe Text
-> Maybe [SubscriptionAddOn]
-> Maybe Float
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 Object)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"action_result")) Parser
(Maybe JsonDateTime
-> Maybe Text
-> Maybe [SubscriptionAddOn]
-> Maybe Float
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe Text
-> Maybe [SubscriptionAddOn]
-> Maybe Float
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"activated_at")) Parser
(Maybe Text
-> Maybe [SubscriptionAddOn]
-> Maybe Float
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Text)
-> Parser
(Maybe [SubscriptionAddOn]
-> Maybe Float
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"active_invoice_id")) Parser
(Maybe [SubscriptionAddOn]
-> Maybe Float
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe [SubscriptionAddOn])
-> Parser
(Maybe Float
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 [SubscriptionAddOn])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"add_ons")) Parser
(Maybe Float
-> Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Float)
-> Parser
(Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"add_ons_total")) Parser
(Maybe Bool
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Bool)
-> Parser
(Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"bank_account_authorized_at")) Parser
(Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"billing_info_id")) Parser
(Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Text)
-> Parser
(Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"business_entity_id")) Parser
(Maybe JsonDateTime
-> Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"canceled_at")) Parser
(Maybe SubscriptionCollection_method
-> Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe SubscriptionCollection_method)
-> Parser
(Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 SubscriptionCollection_method)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"collection_method")) Parser
(Maybe JsonDateTime
-> Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"converted_at")) Parser
(Maybe [CouponRedemptionMini]
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe [CouponRedemptionMini])
-> Parser
(Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 [CouponRedemptionMini])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"coupon_redemptions")) Parser
(Maybe JsonDateTime
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"created_at")) Parser
(Maybe Text
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Text)
-> Parser
(Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"currency")) Parser
(Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"current_period_ends_at")) Parser
(Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"current_period_started_at")) Parser
(Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"current_term_ends_at")) Parser
(Maybe JsonDateTime
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"current_term_started_at")) Parser
(Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe CustomFields)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"customer_notes")) Parser
(Maybe Text
-> Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Text)
-> Parser
(Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"expiration_reason")) Parser
(Maybe JsonDateTime
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"expires_at")) Parser
(Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"gateway_code")) Parser
(Maybe Text
-> Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Text)
-> Parser
(Maybe Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 Int
-> Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Int)
-> Parser
(Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"net_terms")) Parser
(Maybe SubscriptionNet_terms_type
-> Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe SubscriptionNet_terms_type)
-> Parser
(Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 SubscriptionNet_terms_type)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"net_terms_type")) Parser
(Maybe Text
-> Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Text)
-> Parser
(Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"object")) Parser
(Maybe JsonDateTime
-> Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"paused_at")) Parser
(Maybe SubscriptionChange
-> Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe SubscriptionChange)
-> Parser
(Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 SubscriptionChange)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"pending_change")) Parser
(Maybe PlanMini
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe PlanMini)
-> Parser
(Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 PlanMini)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"plan")) Parser
(Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Text)
-> Parser
(Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"po_number")) Parser
(Maybe Int
-> Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Int)
-> Parser
(Maybe [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 [SubscriptionRampIntervalResponse]
-> Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe [SubscriptionRampIntervalResponse])
-> Parser
(Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 [SubscriptionRampIntervalResponse])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"ramp_intervals")) Parser
(Maybe Int
-> Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Int)
-> Parser
(Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"remaining_billing_cycles")) Parser
(Maybe Int
-> Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Int)
-> Parser
(Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"remaining_pause_cycles")) Parser
(Maybe Int
-> Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Int)
-> Parser
(Maybe SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 SubscriptionRevenue_schedule_type
-> Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe SubscriptionRevenue_schedule_type)
-> Parser
(Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 SubscriptionRevenue_schedule_type)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"revenue_schedule_type")) Parser
(Maybe SubscriptionShipping
-> Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe SubscriptionShipping)
-> Parser
(Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 SubscriptionShipping)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"shipping")) Parser
(Maybe Bool
-> Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Bool)
-> Parser
(Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"started_with_gift")) Parser
(Maybe SubscriptionState
-> Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe SubscriptionState)
-> Parser
(Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 SubscriptionState)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"state")) Parser
(Maybe Float
-> Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Float)
-> Parser
(Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"subtotal")) Parser
(Maybe Float
-> Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Float)
-> Parser
(Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"tax")) Parser
(Maybe Bool
-> Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Bool)
-> Parser
(Maybe TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 TaxInfo
-> Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe TaxInfo)
-> Parser
(Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 TaxInfo)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"tax_info")) Parser
(Maybe Text
-> Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Text)
-> Parser
(Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"terms_and_conditions")) Parser
(Maybe Float
-> Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Float)
-> Parser
(Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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
"total")) Parser
(Maybe Int
-> Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe Int)
-> Parser
(Maybe JsonDateTime
-> Maybe JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
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 JsonDateTime
-> Maybe Float
-> Maybe JsonDateTime
-> Maybe Text
-> Subscription)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe JsonDateTime
-> Maybe Float -> Maybe JsonDateTime -> Maybe Text -> Subscription)
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 JsonDateTime
-> Maybe Float -> Maybe JsonDateTime -> Maybe Text -> Subscription)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe Float -> Maybe JsonDateTime -> Maybe Text -> Subscription)
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_started_at")) Parser
(Maybe Float -> Maybe JsonDateTime -> Maybe Text -> Subscription)
-> Parser (Maybe Float)
-> Parser (Maybe JsonDateTime -> Maybe Text -> Subscription)
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 JsonDateTime -> Maybe Text -> Subscription)
-> Parser (Maybe JsonDateTime)
-> Parser (Maybe Text -> Subscription)
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
"updated_at")) Parser (Maybe Text -> Subscription)
-> Parser (Maybe Text) -> Parser Subscription
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
"uuid"))
mkSubscription :: Subscription
mkSubscription :: Subscription
mkSubscription =
Subscription
{ subscriptionAccount :: Maybe AccountMini
subscriptionAccount = Maybe AccountMini
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionAction_result :: Maybe Object
subscriptionAction_result = Maybe Object
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionActivated_at :: Maybe JsonDateTime
subscriptionActivated_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionActive_invoice_id :: Maybe Text
subscriptionActive_invoice_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionAdd_ons :: Maybe [SubscriptionAddOn]
subscriptionAdd_ons = Maybe [SubscriptionAddOn]
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionAdd_ons_total :: Maybe Float
subscriptionAdd_ons_total = Maybe Float
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionAuto_renew :: Maybe Bool
subscriptionAuto_renew = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionBank_account_authorized_at :: Maybe JsonDateTime
subscriptionBank_account_authorized_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionBilling_info_id :: Maybe Text
subscriptionBilling_info_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionBusiness_entity_id :: Maybe Text
subscriptionBusiness_entity_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCanceled_at :: Maybe JsonDateTime
subscriptionCanceled_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCollection_method :: Maybe SubscriptionCollection_method
subscriptionCollection_method = Maybe SubscriptionCollection_method
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionConverted_at :: Maybe JsonDateTime
subscriptionConverted_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCoupon_redemptions :: Maybe [CouponRedemptionMini]
subscriptionCoupon_redemptions = Maybe [CouponRedemptionMini]
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreated_at :: Maybe JsonDateTime
subscriptionCreated_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCurrency :: Maybe Text
subscriptionCurrency = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCurrent_period_ends_at :: Maybe JsonDateTime
subscriptionCurrent_period_ends_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCurrent_period_started_at :: Maybe JsonDateTime
subscriptionCurrent_period_started_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCurrent_term_ends_at :: Maybe JsonDateTime
subscriptionCurrent_term_ends_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCurrent_term_started_at :: Maybe JsonDateTime
subscriptionCurrent_term_started_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCustom_fields :: Maybe CustomFields
subscriptionCustom_fields = Maybe CustomFields
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCustomer_notes :: Maybe Text
subscriptionCustomer_notes = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionExpiration_reason :: Maybe Text
subscriptionExpiration_reason = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionExpires_at :: Maybe JsonDateTime
subscriptionExpires_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionGateway_code :: Maybe Text
subscriptionGateway_code = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionId :: Maybe Text
subscriptionId = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionNet_terms :: Maybe Int
subscriptionNet_terms = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionNet_terms_type :: Maybe SubscriptionNet_terms_type
subscriptionNet_terms_type = Maybe SubscriptionNet_terms_type
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionObject :: Maybe Text
subscriptionObject = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPaused_at :: Maybe JsonDateTime
subscriptionPaused_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPending_change :: Maybe SubscriptionChange
subscriptionPending_change = Maybe SubscriptionChange
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPlan :: Maybe PlanMini
subscriptionPlan = Maybe PlanMini
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionPo_number :: Maybe Text
subscriptionPo_number = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionQuantity :: Maybe Int
subscriptionQuantity = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionRamp_intervals :: Maybe [SubscriptionRampIntervalResponse]
subscriptionRamp_intervals = Maybe [SubscriptionRampIntervalResponse]
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionRemaining_billing_cycles :: Maybe Int
subscriptionRemaining_billing_cycles = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionRemaining_pause_cycles :: Maybe Int
subscriptionRemaining_pause_cycles = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionRenewal_billing_cycles :: Maybe Int
subscriptionRenewal_billing_cycles = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionRevenue_schedule_type :: Maybe SubscriptionRevenue_schedule_type
subscriptionRevenue_schedule_type = Maybe SubscriptionRevenue_schedule_type
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionShipping :: Maybe SubscriptionShipping
subscriptionShipping = Maybe SubscriptionShipping
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionStarted_with_gift :: Maybe Bool
subscriptionStarted_with_gift = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionState :: Maybe SubscriptionState
subscriptionState = Maybe SubscriptionState
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionSubtotal :: Maybe Float
subscriptionSubtotal = Maybe Float
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionTax :: Maybe Float
subscriptionTax = Maybe Float
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionTax_inclusive :: Maybe Bool
subscriptionTax_inclusive = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionTax_info :: Maybe TaxInfo
subscriptionTax_info = Maybe TaxInfo
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionTerms_and_conditions :: Maybe Text
subscriptionTerms_and_conditions = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionTotal :: Maybe Float
subscriptionTotal = Maybe Float
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionTotal_billing_cycles :: Maybe Int
subscriptionTotal_billing_cycles = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionTrial_ends_at :: Maybe JsonDateTime
subscriptionTrial_ends_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionTrial_started_at :: Maybe JsonDateTime
subscriptionTrial_started_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionUnit_amount :: Maybe Float
subscriptionUnit_amount = Maybe Float
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionUpdated_at :: Maybe JsonDateTime
subscriptionUpdated_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionUuid :: Maybe Text
subscriptionUuid = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
}
data SubscriptionCollection_method
=
SubscriptionCollection_methodOther Data.Aeson.Types.Internal.Value
|
SubscriptionCollection_methodTyped Data.Text.Internal.Text
|
SubscriptionCollection_methodEnumAutomatic
|
SubscriptionCollection_methodEnumManual
deriving (Int -> SubscriptionCollection_method -> ShowS
[SubscriptionCollection_method] -> ShowS
SubscriptionCollection_method -> String
(Int -> SubscriptionCollection_method -> ShowS)
-> (SubscriptionCollection_method -> String)
-> ([SubscriptionCollection_method] -> ShowS)
-> Show SubscriptionCollection_method
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionCollection_method -> ShowS
showsPrec :: Int -> SubscriptionCollection_method -> ShowS
$cshow :: SubscriptionCollection_method -> String
show :: SubscriptionCollection_method -> String
$cshowList :: [SubscriptionCollection_method] -> ShowS
showList :: [SubscriptionCollection_method] -> ShowS
GHC.Show.Show, SubscriptionCollection_method
-> SubscriptionCollection_method -> Bool
(SubscriptionCollection_method
-> SubscriptionCollection_method -> Bool)
-> (SubscriptionCollection_method
-> SubscriptionCollection_method -> Bool)
-> Eq SubscriptionCollection_method
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptionCollection_method
-> SubscriptionCollection_method -> Bool
== :: SubscriptionCollection_method
-> SubscriptionCollection_method -> Bool
$c/= :: SubscriptionCollection_method
-> SubscriptionCollection_method -> Bool
/= :: SubscriptionCollection_method
-> SubscriptionCollection_method -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionCollection_method where
toJSON :: SubscriptionCollection_method -> Value
toJSON (SubscriptionCollection_methodOther Value
val) = Value
val
toJSON (SubscriptionCollection_methodTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (SubscriptionCollection_method
SubscriptionCollection_methodEnumAutomatic) = Value
"automatic"
toJSON (SubscriptionCollection_method
SubscriptionCollection_methodEnumManual) = Value
"manual"
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionCollection_method where
parseJSON :: Value -> Parser SubscriptionCollection_method
parseJSON Value
val =
SubscriptionCollection_method
-> Parser SubscriptionCollection_method
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
"automatic" -> SubscriptionCollection_method
SubscriptionCollection_methodEnumAutomatic
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"manual" -> SubscriptionCollection_method
SubscriptionCollection_methodEnumManual
| Bool
GHC.Base.otherwise -> Value -> SubscriptionCollection_method
SubscriptionCollection_methodOther Value
val
)
data SubscriptionNet_terms_type
=
SubscriptionNet_terms_typeOther Data.Aeson.Types.Internal.Value
|
SubscriptionNet_terms_typeTyped Data.Text.Internal.Text
|
SubscriptionNet_terms_typeEnumNet
|
SubscriptionNet_terms_typeEnumEom
deriving (Int -> SubscriptionNet_terms_type -> ShowS
[SubscriptionNet_terms_type] -> ShowS
SubscriptionNet_terms_type -> String
(Int -> SubscriptionNet_terms_type -> ShowS)
-> (SubscriptionNet_terms_type -> String)
-> ([SubscriptionNet_terms_type] -> ShowS)
-> Show SubscriptionNet_terms_type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionNet_terms_type -> ShowS
showsPrec :: Int -> SubscriptionNet_terms_type -> ShowS
$cshow :: SubscriptionNet_terms_type -> String
show :: SubscriptionNet_terms_type -> String
$cshowList :: [SubscriptionNet_terms_type] -> ShowS
showList :: [SubscriptionNet_terms_type] -> ShowS
GHC.Show.Show, SubscriptionNet_terms_type -> SubscriptionNet_terms_type -> Bool
(SubscriptionNet_terms_type -> SubscriptionNet_terms_type -> Bool)
-> (SubscriptionNet_terms_type
-> SubscriptionNet_terms_type -> Bool)
-> Eq SubscriptionNet_terms_type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptionNet_terms_type -> SubscriptionNet_terms_type -> Bool
== :: SubscriptionNet_terms_type -> SubscriptionNet_terms_type -> Bool
$c/= :: SubscriptionNet_terms_type -> SubscriptionNet_terms_type -> Bool
/= :: SubscriptionNet_terms_type -> SubscriptionNet_terms_type -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionNet_terms_type where
toJSON :: SubscriptionNet_terms_type -> Value
toJSON (SubscriptionNet_terms_typeOther Value
val) = Value
val
toJSON (SubscriptionNet_terms_typeTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (SubscriptionNet_terms_type
SubscriptionNet_terms_typeEnumNet) = Value
"net"
toJSON (SubscriptionNet_terms_type
SubscriptionNet_terms_typeEnumEom) = Value
"eom"
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionNet_terms_type where
parseJSON :: Value -> Parser SubscriptionNet_terms_type
parseJSON Value
val =
SubscriptionNet_terms_type -> Parser SubscriptionNet_terms_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
"net" -> SubscriptionNet_terms_type
SubscriptionNet_terms_typeEnumNet
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"eom" -> SubscriptionNet_terms_type
SubscriptionNet_terms_typeEnumEom
| Bool
GHC.Base.otherwise -> Value -> SubscriptionNet_terms_type
SubscriptionNet_terms_typeOther Value
val
)
data SubscriptionRevenue_schedule_type
=
SubscriptionRevenue_schedule_typeOther Data.Aeson.Types.Internal.Value
|
SubscriptionRevenue_schedule_typeTyped Data.Text.Internal.Text
|
SubscriptionRevenue_schedule_typeEnumAt_range_end
|
SubscriptionRevenue_schedule_typeEnumAt_range_start
|
SubscriptionRevenue_schedule_typeEnumEvenly
|
SubscriptionRevenue_schedule_typeEnumNever
deriving (Int -> SubscriptionRevenue_schedule_type -> ShowS
[SubscriptionRevenue_schedule_type] -> ShowS
SubscriptionRevenue_schedule_type -> String
(Int -> SubscriptionRevenue_schedule_type -> ShowS)
-> (SubscriptionRevenue_schedule_type -> String)
-> ([SubscriptionRevenue_schedule_type] -> ShowS)
-> Show SubscriptionRevenue_schedule_type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionRevenue_schedule_type -> ShowS
showsPrec :: Int -> SubscriptionRevenue_schedule_type -> ShowS
$cshow :: SubscriptionRevenue_schedule_type -> String
show :: SubscriptionRevenue_schedule_type -> String
$cshowList :: [SubscriptionRevenue_schedule_type] -> ShowS
showList :: [SubscriptionRevenue_schedule_type] -> ShowS
GHC.Show.Show, SubscriptionRevenue_schedule_type
-> SubscriptionRevenue_schedule_type -> Bool
(SubscriptionRevenue_schedule_type
-> SubscriptionRevenue_schedule_type -> Bool)
-> (SubscriptionRevenue_schedule_type
-> SubscriptionRevenue_schedule_type -> Bool)
-> Eq SubscriptionRevenue_schedule_type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptionRevenue_schedule_type
-> SubscriptionRevenue_schedule_type -> Bool
== :: SubscriptionRevenue_schedule_type
-> SubscriptionRevenue_schedule_type -> Bool
$c/= :: SubscriptionRevenue_schedule_type
-> SubscriptionRevenue_schedule_type -> Bool
/= :: SubscriptionRevenue_schedule_type
-> SubscriptionRevenue_schedule_type -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionRevenue_schedule_type where
toJSON :: SubscriptionRevenue_schedule_type -> Value
toJSON (SubscriptionRevenue_schedule_typeOther Value
val) = Value
val
toJSON (SubscriptionRevenue_schedule_typeTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (SubscriptionRevenue_schedule_type
SubscriptionRevenue_schedule_typeEnumAt_range_end) = Value
"at_range_end"
toJSON (SubscriptionRevenue_schedule_type
SubscriptionRevenue_schedule_typeEnumAt_range_start) = Value
"at_range_start"
toJSON (SubscriptionRevenue_schedule_type
SubscriptionRevenue_schedule_typeEnumEvenly) = Value
"evenly"
toJSON (SubscriptionRevenue_schedule_type
SubscriptionRevenue_schedule_typeEnumNever) = Value
"never"
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionRevenue_schedule_type where
parseJSON :: Value -> Parser SubscriptionRevenue_schedule_type
parseJSON Value
val =
SubscriptionRevenue_schedule_type
-> Parser SubscriptionRevenue_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" -> SubscriptionRevenue_schedule_type
SubscriptionRevenue_schedule_typeEnumAt_range_end
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"at_range_start" -> SubscriptionRevenue_schedule_type
SubscriptionRevenue_schedule_typeEnumAt_range_start
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"evenly" -> SubscriptionRevenue_schedule_type
SubscriptionRevenue_schedule_typeEnumEvenly
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"never" -> SubscriptionRevenue_schedule_type
SubscriptionRevenue_schedule_typeEnumNever
| Bool
GHC.Base.otherwise -> Value -> SubscriptionRevenue_schedule_type
SubscriptionRevenue_schedule_typeOther Value
val
)
data SubscriptionState
=
SubscriptionStateOther Data.Aeson.Types.Internal.Value
|
SubscriptionStateTyped Data.Text.Internal.Text
|
SubscriptionStateEnumActive
|
SubscriptionStateEnumCanceled
|
SubscriptionStateEnumExpired
|
SubscriptionStateEnumFailed
|
SubscriptionStateEnumFuture
|
SubscriptionStateEnumPaused
deriving (Int -> SubscriptionState -> ShowS
[SubscriptionState] -> ShowS
SubscriptionState -> String
(Int -> SubscriptionState -> ShowS)
-> (SubscriptionState -> String)
-> ([SubscriptionState] -> ShowS)
-> Show SubscriptionState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionState -> ShowS
showsPrec :: Int -> SubscriptionState -> ShowS
$cshow :: SubscriptionState -> String
show :: SubscriptionState -> String
$cshowList :: [SubscriptionState] -> ShowS
showList :: [SubscriptionState] -> ShowS
GHC.Show.Show, SubscriptionState -> SubscriptionState -> Bool
(SubscriptionState -> SubscriptionState -> Bool)
-> (SubscriptionState -> SubscriptionState -> Bool)
-> Eq SubscriptionState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptionState -> SubscriptionState -> Bool
== :: SubscriptionState -> SubscriptionState -> Bool
$c/= :: SubscriptionState -> SubscriptionState -> Bool
/= :: SubscriptionState -> SubscriptionState -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionState where
toJSON :: SubscriptionState -> Value
toJSON (SubscriptionStateOther Value
val) = Value
val
toJSON (SubscriptionStateTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (SubscriptionState
SubscriptionStateEnumActive) = Value
"active"
toJSON (SubscriptionState
SubscriptionStateEnumCanceled) = Value
"canceled"
toJSON (SubscriptionState
SubscriptionStateEnumExpired) = Value
"expired"
toJSON (SubscriptionState
SubscriptionStateEnumFailed) = Value
"failed"
toJSON (SubscriptionState
SubscriptionStateEnumFuture) = Value
"future"
toJSON (SubscriptionState
SubscriptionStateEnumPaused) = Value
"paused"
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionState where
parseJSON :: Value -> Parser SubscriptionState
parseJSON Value
val =
SubscriptionState -> Parser SubscriptionState
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
"active" -> SubscriptionState
SubscriptionStateEnumActive
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"canceled" -> SubscriptionState
SubscriptionStateEnumCanceled
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"expired" -> SubscriptionState
SubscriptionStateEnumExpired
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"failed" -> SubscriptionState
SubscriptionStateEnumFailed
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"future" -> SubscriptionState
SubscriptionStateEnumFuture
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"paused" -> SubscriptionState
SubscriptionStateEnumPaused
| Bool
GHC.Base.otherwise -> Value -> SubscriptionState
SubscriptionStateOther Value
val
)