{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module RecurlyClient.Types.SubscriptionCreate 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.AccountCreate
import {-# SOURCE #-} RecurlyClient.Types.SubscriptionAddOnCreate
import {-# SOURCE #-} RecurlyClient.Types.SubscriptionRampInterval
import {-# SOURCE #-} RecurlyClient.Types.SubscriptionShippingCreate
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe
data SubscriptionCreate = SubscriptionCreate
{ SubscriptionCreate -> AccountCreate
subscriptionCreateAccount :: AccountCreate
, SubscriptionCreate -> Maybe [SubscriptionAddOnCreate]
subscriptionCreateAdd_ons :: (GHC.Maybe.Maybe [SubscriptionAddOnCreate])
, SubscriptionCreate -> Maybe Bool
subscriptionCreateAuto_renew :: (GHC.Maybe.Maybe GHC.Types.Bool)
, SubscriptionCreate -> Maybe Text
subscriptionCreateBilling_info_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, SubscriptionCreate -> Maybe Bool
subscriptionCreateBulk :: (GHC.Maybe.Maybe GHC.Types.Bool)
, SubscriptionCreate -> Maybe Text
subscriptionCreateBusiness_entity_code :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, SubscriptionCreate -> Maybe Text
subscriptionCreateBusiness_entity_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, SubscriptionCreate -> Maybe SubscriptionCreateCollection_method
subscriptionCreateCollection_method :: (GHC.Maybe.Maybe SubscriptionCreateCollection_method)
, SubscriptionCreate -> Maybe [Text]
subscriptionCreateCoupon_codes :: (GHC.Maybe.Maybe [Data.Text.Internal.Text])
, SubscriptionCreate -> Maybe Text
subscriptionCreateCredit_customer_notes :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, SubscriptionCreate -> Text
subscriptionCreateCurrency :: Data.Text.Internal.Text
, SubscriptionCreate -> Maybe CustomFields
subscriptionCreateCustom_fields :: (GHC.Maybe.Maybe CustomFields)
, SubscriptionCreate -> Maybe Text
subscriptionCreateCustomer_notes :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, SubscriptionCreate -> Maybe Text
subscriptionCreateGateway_code :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, SubscriptionCreate -> Maybe Text
subscriptionCreateGift_card_redemption_code :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, SubscriptionCreate -> Maybe Int
subscriptionCreateNet_terms :: (GHC.Maybe.Maybe GHC.Types.Int)
, SubscriptionCreate -> Maybe SubscriptionCreateNet_terms_type
subscriptionCreateNet_terms_type :: (GHC.Maybe.Maybe SubscriptionCreateNet_terms_type)
, SubscriptionCreate -> Maybe JsonDateTime
subscriptionCreateNext_bill_date :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, SubscriptionCreate -> Text
subscriptionCreatePlan_code :: Data.Text.Internal.Text
, SubscriptionCreate -> Maybe Text
subscriptionCreatePlan_id :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, SubscriptionCreate -> Maybe Text
subscriptionCreatePo_number :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, SubscriptionCreate -> Maybe Int
subscriptionCreateQuantity :: (GHC.Maybe.Maybe GHC.Types.Int)
, SubscriptionCreate -> Maybe [SubscriptionRampInterval]
subscriptionCreateRamp_intervals :: (GHC.Maybe.Maybe [SubscriptionRampInterval])
, SubscriptionCreate -> Maybe Int
subscriptionCreateRenewal_billing_cycles :: (GHC.Maybe.Maybe GHC.Types.Int)
, SubscriptionCreate -> Maybe SubscriptionCreateRevenue_schedule_type
subscriptionCreateRevenue_schedule_type :: (GHC.Maybe.Maybe SubscriptionCreateRevenue_schedule_type)
, SubscriptionCreate -> Maybe SubscriptionShippingCreate
subscriptionCreateShipping :: (GHC.Maybe.Maybe SubscriptionShippingCreate)
, SubscriptionCreate -> Maybe JsonDateTime
subscriptionCreateStarts_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, SubscriptionCreate -> Maybe Bool
subscriptionCreateTax_inclusive :: (GHC.Maybe.Maybe GHC.Types.Bool)
, SubscriptionCreate -> Maybe Text
subscriptionCreateTerms_and_conditions :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, SubscriptionCreate -> Maybe Int
subscriptionCreateTotal_billing_cycles :: (GHC.Maybe.Maybe GHC.Types.Int)
, SubscriptionCreate -> Maybe SubscriptionCreateTransaction_type
subscriptionCreateTransaction_type :: (GHC.Maybe.Maybe SubscriptionCreateTransaction_type)
, SubscriptionCreate -> Maybe JsonDateTime
subscriptionCreateTrial_ends_at :: (GHC.Maybe.Maybe RecurlyClient.Common.JsonDateTime)
, SubscriptionCreate -> Maybe Float
subscriptionCreateUnit_amount :: (GHC.Maybe.Maybe GHC.Types.Float)
}
deriving
( Int -> SubscriptionCreate -> ShowS
[SubscriptionCreate] -> ShowS
SubscriptionCreate -> String
(Int -> SubscriptionCreate -> ShowS)
-> (SubscriptionCreate -> String)
-> ([SubscriptionCreate] -> ShowS)
-> Show SubscriptionCreate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionCreate -> ShowS
showsPrec :: Int -> SubscriptionCreate -> ShowS
$cshow :: SubscriptionCreate -> String
show :: SubscriptionCreate -> String
$cshowList :: [SubscriptionCreate] -> ShowS
showList :: [SubscriptionCreate] -> ShowS
GHC.Show.Show
, SubscriptionCreate -> SubscriptionCreate -> Bool
(SubscriptionCreate -> SubscriptionCreate -> Bool)
-> (SubscriptionCreate -> SubscriptionCreate -> Bool)
-> Eq SubscriptionCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptionCreate -> SubscriptionCreate -> Bool
== :: SubscriptionCreate -> SubscriptionCreate -> Bool
$c/= :: SubscriptionCreate -> SubscriptionCreate -> Bool
/= :: SubscriptionCreate -> SubscriptionCreate -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionCreate where
toJSON :: SubscriptionCreate -> Value
toJSON SubscriptionCreate
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object ([[Pair]] -> [Pair]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Key
"account" Key -> AccountCreate -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..= SubscriptionCreate -> AccountCreate
subscriptionCreateAccount SubscriptionCreate
obj] [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> ([SubscriptionAddOnCreate] -> [Pair])
-> Maybe [SubscriptionAddOnCreate]
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> ([SubscriptionAddOnCreate] -> Pair)
-> [SubscriptionAddOnCreate]
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"add_ons" Key -> [SubscriptionAddOnCreate] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe [SubscriptionAddOnCreate]
subscriptionCreateAdd_ons SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Bool
subscriptionCreateAuto_renew SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateBilling_info_id SubscriptionCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Bool -> [Pair]) -> Maybe Bool -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Bool -> Pair) -> Bool -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"bulk" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe Bool
subscriptionCreateBulk SubscriptionCreate
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_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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateBusiness_entity_code SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateBusiness_entity_id SubscriptionCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (SubscriptionCreateCollection_method -> [Pair])
-> Maybe SubscriptionCreateCollection_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])
-> (SubscriptionCreateCollection_method -> Pair)
-> SubscriptionCreateCollection_method
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"collection_method" Key -> SubscriptionCreateCollection_method -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe SubscriptionCreateCollection_method
subscriptionCreateCollection_method SubscriptionCreate
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
"coupon_codes" Key -> [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe [Text]
subscriptionCreateCoupon_codes SubscriptionCreate
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
"credit_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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateCredit_customer_notes SubscriptionCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [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..= SubscriptionCreate -> Text
subscriptionCreateCurrency SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe CustomFields
subscriptionCreateCustom_fields SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateCustomer_notes SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateGateway_code SubscriptionCreate
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
"gift_card_redemption_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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateGift_card_redemption_code SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Int
subscriptionCreateNet_terms SubscriptionCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (SubscriptionCreateNet_terms_type -> [Pair])
-> Maybe SubscriptionCreateNet_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])
-> (SubscriptionCreateNet_terms_type -> Pair)
-> SubscriptionCreateNet_terms_type
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"net_terms_type" Key -> SubscriptionCreateNet_terms_type -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe SubscriptionCreateNet_terms_type
subscriptionCreateNet_terms_type SubscriptionCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (JsonDateTime -> [Pair]) -> Maybe JsonDateTime -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (JsonDateTime -> Pair) -> JsonDateTime -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"next_bill_date" Key -> JsonDateTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe JsonDateTime
subscriptionCreateNext_bill_date SubscriptionCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Key
"plan_code" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..= SubscriptionCreate -> Text
subscriptionCreatePlan_code SubscriptionCreate
obj] [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (Text -> [Pair]) -> Maybe Text -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair]) -> (Text -> Pair) -> Text -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"plan_id" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreatePlan_id SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreatePo_number SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Int
subscriptionCreateQuantity SubscriptionCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> ([SubscriptionRampInterval] -> [Pair])
-> Maybe [SubscriptionRampInterval]
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> ([SubscriptionRampInterval] -> Pair)
-> [SubscriptionRampInterval]
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"ramp_intervals" Key -> [SubscriptionRampInterval] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe [SubscriptionRampInterval]
subscriptionCreateRamp_intervals SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Int
subscriptionCreateRenewal_billing_cycles SubscriptionCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (SubscriptionCreateRevenue_schedule_type -> [Pair])
-> Maybe SubscriptionCreateRevenue_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])
-> (SubscriptionCreateRevenue_schedule_type -> Pair)
-> SubscriptionCreateRevenue_schedule_type
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"revenue_schedule_type" Key -> SubscriptionCreateRevenue_schedule_type -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe SubscriptionCreateRevenue_schedule_type
subscriptionCreateRevenue_schedule_type SubscriptionCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (SubscriptionShippingCreate -> [Pair])
-> Maybe SubscriptionShippingCreate
-> [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])
-> (SubscriptionShippingCreate -> Pair)
-> SubscriptionShippingCreate
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"shipping" Key -> SubscriptionShippingCreate -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe SubscriptionShippingCreate
subscriptionCreateShipping SubscriptionCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair] -> (JsonDateTime -> [Pair]) -> Maybe JsonDateTime -> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (JsonDateTime -> Pair) -> JsonDateTime -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"starts_at" Key -> JsonDateTime -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe JsonDateTime
subscriptionCreateStarts_at SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Bool
subscriptionCreateTax_inclusive SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateTerms_and_conditions SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Int
subscriptionCreateTotal_billing_cycles SubscriptionCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (SubscriptionCreateTransaction_type -> [Pair])
-> Maybe SubscriptionCreateTransaction_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])
-> (SubscriptionCreateTransaction_type -> Pair)
-> SubscriptionCreateTransaction_type
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"transaction_type" Key -> SubscriptionCreateTransaction_type -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe SubscriptionCreateTransaction_type
subscriptionCreateTransaction_type SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe JsonDateTime
subscriptionCreateTrial_ends_at SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Float
subscriptionCreateUnit_amount SubscriptionCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [[Pair]]
forall a. Monoid a => a
GHC.Base.mempty))
toEncoding :: SubscriptionCreate -> Encoding
toEncoding SubscriptionCreate
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 ([Key
"account" Key -> AccountCreate -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..= SubscriptionCreate -> AccountCreate
subscriptionCreateAccount SubscriptionCreate
obj] [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> ([SubscriptionAddOnCreate] -> [Series])
-> Maybe [SubscriptionAddOnCreate]
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> ([SubscriptionAddOnCreate] -> Series)
-> [SubscriptionAddOnCreate]
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"add_ons" Key -> [SubscriptionAddOnCreate] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe [SubscriptionAddOnCreate]
subscriptionCreateAdd_ons SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Bool
subscriptionCreateAuto_renew SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateBilling_info_id SubscriptionCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Bool -> [Series]) -> Maybe Bool -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Bool -> Series) -> Bool -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"bulk" Key -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe Bool
subscriptionCreateBulk SubscriptionCreate
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_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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateBusiness_entity_code SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateBusiness_entity_id SubscriptionCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (SubscriptionCreateCollection_method -> [Series])
-> Maybe SubscriptionCreateCollection_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])
-> (SubscriptionCreateCollection_method -> Series)
-> SubscriptionCreateCollection_method
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"collection_method" Key -> SubscriptionCreateCollection_method -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe SubscriptionCreateCollection_method
subscriptionCreateCollection_method SubscriptionCreate
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
"coupon_codes" Key -> [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe [Text]
subscriptionCreateCoupon_codes SubscriptionCreate
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
"credit_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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateCredit_customer_notes SubscriptionCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [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..= SubscriptionCreate -> Text
subscriptionCreateCurrency SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe CustomFields
subscriptionCreateCustom_fields SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateCustomer_notes SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateGateway_code SubscriptionCreate
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
"gift_card_redemption_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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateGift_card_redemption_code SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Int
subscriptionCreateNet_terms SubscriptionCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (SubscriptionCreateNet_terms_type -> [Series])
-> Maybe SubscriptionCreateNet_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])
-> (SubscriptionCreateNet_terms_type -> Series)
-> SubscriptionCreateNet_terms_type
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"net_terms_type" Key -> SubscriptionCreateNet_terms_type -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe SubscriptionCreateNet_terms_type
subscriptionCreateNet_terms_type SubscriptionCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (JsonDateTime -> [Series]) -> Maybe JsonDateTime -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (JsonDateTime -> Series) -> JsonDateTime -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"next_bill_date" Key -> JsonDateTime -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe JsonDateTime
subscriptionCreateNext_bill_date SubscriptionCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Key
"plan_code" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..= SubscriptionCreate -> Text
subscriptionCreatePlan_code SubscriptionCreate
obj] [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series] -> (Text -> [Series]) -> Maybe Text -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series]) -> (Text -> Series) -> Text -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"plan_id" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreatePlan_id SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreatePo_number SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Int
subscriptionCreateQuantity SubscriptionCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> ([SubscriptionRampInterval] -> [Series])
-> Maybe [SubscriptionRampInterval]
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> ([SubscriptionRampInterval] -> Series)
-> [SubscriptionRampInterval]
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"ramp_intervals" Key -> [SubscriptionRampInterval] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe [SubscriptionRampInterval]
subscriptionCreateRamp_intervals SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Int
subscriptionCreateRenewal_billing_cycles SubscriptionCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (SubscriptionCreateRevenue_schedule_type -> [Series])
-> Maybe SubscriptionCreateRevenue_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])
-> (SubscriptionCreateRevenue_schedule_type -> Series)
-> SubscriptionCreateRevenue_schedule_type
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"revenue_schedule_type" Key -> SubscriptionCreateRevenue_schedule_type -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe SubscriptionCreateRevenue_schedule_type
subscriptionCreateRevenue_schedule_type SubscriptionCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (SubscriptionShippingCreate -> [Series])
-> Maybe SubscriptionShippingCreate
-> [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])
-> (SubscriptionShippingCreate -> Series)
-> SubscriptionShippingCreate
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"shipping" Key -> SubscriptionShippingCreate -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe SubscriptionShippingCreate
subscriptionCreateShipping SubscriptionCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (JsonDateTime -> [Series]) -> Maybe JsonDateTime -> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (JsonDateTime -> Series) -> JsonDateTime -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"starts_at" Key -> JsonDateTime -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe JsonDateTime
subscriptionCreateStarts_at SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Bool
subscriptionCreateTax_inclusive SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Text
subscriptionCreateTerms_and_conditions SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Int
subscriptionCreateTotal_billing_cycles SubscriptionCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (SubscriptionCreateTransaction_type -> [Series])
-> Maybe SubscriptionCreateTransaction_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])
-> (SubscriptionCreateTransaction_type -> Series)
-> SubscriptionCreateTransaction_type
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"transaction_type" Key -> SubscriptionCreateTransaction_type -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (SubscriptionCreate -> Maybe SubscriptionCreateTransaction_type
subscriptionCreateTransaction_type SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe JsonDateTime
subscriptionCreateTrial_ends_at SubscriptionCreate
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..=)) (SubscriptionCreate -> Maybe Float
subscriptionCreateUnit_amount SubscriptionCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [[Series]]
forall a. Monoid a => a
GHC.Base.mempty)))
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionCreate where
parseJSON :: Value -> Parser SubscriptionCreate
parseJSON = String
-> (Object -> Parser SubscriptionCreate)
-> Value
-> Parser SubscriptionCreate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"SubscriptionCreate" (\Object
obj -> (((((((((((((((((((((((((((((((((AccountCreate
-> Maybe [SubscriptionAddOnCreate]
-> Maybe Bool
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser
(AccountCreate
-> Maybe [SubscriptionAddOnCreate]
-> Maybe Bool
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure AccountCreate
-> Maybe [SubscriptionAddOnCreate]
-> Maybe Bool
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate
SubscriptionCreate Parser
(AccountCreate
-> Maybe [SubscriptionAddOnCreate]
-> Maybe Bool
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser AccountCreate
-> Parser
(Maybe [SubscriptionAddOnCreate]
-> Maybe Bool
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 AccountCreate
forall a. FromJSON a => Object -> Key -> Parser a
Data.Aeson.Types.FromJSON..: Key
"account")) Parser
(Maybe [SubscriptionAddOnCreate]
-> Maybe Bool
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe [SubscriptionAddOnCreate])
-> Parser
(Maybe Bool
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe [SubscriptionAddOnCreate])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"add_ons")) Parser
(Maybe Bool
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Bool)
-> Parser
(Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Text)
-> Parser
(Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 Bool
-> Maybe Text
-> Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Bool)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"bulk")) Parser
(Maybe Text
-> Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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_code")) Parser
(Maybe Text
-> Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Text)
-> Parser
(Maybe SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 SubscriptionCreateCollection_method
-> Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe SubscriptionCreateCollection_method)
-> Parser
(Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 SubscriptionCreateCollection_method)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"collection_method")) Parser
(Maybe [Text]
-> Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe [Text])
-> Parser
(Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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
"coupon_codes")) Parser
(Maybe Text
-> Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Text)
-> Parser
(Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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
"credit_customer_notes")) Parser
(Text
-> Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser Text
-> Parser
(Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
Data.Aeson.Types.FromJSON..: Key
"currency")) Parser
(Maybe CustomFields
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe CustomFields)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Text)
-> Parser
(Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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
"gift_card_redemption_code")) Parser
(Maybe Int
-> Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Int)
-> Parser
(Maybe SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 SubscriptionCreateNet_terms_type
-> Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe SubscriptionCreateNet_terms_type)
-> Parser
(Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 SubscriptionCreateNet_terms_type)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"net_terms_type")) Parser
(Maybe JsonDateTime
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe JsonDateTime)
-> Parser
(Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe JsonDateTime)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"next_bill_date")) Parser
(Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser Text
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
Data.Aeson.Types.FromJSON..: Key
"plan_code")) Parser
(Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"plan_id")) Parser
(Maybe Text
-> Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Text)
-> Parser
(Maybe Int
-> Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Int)
-> Parser
(Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"quantity")) Parser
(Maybe [SubscriptionRampInterval]
-> Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe [SubscriptionRampInterval])
-> Parser
(Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe [SubscriptionRampInterval])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"ramp_intervals")) Parser
(Maybe Int
-> Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Int)
-> Parser
(Maybe SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 SubscriptionCreateRevenue_schedule_type
-> Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe SubscriptionCreateRevenue_schedule_type)
-> Parser
(Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 SubscriptionCreateRevenue_schedule_type)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"revenue_schedule_type")) Parser
(Maybe SubscriptionShippingCreate
-> Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe SubscriptionShippingCreate)
-> Parser
(Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 SubscriptionShippingCreate)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"shipping")) Parser
(Maybe JsonDateTime
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe JsonDateTime)
-> Parser
(Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe JsonDateTime)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"starts_at")) Parser
(Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Bool)
-> Parser
(Maybe Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 Text
-> Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Text)
-> Parser
(Maybe Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
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 Int
-> Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime
-> Maybe Float
-> SubscriptionCreate)
-> Parser (Maybe Int)
-> Parser
(Maybe SubscriptionCreateTransaction_type
-> Maybe JsonDateTime -> Maybe Float -> SubscriptionCreate)
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 SubscriptionCreateTransaction_type
-> Maybe JsonDateTime -> Maybe Float -> SubscriptionCreate)
-> Parser (Maybe SubscriptionCreateTransaction_type)
-> Parser (Maybe JsonDateTime -> Maybe Float -> SubscriptionCreate)
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 SubscriptionCreateTransaction_type)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"transaction_type")) Parser (Maybe JsonDateTime -> Maybe Float -> SubscriptionCreate)
-> Parser (Maybe JsonDateTime)
-> Parser (Maybe Float -> SubscriptionCreate)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Key -> Parser (Maybe JsonDateTime)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"trial_ends_at")) Parser (Maybe Float -> SubscriptionCreate)
-> Parser (Maybe Float) -> Parser SubscriptionCreate
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"))
mkSubscriptionCreate ::
AccountCreate ->
Data.Text.Internal.Text ->
Data.Text.Internal.Text ->
SubscriptionCreate
mkSubscriptionCreate :: AccountCreate -> Text -> Text -> SubscriptionCreate
mkSubscriptionCreate AccountCreate
subscriptionCreateAccount Text
subscriptionCreateCurrency Text
subscriptionCreatePlan_code =
SubscriptionCreate
{ subscriptionCreateAccount :: AccountCreate
subscriptionCreateAccount = AccountCreate
subscriptionCreateAccount
, subscriptionCreateAdd_ons :: Maybe [SubscriptionAddOnCreate]
subscriptionCreateAdd_ons = Maybe [SubscriptionAddOnCreate]
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateAuto_renew :: Maybe Bool
subscriptionCreateAuto_renew = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateBilling_info_id :: Maybe Text
subscriptionCreateBilling_info_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateBulk :: Maybe Bool
subscriptionCreateBulk = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateBusiness_entity_code :: Maybe Text
subscriptionCreateBusiness_entity_code = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateBusiness_entity_id :: Maybe Text
subscriptionCreateBusiness_entity_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateCollection_method :: Maybe SubscriptionCreateCollection_method
subscriptionCreateCollection_method = Maybe SubscriptionCreateCollection_method
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateCoupon_codes :: Maybe [Text]
subscriptionCreateCoupon_codes = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateCredit_customer_notes :: Maybe Text
subscriptionCreateCredit_customer_notes = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateCurrency :: Text
subscriptionCreateCurrency = Text
subscriptionCreateCurrency
, subscriptionCreateCustom_fields :: Maybe CustomFields
subscriptionCreateCustom_fields = Maybe CustomFields
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateCustomer_notes :: Maybe Text
subscriptionCreateCustomer_notes = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateGateway_code :: Maybe Text
subscriptionCreateGateway_code = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateGift_card_redemption_code :: Maybe Text
subscriptionCreateGift_card_redemption_code = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateNet_terms :: Maybe Int
subscriptionCreateNet_terms = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateNet_terms_type :: Maybe SubscriptionCreateNet_terms_type
subscriptionCreateNet_terms_type = Maybe SubscriptionCreateNet_terms_type
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateNext_bill_date :: Maybe JsonDateTime
subscriptionCreateNext_bill_date = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreatePlan_code :: Text
subscriptionCreatePlan_code = Text
subscriptionCreatePlan_code
, subscriptionCreatePlan_id :: Maybe Text
subscriptionCreatePlan_id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreatePo_number :: Maybe Text
subscriptionCreatePo_number = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateQuantity :: Maybe Int
subscriptionCreateQuantity = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateRamp_intervals :: Maybe [SubscriptionRampInterval]
subscriptionCreateRamp_intervals = Maybe [SubscriptionRampInterval]
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateRenewal_billing_cycles :: Maybe Int
subscriptionCreateRenewal_billing_cycles = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateRevenue_schedule_type :: Maybe SubscriptionCreateRevenue_schedule_type
subscriptionCreateRevenue_schedule_type = Maybe SubscriptionCreateRevenue_schedule_type
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateShipping :: Maybe SubscriptionShippingCreate
subscriptionCreateShipping = Maybe SubscriptionShippingCreate
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateStarts_at :: Maybe JsonDateTime
subscriptionCreateStarts_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateTax_inclusive :: Maybe Bool
subscriptionCreateTax_inclusive = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateTerms_and_conditions :: Maybe Text
subscriptionCreateTerms_and_conditions = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateTotal_billing_cycles :: Maybe Int
subscriptionCreateTotal_billing_cycles = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateTransaction_type :: Maybe SubscriptionCreateTransaction_type
subscriptionCreateTransaction_type = Maybe SubscriptionCreateTransaction_type
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateTrial_ends_at :: Maybe JsonDateTime
subscriptionCreateTrial_ends_at = Maybe JsonDateTime
forall a. Maybe a
GHC.Maybe.Nothing
, subscriptionCreateUnit_amount :: Maybe Float
subscriptionCreateUnit_amount = Maybe Float
forall a. Maybe a
GHC.Maybe.Nothing
}
data SubscriptionCreateCollection_method
=
SubscriptionCreateCollection_methodOther Data.Aeson.Types.Internal.Value
|
SubscriptionCreateCollection_methodTyped Data.Text.Internal.Text
|
SubscriptionCreateCollection_methodEnumAutomatic
|
SubscriptionCreateCollection_methodEnumManual
deriving (Int -> SubscriptionCreateCollection_method -> ShowS
[SubscriptionCreateCollection_method] -> ShowS
SubscriptionCreateCollection_method -> String
(Int -> SubscriptionCreateCollection_method -> ShowS)
-> (SubscriptionCreateCollection_method -> String)
-> ([SubscriptionCreateCollection_method] -> ShowS)
-> Show SubscriptionCreateCollection_method
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionCreateCollection_method -> ShowS
showsPrec :: Int -> SubscriptionCreateCollection_method -> ShowS
$cshow :: SubscriptionCreateCollection_method -> String
show :: SubscriptionCreateCollection_method -> String
$cshowList :: [SubscriptionCreateCollection_method] -> ShowS
showList :: [SubscriptionCreateCollection_method] -> ShowS
GHC.Show.Show, SubscriptionCreateCollection_method
-> SubscriptionCreateCollection_method -> Bool
(SubscriptionCreateCollection_method
-> SubscriptionCreateCollection_method -> Bool)
-> (SubscriptionCreateCollection_method
-> SubscriptionCreateCollection_method -> Bool)
-> Eq SubscriptionCreateCollection_method
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptionCreateCollection_method
-> SubscriptionCreateCollection_method -> Bool
== :: SubscriptionCreateCollection_method
-> SubscriptionCreateCollection_method -> Bool
$c/= :: SubscriptionCreateCollection_method
-> SubscriptionCreateCollection_method -> Bool
/= :: SubscriptionCreateCollection_method
-> SubscriptionCreateCollection_method -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionCreateCollection_method where
toJSON :: SubscriptionCreateCollection_method -> Value
toJSON (SubscriptionCreateCollection_methodOther Value
val) = Value
val
toJSON (SubscriptionCreateCollection_methodTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (SubscriptionCreateCollection_method
SubscriptionCreateCollection_methodEnumAutomatic) = Value
"automatic"
toJSON (SubscriptionCreateCollection_method
SubscriptionCreateCollection_methodEnumManual) = Value
"manual"
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionCreateCollection_method where
parseJSON :: Value -> Parser SubscriptionCreateCollection_method
parseJSON Value
val =
SubscriptionCreateCollection_method
-> Parser SubscriptionCreateCollection_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" -> SubscriptionCreateCollection_method
SubscriptionCreateCollection_methodEnumAutomatic
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"manual" -> SubscriptionCreateCollection_method
SubscriptionCreateCollection_methodEnumManual
| Bool
GHC.Base.otherwise -> Value -> SubscriptionCreateCollection_method
SubscriptionCreateCollection_methodOther Value
val
)
data SubscriptionCreateNet_terms_type
=
SubscriptionCreateNet_terms_typeOther Data.Aeson.Types.Internal.Value
|
SubscriptionCreateNet_terms_typeTyped Data.Text.Internal.Text
|
SubscriptionCreateNet_terms_typeEnumNet
|
SubscriptionCreateNet_terms_typeEnumEom
deriving (Int -> SubscriptionCreateNet_terms_type -> ShowS
[SubscriptionCreateNet_terms_type] -> ShowS
SubscriptionCreateNet_terms_type -> String
(Int -> SubscriptionCreateNet_terms_type -> ShowS)
-> (SubscriptionCreateNet_terms_type -> String)
-> ([SubscriptionCreateNet_terms_type] -> ShowS)
-> Show SubscriptionCreateNet_terms_type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionCreateNet_terms_type -> ShowS
showsPrec :: Int -> SubscriptionCreateNet_terms_type -> ShowS
$cshow :: SubscriptionCreateNet_terms_type -> String
show :: SubscriptionCreateNet_terms_type -> String
$cshowList :: [SubscriptionCreateNet_terms_type] -> ShowS
showList :: [SubscriptionCreateNet_terms_type] -> ShowS
GHC.Show.Show, SubscriptionCreateNet_terms_type
-> SubscriptionCreateNet_terms_type -> Bool
(SubscriptionCreateNet_terms_type
-> SubscriptionCreateNet_terms_type -> Bool)
-> (SubscriptionCreateNet_terms_type
-> SubscriptionCreateNet_terms_type -> Bool)
-> Eq SubscriptionCreateNet_terms_type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptionCreateNet_terms_type
-> SubscriptionCreateNet_terms_type -> Bool
== :: SubscriptionCreateNet_terms_type
-> SubscriptionCreateNet_terms_type -> Bool
$c/= :: SubscriptionCreateNet_terms_type
-> SubscriptionCreateNet_terms_type -> Bool
/= :: SubscriptionCreateNet_terms_type
-> SubscriptionCreateNet_terms_type -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionCreateNet_terms_type where
toJSON :: SubscriptionCreateNet_terms_type -> Value
toJSON (SubscriptionCreateNet_terms_typeOther Value
val) = Value
val
toJSON (SubscriptionCreateNet_terms_typeTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (SubscriptionCreateNet_terms_type
SubscriptionCreateNet_terms_typeEnumNet) = Value
"net"
toJSON (SubscriptionCreateNet_terms_type
SubscriptionCreateNet_terms_typeEnumEom) = Value
"eom"
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionCreateNet_terms_type where
parseJSON :: Value -> Parser SubscriptionCreateNet_terms_type
parseJSON Value
val =
SubscriptionCreateNet_terms_type
-> Parser SubscriptionCreateNet_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" -> SubscriptionCreateNet_terms_type
SubscriptionCreateNet_terms_typeEnumNet
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"eom" -> SubscriptionCreateNet_terms_type
SubscriptionCreateNet_terms_typeEnumEom
| Bool
GHC.Base.otherwise -> Value -> SubscriptionCreateNet_terms_type
SubscriptionCreateNet_terms_typeOther Value
val
)
data SubscriptionCreateRevenue_schedule_type
=
SubscriptionCreateRevenue_schedule_typeOther Data.Aeson.Types.Internal.Value
|
SubscriptionCreateRevenue_schedule_typeTyped Data.Text.Internal.Text
|
SubscriptionCreateRevenue_schedule_typeEnumAt_range_end
|
SubscriptionCreateRevenue_schedule_typeEnumAt_range_start
|
SubscriptionCreateRevenue_schedule_typeEnumEvenly
|
SubscriptionCreateRevenue_schedule_typeEnumNever
deriving (Int -> SubscriptionCreateRevenue_schedule_type -> ShowS
[SubscriptionCreateRevenue_schedule_type] -> ShowS
SubscriptionCreateRevenue_schedule_type -> String
(Int -> SubscriptionCreateRevenue_schedule_type -> ShowS)
-> (SubscriptionCreateRevenue_schedule_type -> String)
-> ([SubscriptionCreateRevenue_schedule_type] -> ShowS)
-> Show SubscriptionCreateRevenue_schedule_type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionCreateRevenue_schedule_type -> ShowS
showsPrec :: Int -> SubscriptionCreateRevenue_schedule_type -> ShowS
$cshow :: SubscriptionCreateRevenue_schedule_type -> String
show :: SubscriptionCreateRevenue_schedule_type -> String
$cshowList :: [SubscriptionCreateRevenue_schedule_type] -> ShowS
showList :: [SubscriptionCreateRevenue_schedule_type] -> ShowS
GHC.Show.Show, SubscriptionCreateRevenue_schedule_type
-> SubscriptionCreateRevenue_schedule_type -> Bool
(SubscriptionCreateRevenue_schedule_type
-> SubscriptionCreateRevenue_schedule_type -> Bool)
-> (SubscriptionCreateRevenue_schedule_type
-> SubscriptionCreateRevenue_schedule_type -> Bool)
-> Eq SubscriptionCreateRevenue_schedule_type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptionCreateRevenue_schedule_type
-> SubscriptionCreateRevenue_schedule_type -> Bool
== :: SubscriptionCreateRevenue_schedule_type
-> SubscriptionCreateRevenue_schedule_type -> Bool
$c/= :: SubscriptionCreateRevenue_schedule_type
-> SubscriptionCreateRevenue_schedule_type -> Bool
/= :: SubscriptionCreateRevenue_schedule_type
-> SubscriptionCreateRevenue_schedule_type -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionCreateRevenue_schedule_type where
toJSON :: SubscriptionCreateRevenue_schedule_type -> Value
toJSON (SubscriptionCreateRevenue_schedule_typeOther Value
val) = Value
val
toJSON (SubscriptionCreateRevenue_schedule_typeTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (SubscriptionCreateRevenue_schedule_type
SubscriptionCreateRevenue_schedule_typeEnumAt_range_end) = Value
"at_range_end"
toJSON (SubscriptionCreateRevenue_schedule_type
SubscriptionCreateRevenue_schedule_typeEnumAt_range_start) = Value
"at_range_start"
toJSON (SubscriptionCreateRevenue_schedule_type
SubscriptionCreateRevenue_schedule_typeEnumEvenly) = Value
"evenly"
toJSON (SubscriptionCreateRevenue_schedule_type
SubscriptionCreateRevenue_schedule_typeEnumNever) = Value
"never"
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionCreateRevenue_schedule_type where
parseJSON :: Value -> Parser SubscriptionCreateRevenue_schedule_type
parseJSON Value
val =
SubscriptionCreateRevenue_schedule_type
-> Parser SubscriptionCreateRevenue_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" -> SubscriptionCreateRevenue_schedule_type
SubscriptionCreateRevenue_schedule_typeEnumAt_range_end
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"at_range_start" -> SubscriptionCreateRevenue_schedule_type
SubscriptionCreateRevenue_schedule_typeEnumAt_range_start
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"evenly" -> SubscriptionCreateRevenue_schedule_type
SubscriptionCreateRevenue_schedule_typeEnumEvenly
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"never" -> SubscriptionCreateRevenue_schedule_type
SubscriptionCreateRevenue_schedule_typeEnumNever
| Bool
GHC.Base.otherwise -> Value -> SubscriptionCreateRevenue_schedule_type
SubscriptionCreateRevenue_schedule_typeOther Value
val
)
data SubscriptionCreateTransaction_type
=
SubscriptionCreateTransaction_typeOther Data.Aeson.Types.Internal.Value
|
SubscriptionCreateTransaction_typeTyped Data.Text.Internal.Text
|
SubscriptionCreateTransaction_typeEnumMoto
deriving (Int -> SubscriptionCreateTransaction_type -> ShowS
[SubscriptionCreateTransaction_type] -> ShowS
SubscriptionCreateTransaction_type -> String
(Int -> SubscriptionCreateTransaction_type -> ShowS)
-> (SubscriptionCreateTransaction_type -> String)
-> ([SubscriptionCreateTransaction_type] -> ShowS)
-> Show SubscriptionCreateTransaction_type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscriptionCreateTransaction_type -> ShowS
showsPrec :: Int -> SubscriptionCreateTransaction_type -> ShowS
$cshow :: SubscriptionCreateTransaction_type -> String
show :: SubscriptionCreateTransaction_type -> String
$cshowList :: [SubscriptionCreateTransaction_type] -> ShowS
showList :: [SubscriptionCreateTransaction_type] -> ShowS
GHC.Show.Show, SubscriptionCreateTransaction_type
-> SubscriptionCreateTransaction_type -> Bool
(SubscriptionCreateTransaction_type
-> SubscriptionCreateTransaction_type -> Bool)
-> (SubscriptionCreateTransaction_type
-> SubscriptionCreateTransaction_type -> Bool)
-> Eq SubscriptionCreateTransaction_type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscriptionCreateTransaction_type
-> SubscriptionCreateTransaction_type -> Bool
== :: SubscriptionCreateTransaction_type
-> SubscriptionCreateTransaction_type -> Bool
$c/= :: SubscriptionCreateTransaction_type
-> SubscriptionCreateTransaction_type -> Bool
/= :: SubscriptionCreateTransaction_type
-> SubscriptionCreateTransaction_type -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON SubscriptionCreateTransaction_type where
toJSON :: SubscriptionCreateTransaction_type -> Value
toJSON (SubscriptionCreateTransaction_typeOther Value
val) = Value
val
toJSON (SubscriptionCreateTransaction_typeTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (SubscriptionCreateTransaction_type
SubscriptionCreateTransaction_typeEnumMoto) = Value
"moto"
instance Data.Aeson.Types.FromJSON.FromJSON SubscriptionCreateTransaction_type where
parseJSON :: Value -> Parser SubscriptionCreateTransaction_type
parseJSON Value
val =
SubscriptionCreateTransaction_type
-> Parser SubscriptionCreateTransaction_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
"moto" -> SubscriptionCreateTransaction_type
SubscriptionCreateTransaction_typeEnumMoto
| Bool
GHC.Base.otherwise -> Value -> SubscriptionCreateTransaction_type
SubscriptionCreateTransaction_typeOther Value
val
)