{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module RecurlyClient.Types.CouponCreate 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.CouponPricing
import {-# SOURCE #-} RecurlyClient.Types.CouponUpdate
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe
data CouponCreate = CouponCreate
{ CouponCreate -> Maybe Bool
couponCreateApplies_to_all_items :: (GHC.Maybe.Maybe GHC.Types.Bool)
, CouponCreate -> Maybe Bool
couponCreateApplies_to_all_plans :: (GHC.Maybe.Maybe GHC.Types.Bool)
, CouponCreate -> Maybe Bool
couponCreateApplies_to_non_plan_charges :: (GHC.Maybe.Maybe GHC.Types.Bool)
, CouponCreate -> Text
couponCreateCode :: Data.Text.Internal.Text
, CouponCreate -> Maybe CouponCreateCoupon_type
couponCreateCoupon_type :: (GHC.Maybe.Maybe CouponCreateCoupon_type)
, CouponCreate -> Maybe [CouponPricing]
couponCreateCurrencies :: (GHC.Maybe.Maybe [CouponPricing])
, CouponCreate -> Maybe Int
couponCreateDiscount_percent :: (GHC.Maybe.Maybe GHC.Types.Int)
, CouponCreate -> CouponCreateDiscount_type
couponCreateDiscount_type :: CouponCreateDiscount_type
, CouponCreate -> Maybe CouponCreateDuration
couponCreateDuration :: (GHC.Maybe.Maybe CouponCreateDuration)
, CouponCreate -> Maybe Int
couponCreateFree_trial_amount :: (GHC.Maybe.Maybe GHC.Types.Int)
, CouponCreate -> Maybe CouponCreateFree_trial_unit
couponCreateFree_trial_unit :: (GHC.Maybe.Maybe CouponCreateFree_trial_unit)
, CouponCreate -> Maybe Text
couponCreateHosted_description :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, CouponCreate -> Maybe Text
couponCreateInvoice_description :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, CouponCreate -> Maybe [Text]
couponCreateItem_codes :: (GHC.Maybe.Maybe [Data.Text.Internal.Text])
, CouponCreate -> Maybe Int
couponCreateMax_redemptions :: (GHC.Maybe.Maybe GHC.Types.Int)
, CouponCreate -> Maybe Int
couponCreateMax_redemptions_per_account :: (GHC.Maybe.Maybe GHC.Types.Int)
, CouponCreate -> Text
couponCreateName :: Data.Text.Internal.Text
, CouponCreate -> Maybe [Text]
couponCreatePlan_codes :: (GHC.Maybe.Maybe [Data.Text.Internal.Text])
, CouponCreate -> Maybe Text
couponCreateRedeem_by_date :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
, CouponCreate -> Maybe CouponCreateRedemption_resource
couponCreateRedemption_resource :: (GHC.Maybe.Maybe CouponCreateRedemption_resource)
, CouponCreate -> Maybe Int
couponCreateTemporal_amount :: (GHC.Maybe.Maybe GHC.Types.Int)
, CouponCreate -> Maybe CouponCreateTemporal_unit
couponCreateTemporal_unit :: (GHC.Maybe.Maybe CouponCreateTemporal_unit)
, CouponCreate -> Maybe Text
couponCreateUnique_code_template :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
}
deriving
( Int -> CouponCreate -> ShowS
[CouponCreate] -> ShowS
CouponCreate -> String
(Int -> CouponCreate -> ShowS)
-> (CouponCreate -> String)
-> ([CouponCreate] -> ShowS)
-> Show CouponCreate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CouponCreate -> ShowS
showsPrec :: Int -> CouponCreate -> ShowS
$cshow :: CouponCreate -> String
show :: CouponCreate -> String
$cshowList :: [CouponCreate] -> ShowS
showList :: [CouponCreate] -> ShowS
GHC.Show.Show
, CouponCreate -> CouponCreate -> Bool
(CouponCreate -> CouponCreate -> Bool)
-> (CouponCreate -> CouponCreate -> Bool) -> Eq CouponCreate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CouponCreate -> CouponCreate -> Bool
== :: CouponCreate -> CouponCreate -> Bool
$c/= :: CouponCreate -> CouponCreate -> Bool
/= :: CouponCreate -> CouponCreate -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON CouponCreate where
toJSON :: CouponCreate -> Value
toJSON CouponCreate
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object ([[Pair]] -> [Pair]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([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
"applies_to_all_items" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Bool
couponCreateApplies_to_all_items CouponCreate
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
"applies_to_all_plans" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Bool
couponCreateApplies_to_all_plans CouponCreate
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
"applies_to_non_plan_charges" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Bool
couponCreateApplies_to_non_plan_charges CouponCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Key
"code" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..= CouponCreate -> Text
couponCreateCode CouponCreate
obj] [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (CouponCreateCoupon_type -> [Pair])
-> Maybe CouponCreateCoupon_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])
-> (CouponCreateCoupon_type -> Pair)
-> CouponCreateCoupon_type
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"coupon_type" Key -> CouponCreateCoupon_type -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe CouponCreateCoupon_type
couponCreateCoupon_type CouponCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> ([CouponPricing] -> [Pair]) -> Maybe [CouponPricing] -> [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])
-> ([CouponPricing] -> Pair) -> [CouponPricing] -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"currencies" Key -> [CouponPricing] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe [CouponPricing]
couponCreateCurrencies CouponCreate
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
"discount_percent" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Int
couponCreateDiscount_percent CouponCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Key
"discount_type" Key -> CouponCreateDiscount_type -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..= CouponCreate -> CouponCreateDiscount_type
couponCreateDiscount_type CouponCreate
obj] [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (CouponCreateDuration -> [Pair])
-> Maybe CouponCreateDuration
-> [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])
-> (CouponCreateDuration -> Pair) -> CouponCreateDuration -> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"duration" Key -> CouponCreateDuration -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe CouponCreateDuration
couponCreateDuration CouponCreate
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
"free_trial_amount" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Int
couponCreateFree_trial_amount CouponCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (CouponCreateFree_trial_unit -> [Pair])
-> Maybe CouponCreateFree_trial_unit
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (CouponCreateFree_trial_unit -> Pair)
-> CouponCreateFree_trial_unit
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"free_trial_unit" Key -> CouponCreateFree_trial_unit -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe CouponCreateFree_trial_unit
couponCreateFree_trial_unit CouponCreate
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
"hosted_description" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Text
couponCreateHosted_description CouponCreate
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
"invoice_description" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Text
couponCreateInvoice_description CouponCreate
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
"item_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..=)) (CouponCreate -> Maybe [Text]
couponCreateItem_codes CouponCreate
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
"max_redemptions" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Int
couponCreateMax_redemptions CouponCreate
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
"max_redemptions_per_account" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Int
couponCreateMax_redemptions_per_account CouponCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Key
"name" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..= CouponCreate -> Text
couponCreateName CouponCreate
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_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..=)) (CouponCreate -> Maybe [Text]
couponCreatePlan_codes CouponCreate
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
"redeem_by_date" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Text
couponCreateRedeem_by_date CouponCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (CouponCreateRedemption_resource -> [Pair])
-> Maybe CouponCreateRedemption_resource
-> [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])
-> (CouponCreateRedemption_resource -> Pair)
-> CouponCreateRedemption_resource
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"redemption_resource" Key -> CouponCreateRedemption_resource -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe CouponCreateRedemption_resource
couponCreateRedemption_resource CouponCreate
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
"temporal_amount" Key -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Int
couponCreateTemporal_amount CouponCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [Pair]
-> (CouponCreateTemporal_unit -> [Pair])
-> Maybe CouponCreateTemporal_unit
-> [Pair]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Pair]
forall a. Monoid a => a
GHC.Base.mempty (Pair -> [Pair]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Pair -> [Pair])
-> (CouponCreateTemporal_unit -> Pair)
-> CouponCreateTemporal_unit
-> [Pair]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"temporal_unit" Key -> CouponCreateTemporal_unit -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe CouponCreateTemporal_unit
couponCreateTemporal_unit CouponCreate
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
"unique_code_template" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Text
couponCreateUnique_code_template CouponCreate
obj) [Pair] -> [[Pair]] -> [[Pair]]
forall a. a -> [a] -> [a]
: [[Pair]]
forall a. Monoid a => a
GHC.Base.mempty))
toEncoding :: CouponCreate -> Encoding
toEncoding CouponCreate
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ([Series] -> Series
forall a. Monoid a => [a] -> a
GHC.Base.mconcat ([[Series]] -> [Series]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
Data.Foldable.concat ([Series] -> (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
"applies_to_all_items" Key -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Bool
couponCreateApplies_to_all_items CouponCreate
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
"applies_to_all_plans" Key -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Bool
couponCreateApplies_to_all_plans CouponCreate
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
"applies_to_non_plan_charges" Key -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Bool
couponCreateApplies_to_non_plan_charges CouponCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Key
"code" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..= CouponCreate -> Text
couponCreateCode CouponCreate
obj] [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (CouponCreateCoupon_type -> [Series])
-> Maybe CouponCreateCoupon_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])
-> (CouponCreateCoupon_type -> Series)
-> CouponCreateCoupon_type
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"coupon_type" Key -> CouponCreateCoupon_type -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe CouponCreateCoupon_type
couponCreateCoupon_type CouponCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> ([CouponPricing] -> [Series])
-> Maybe [CouponPricing]
-> [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])
-> ([CouponPricing] -> Series) -> [CouponPricing] -> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"currencies" Key -> [CouponPricing] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe [CouponPricing]
couponCreateCurrencies CouponCreate
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
"discount_percent" Key -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Int
couponCreateDiscount_percent CouponCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Key
"discount_type" Key -> CouponCreateDiscount_type -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..= CouponCreate -> CouponCreateDiscount_type
couponCreateDiscount_type CouponCreate
obj] [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (CouponCreateDuration -> [Series])
-> Maybe CouponCreateDuration
-> [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])
-> (CouponCreateDuration -> Series)
-> CouponCreateDuration
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"duration" Key -> CouponCreateDuration -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe CouponCreateDuration
couponCreateDuration CouponCreate
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
"free_trial_amount" Key -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Int
couponCreateFree_trial_amount CouponCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (CouponCreateFree_trial_unit -> [Series])
-> Maybe CouponCreateFree_trial_unit
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (CouponCreateFree_trial_unit -> Series)
-> CouponCreateFree_trial_unit
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"free_trial_unit" Key -> CouponCreateFree_trial_unit -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe CouponCreateFree_trial_unit
couponCreateFree_trial_unit CouponCreate
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
"hosted_description" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Text
couponCreateHosted_description CouponCreate
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
"invoice_description" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Text
couponCreateInvoice_description CouponCreate
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
"item_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..=)) (CouponCreate -> Maybe [Text]
couponCreateItem_codes CouponCreate
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
"max_redemptions" Key -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Int
couponCreateMax_redemptions CouponCreate
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
"max_redemptions_per_account" Key -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Int
couponCreateMax_redemptions_per_account CouponCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Key
"name" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..= CouponCreate -> Text
couponCreateName CouponCreate
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_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..=)) (CouponCreate -> Maybe [Text]
couponCreatePlan_codes CouponCreate
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
"redeem_by_date" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Text
couponCreateRedeem_by_date CouponCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (CouponCreateRedemption_resource -> [Series])
-> Maybe CouponCreateRedemption_resource
-> [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])
-> (CouponCreateRedemption_resource -> Series)
-> CouponCreateRedemption_resource
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"redemption_resource" Key -> CouponCreateRedemption_resource -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe CouponCreateRedemption_resource
couponCreateRedemption_resource CouponCreate
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
"temporal_amount" Key -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Int
couponCreateTemporal_amount CouponCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [Series]
-> (CouponCreateTemporal_unit -> [Series])
-> Maybe CouponCreateTemporal_unit
-> [Series]
forall b a. b -> (a -> b) -> Maybe a -> b
Data.Maybe.maybe [Series]
forall a. Monoid a => a
GHC.Base.mempty (Series -> [Series]
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure (Series -> [Series])
-> (CouponCreateTemporal_unit -> Series)
-> CouponCreateTemporal_unit
-> [Series]
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. (Key
"temporal_unit" Key -> CouponCreateTemporal_unit -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe CouponCreateTemporal_unit
couponCreateTemporal_unit CouponCreate
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
"unique_code_template" Key -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Series
Data.Aeson.Types.ToJSON..=)) (CouponCreate -> Maybe Text
couponCreateUnique_code_template CouponCreate
obj) [Series] -> [[Series]] -> [[Series]]
forall a. a -> [a] -> [a]
: [[Series]]
forall a. Monoid a => a
GHC.Base.mempty)))
instance Data.Aeson.Types.FromJSON.FromJSON CouponCreate where
parseJSON :: Value -> Parser CouponCreate
parseJSON = String
-> (Object -> Parser CouponCreate) -> Value -> Parser CouponCreate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"CouponCreate" (\Object
obj -> (((((((((((((((((((((((Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Text
-> Maybe CouponCreateCoupon_type
-> Maybe [CouponPricing]
-> Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Text
-> Maybe CouponCreateCoupon_type
-> Maybe [CouponPricing]
-> Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Text
-> Maybe CouponCreateCoupon_type
-> Maybe [CouponPricing]
-> Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate
CouponCreate Parser
(Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Text
-> Maybe CouponCreateCoupon_type
-> Maybe [CouponPricing]
-> Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe Bool)
-> Parser
(Maybe Bool
-> Maybe Bool
-> Text
-> Maybe CouponCreateCoupon_type
-> Maybe [CouponPricing]
-> Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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
"applies_to_all_items")) Parser
(Maybe Bool
-> Maybe Bool
-> Text
-> Maybe CouponCreateCoupon_type
-> Maybe [CouponPricing]
-> Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe Bool)
-> Parser
(Maybe Bool
-> Text
-> Maybe CouponCreateCoupon_type
-> Maybe [CouponPricing]
-> Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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
"applies_to_all_plans")) Parser
(Maybe Bool
-> Text
-> Maybe CouponCreateCoupon_type
-> Maybe [CouponPricing]
-> Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe Bool)
-> Parser
(Text
-> Maybe CouponCreateCoupon_type
-> Maybe [CouponPricing]
-> Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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
"applies_to_non_plan_charges")) Parser
(Text
-> Maybe CouponCreateCoupon_type
-> Maybe [CouponPricing]
-> Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser Text
-> Parser
(Maybe CouponCreateCoupon_type
-> Maybe [CouponPricing]
-> Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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
"code")) Parser
(Maybe CouponCreateCoupon_type
-> Maybe [CouponPricing]
-> Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe CouponCreateCoupon_type)
-> Parser
(Maybe [CouponPricing]
-> Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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 CouponCreateCoupon_type)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"coupon_type")) Parser
(Maybe [CouponPricing]
-> Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe [CouponPricing])
-> Parser
(Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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 [CouponPricing])
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"currencies")) Parser
(Maybe Int
-> CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe Int)
-> Parser
(CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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
"discount_percent")) Parser
(CouponCreateDiscount_type
-> Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser CouponCreateDiscount_type
-> Parser
(Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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 CouponCreateDiscount_type
forall a. FromJSON a => Object -> Key -> Parser a
Data.Aeson.Types.FromJSON..: Key
"discount_type")) Parser
(Maybe CouponCreateDuration
-> Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe CouponCreateDuration)
-> Parser
(Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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 CouponCreateDuration)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"duration")) Parser
(Maybe Int
-> Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe Int)
-> Parser
(Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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
"free_trial_amount")) Parser
(Maybe CouponCreateFree_trial_unit
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe CouponCreateFree_trial_unit)
-> Parser
(Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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 CouponCreateFree_trial_unit)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"free_trial_unit")) Parser
(Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe Text)
-> Parser
(Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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
"hosted_description")) Parser
(Maybe Text
-> Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe Text)
-> Parser
(Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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
"invoice_description")) Parser
(Maybe [Text]
-> Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe [Text])
-> Parser
(Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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
"item_codes")) Parser
(Maybe Int
-> Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe Int)
-> Parser
(Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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
"max_redemptions")) Parser
(Maybe Int
-> Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe Int)
-> Parser
(Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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
"max_redemptions_per_account")) Parser
(Text
-> Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser Text
-> Parser
(Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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
"name")) Parser
(Maybe [Text]
-> Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe [Text])
-> Parser
(Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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_codes")) Parser
(Maybe Text
-> Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe Text)
-> Parser
(Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
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
"redeem_by_date")) Parser
(Maybe CouponCreateRedemption_resource
-> Maybe Int
-> Maybe CouponCreateTemporal_unit
-> Maybe Text
-> CouponCreate)
-> Parser (Maybe CouponCreateRedemption_resource)
-> Parser
(Maybe Int
-> Maybe CouponCreateTemporal_unit -> Maybe Text -> CouponCreate)
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 CouponCreateRedemption_resource)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"redemption_resource")) Parser
(Maybe Int
-> Maybe CouponCreateTemporal_unit -> Maybe Text -> CouponCreate)
-> Parser (Maybe Int)
-> Parser
(Maybe CouponCreateTemporal_unit -> Maybe Text -> CouponCreate)
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
"temporal_amount")) Parser
(Maybe CouponCreateTemporal_unit -> Maybe Text -> CouponCreate)
-> Parser (Maybe CouponCreateTemporal_unit)
-> Parser (Maybe Text -> CouponCreate)
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 CouponCreateTemporal_unit)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Key
"temporal_unit")) Parser (Maybe Text -> CouponCreate)
-> Parser (Maybe Text) -> Parser CouponCreate
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
"unique_code_template"))
mkCouponCreate ::
Data.Text.Internal.Text ->
CouponCreateDiscount_type ->
Data.Text.Internal.Text ->
CouponCreate
mkCouponCreate :: Text -> CouponCreateDiscount_type -> Text -> CouponCreate
mkCouponCreate Text
couponCreateCode CouponCreateDiscount_type
couponCreateDiscount_type Text
couponCreateName =
CouponCreate
{ couponCreateApplies_to_all_items :: Maybe Bool
couponCreateApplies_to_all_items = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateApplies_to_all_plans :: Maybe Bool
couponCreateApplies_to_all_plans = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateApplies_to_non_plan_charges :: Maybe Bool
couponCreateApplies_to_non_plan_charges = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateCode :: Text
couponCreateCode = Text
couponCreateCode
, couponCreateCoupon_type :: Maybe CouponCreateCoupon_type
couponCreateCoupon_type = Maybe CouponCreateCoupon_type
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateCurrencies :: Maybe [CouponPricing]
couponCreateCurrencies = Maybe [CouponPricing]
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateDiscount_percent :: Maybe Int
couponCreateDiscount_percent = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateDiscount_type :: CouponCreateDiscount_type
couponCreateDiscount_type = CouponCreateDiscount_type
couponCreateDiscount_type
, couponCreateDuration :: Maybe CouponCreateDuration
couponCreateDuration = Maybe CouponCreateDuration
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateFree_trial_amount :: Maybe Int
couponCreateFree_trial_amount = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateFree_trial_unit :: Maybe CouponCreateFree_trial_unit
couponCreateFree_trial_unit = Maybe CouponCreateFree_trial_unit
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateHosted_description :: Maybe Text
couponCreateHosted_description = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateInvoice_description :: Maybe Text
couponCreateInvoice_description = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateItem_codes :: Maybe [Text]
couponCreateItem_codes = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateMax_redemptions :: Maybe Int
couponCreateMax_redemptions = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateMax_redemptions_per_account :: Maybe Int
couponCreateMax_redemptions_per_account = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateName :: Text
couponCreateName = Text
couponCreateName
, couponCreatePlan_codes :: Maybe [Text]
couponCreatePlan_codes = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateRedeem_by_date :: Maybe Text
couponCreateRedeem_by_date = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateRedemption_resource :: Maybe CouponCreateRedemption_resource
couponCreateRedemption_resource = Maybe CouponCreateRedemption_resource
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateTemporal_amount :: Maybe Int
couponCreateTemporal_amount = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateTemporal_unit :: Maybe CouponCreateTemporal_unit
couponCreateTemporal_unit = Maybe CouponCreateTemporal_unit
forall a. Maybe a
GHC.Maybe.Nothing
, couponCreateUnique_code_template :: Maybe Text
couponCreateUnique_code_template = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
}
data CouponCreateCoupon_type
=
CouponCreateCoupon_typeOther Data.Aeson.Types.Internal.Value
|
CouponCreateCoupon_typeTyped Data.Text.Internal.Text
|
CouponCreateCoupon_typeEnumBulk
|
CouponCreateCoupon_typeEnumSingle_code
deriving (Int -> CouponCreateCoupon_type -> ShowS
[CouponCreateCoupon_type] -> ShowS
CouponCreateCoupon_type -> String
(Int -> CouponCreateCoupon_type -> ShowS)
-> (CouponCreateCoupon_type -> String)
-> ([CouponCreateCoupon_type] -> ShowS)
-> Show CouponCreateCoupon_type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CouponCreateCoupon_type -> ShowS
showsPrec :: Int -> CouponCreateCoupon_type -> ShowS
$cshow :: CouponCreateCoupon_type -> String
show :: CouponCreateCoupon_type -> String
$cshowList :: [CouponCreateCoupon_type] -> ShowS
showList :: [CouponCreateCoupon_type] -> ShowS
GHC.Show.Show, CouponCreateCoupon_type -> CouponCreateCoupon_type -> Bool
(CouponCreateCoupon_type -> CouponCreateCoupon_type -> Bool)
-> (CouponCreateCoupon_type -> CouponCreateCoupon_type -> Bool)
-> Eq CouponCreateCoupon_type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CouponCreateCoupon_type -> CouponCreateCoupon_type -> Bool
== :: CouponCreateCoupon_type -> CouponCreateCoupon_type -> Bool
$c/= :: CouponCreateCoupon_type -> CouponCreateCoupon_type -> Bool
/= :: CouponCreateCoupon_type -> CouponCreateCoupon_type -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON CouponCreateCoupon_type where
toJSON :: CouponCreateCoupon_type -> Value
toJSON (CouponCreateCoupon_typeOther Value
val) = Value
val
toJSON (CouponCreateCoupon_typeTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (CouponCreateCoupon_type
CouponCreateCoupon_typeEnumBulk) = Value
"bulk"
toJSON (CouponCreateCoupon_type
CouponCreateCoupon_typeEnumSingle_code) = Value
"single_code"
instance Data.Aeson.Types.FromJSON.FromJSON CouponCreateCoupon_type where
parseJSON :: Value -> Parser CouponCreateCoupon_type
parseJSON Value
val =
CouponCreateCoupon_type -> Parser CouponCreateCoupon_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
"bulk" -> CouponCreateCoupon_type
CouponCreateCoupon_typeEnumBulk
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"single_code" -> CouponCreateCoupon_type
CouponCreateCoupon_typeEnumSingle_code
| Bool
GHC.Base.otherwise -> Value -> CouponCreateCoupon_type
CouponCreateCoupon_typeOther Value
val
)
data CouponCreateDiscount_type
=
CouponCreateDiscount_typeOther Data.Aeson.Types.Internal.Value
|
CouponCreateDiscount_typeTyped Data.Text.Internal.Text
|
CouponCreateDiscount_typeEnumFixed
|
CouponCreateDiscount_typeEnumFree_trial
|
CouponCreateDiscount_typeEnumPercent
deriving (Int -> CouponCreateDiscount_type -> ShowS
[CouponCreateDiscount_type] -> ShowS
CouponCreateDiscount_type -> String
(Int -> CouponCreateDiscount_type -> ShowS)
-> (CouponCreateDiscount_type -> String)
-> ([CouponCreateDiscount_type] -> ShowS)
-> Show CouponCreateDiscount_type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CouponCreateDiscount_type -> ShowS
showsPrec :: Int -> CouponCreateDiscount_type -> ShowS
$cshow :: CouponCreateDiscount_type -> String
show :: CouponCreateDiscount_type -> String
$cshowList :: [CouponCreateDiscount_type] -> ShowS
showList :: [CouponCreateDiscount_type] -> ShowS
GHC.Show.Show, CouponCreateDiscount_type -> CouponCreateDiscount_type -> Bool
(CouponCreateDiscount_type -> CouponCreateDiscount_type -> Bool)
-> (CouponCreateDiscount_type -> CouponCreateDiscount_type -> Bool)
-> Eq CouponCreateDiscount_type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CouponCreateDiscount_type -> CouponCreateDiscount_type -> Bool
== :: CouponCreateDiscount_type -> CouponCreateDiscount_type -> Bool
$c/= :: CouponCreateDiscount_type -> CouponCreateDiscount_type -> Bool
/= :: CouponCreateDiscount_type -> CouponCreateDiscount_type -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON CouponCreateDiscount_type where
toJSON :: CouponCreateDiscount_type -> Value
toJSON (CouponCreateDiscount_typeOther Value
val) = Value
val
toJSON (CouponCreateDiscount_typeTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (CouponCreateDiscount_type
CouponCreateDiscount_typeEnumFixed) = Value
"fixed"
toJSON (CouponCreateDiscount_type
CouponCreateDiscount_typeEnumFree_trial) = Value
"free_trial"
toJSON (CouponCreateDiscount_type
CouponCreateDiscount_typeEnumPercent) = Value
"percent"
instance Data.Aeson.Types.FromJSON.FromJSON CouponCreateDiscount_type where
parseJSON :: Value -> Parser CouponCreateDiscount_type
parseJSON Value
val =
CouponCreateDiscount_type -> Parser CouponCreateDiscount_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
"fixed" -> CouponCreateDiscount_type
CouponCreateDiscount_typeEnumFixed
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"free_trial" -> CouponCreateDiscount_type
CouponCreateDiscount_typeEnumFree_trial
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"percent" -> CouponCreateDiscount_type
CouponCreateDiscount_typeEnumPercent
| Bool
GHC.Base.otherwise -> Value -> CouponCreateDiscount_type
CouponCreateDiscount_typeOther Value
val
)
data CouponCreateDuration
=
CouponCreateDurationOther Data.Aeson.Types.Internal.Value
|
CouponCreateDurationTyped Data.Text.Internal.Text
|
CouponCreateDurationEnumForever
|
CouponCreateDurationEnumSingle_use
|
CouponCreateDurationEnumTemporal
deriving (Int -> CouponCreateDuration -> ShowS
[CouponCreateDuration] -> ShowS
CouponCreateDuration -> String
(Int -> CouponCreateDuration -> ShowS)
-> (CouponCreateDuration -> String)
-> ([CouponCreateDuration] -> ShowS)
-> Show CouponCreateDuration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CouponCreateDuration -> ShowS
showsPrec :: Int -> CouponCreateDuration -> ShowS
$cshow :: CouponCreateDuration -> String
show :: CouponCreateDuration -> String
$cshowList :: [CouponCreateDuration] -> ShowS
showList :: [CouponCreateDuration] -> ShowS
GHC.Show.Show, CouponCreateDuration -> CouponCreateDuration -> Bool
(CouponCreateDuration -> CouponCreateDuration -> Bool)
-> (CouponCreateDuration -> CouponCreateDuration -> Bool)
-> Eq CouponCreateDuration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CouponCreateDuration -> CouponCreateDuration -> Bool
== :: CouponCreateDuration -> CouponCreateDuration -> Bool
$c/= :: CouponCreateDuration -> CouponCreateDuration -> Bool
/= :: CouponCreateDuration -> CouponCreateDuration -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON CouponCreateDuration where
toJSON :: CouponCreateDuration -> Value
toJSON (CouponCreateDurationOther Value
val) = Value
val
toJSON (CouponCreateDurationTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (CouponCreateDuration
CouponCreateDurationEnumForever) = Value
"forever"
toJSON (CouponCreateDuration
CouponCreateDurationEnumSingle_use) = Value
"single_use"
toJSON (CouponCreateDuration
CouponCreateDurationEnumTemporal) = Value
"temporal"
instance Data.Aeson.Types.FromJSON.FromJSON CouponCreateDuration where
parseJSON :: Value -> Parser CouponCreateDuration
parseJSON Value
val =
CouponCreateDuration -> Parser CouponCreateDuration
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
"forever" -> CouponCreateDuration
CouponCreateDurationEnumForever
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"single_use" -> CouponCreateDuration
CouponCreateDurationEnumSingle_use
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"temporal" -> CouponCreateDuration
CouponCreateDurationEnumTemporal
| Bool
GHC.Base.otherwise -> Value -> CouponCreateDuration
CouponCreateDurationOther Value
val
)
data CouponCreateFree_trial_unit
=
CouponCreateFree_trial_unitOther Data.Aeson.Types.Internal.Value
|
CouponCreateFree_trial_unitTyped Data.Text.Internal.Text
|
CouponCreateFree_trial_unitEnumDay
|
CouponCreateFree_trial_unitEnumMonth
|
CouponCreateFree_trial_unitEnumWeek
deriving (Int -> CouponCreateFree_trial_unit -> ShowS
[CouponCreateFree_trial_unit] -> ShowS
CouponCreateFree_trial_unit -> String
(Int -> CouponCreateFree_trial_unit -> ShowS)
-> (CouponCreateFree_trial_unit -> String)
-> ([CouponCreateFree_trial_unit] -> ShowS)
-> Show CouponCreateFree_trial_unit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CouponCreateFree_trial_unit -> ShowS
showsPrec :: Int -> CouponCreateFree_trial_unit -> ShowS
$cshow :: CouponCreateFree_trial_unit -> String
show :: CouponCreateFree_trial_unit -> String
$cshowList :: [CouponCreateFree_trial_unit] -> ShowS
showList :: [CouponCreateFree_trial_unit] -> ShowS
GHC.Show.Show, CouponCreateFree_trial_unit -> CouponCreateFree_trial_unit -> Bool
(CouponCreateFree_trial_unit
-> CouponCreateFree_trial_unit -> Bool)
-> (CouponCreateFree_trial_unit
-> CouponCreateFree_trial_unit -> Bool)
-> Eq CouponCreateFree_trial_unit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CouponCreateFree_trial_unit -> CouponCreateFree_trial_unit -> Bool
== :: CouponCreateFree_trial_unit -> CouponCreateFree_trial_unit -> Bool
$c/= :: CouponCreateFree_trial_unit -> CouponCreateFree_trial_unit -> Bool
/= :: CouponCreateFree_trial_unit -> CouponCreateFree_trial_unit -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON CouponCreateFree_trial_unit where
toJSON :: CouponCreateFree_trial_unit -> Value
toJSON (CouponCreateFree_trial_unitOther Value
val) = Value
val
toJSON (CouponCreateFree_trial_unitTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (CouponCreateFree_trial_unit
CouponCreateFree_trial_unitEnumDay) = Value
"day"
toJSON (CouponCreateFree_trial_unit
CouponCreateFree_trial_unitEnumMonth) = Value
"month"
toJSON (CouponCreateFree_trial_unit
CouponCreateFree_trial_unitEnumWeek) = Value
"week"
instance Data.Aeson.Types.FromJSON.FromJSON CouponCreateFree_trial_unit where
parseJSON :: Value -> Parser CouponCreateFree_trial_unit
parseJSON Value
val =
CouponCreateFree_trial_unit -> Parser CouponCreateFree_trial_unit
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
( if
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"day" -> CouponCreateFree_trial_unit
CouponCreateFree_trial_unitEnumDay
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"month" -> CouponCreateFree_trial_unit
CouponCreateFree_trial_unitEnumMonth
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"week" -> CouponCreateFree_trial_unit
CouponCreateFree_trial_unitEnumWeek
| Bool
GHC.Base.otherwise -> Value -> CouponCreateFree_trial_unit
CouponCreateFree_trial_unitOther Value
val
)
data CouponCreateRedemption_resource
=
CouponCreateRedemption_resourceOther Data.Aeson.Types.Internal.Value
|
CouponCreateRedemption_resourceTyped Data.Text.Internal.Text
|
CouponCreateRedemption_resourceEnumAccount
|
CouponCreateRedemption_resourceEnumSubscription
deriving (Int -> CouponCreateRedemption_resource -> ShowS
[CouponCreateRedemption_resource] -> ShowS
CouponCreateRedemption_resource -> String
(Int -> CouponCreateRedemption_resource -> ShowS)
-> (CouponCreateRedemption_resource -> String)
-> ([CouponCreateRedemption_resource] -> ShowS)
-> Show CouponCreateRedemption_resource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CouponCreateRedemption_resource -> ShowS
showsPrec :: Int -> CouponCreateRedemption_resource -> ShowS
$cshow :: CouponCreateRedemption_resource -> String
show :: CouponCreateRedemption_resource -> String
$cshowList :: [CouponCreateRedemption_resource] -> ShowS
showList :: [CouponCreateRedemption_resource] -> ShowS
GHC.Show.Show, CouponCreateRedemption_resource
-> CouponCreateRedemption_resource -> Bool
(CouponCreateRedemption_resource
-> CouponCreateRedemption_resource -> Bool)
-> (CouponCreateRedemption_resource
-> CouponCreateRedemption_resource -> Bool)
-> Eq CouponCreateRedemption_resource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CouponCreateRedemption_resource
-> CouponCreateRedemption_resource -> Bool
== :: CouponCreateRedemption_resource
-> CouponCreateRedemption_resource -> Bool
$c/= :: CouponCreateRedemption_resource
-> CouponCreateRedemption_resource -> Bool
/= :: CouponCreateRedemption_resource
-> CouponCreateRedemption_resource -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON CouponCreateRedemption_resource where
toJSON :: CouponCreateRedemption_resource -> Value
toJSON (CouponCreateRedemption_resourceOther Value
val) = Value
val
toJSON (CouponCreateRedemption_resourceTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (CouponCreateRedemption_resource
CouponCreateRedemption_resourceEnumAccount) = Value
"account"
toJSON (CouponCreateRedemption_resource
CouponCreateRedemption_resourceEnumSubscription) = Value
"subscription"
instance Data.Aeson.Types.FromJSON.FromJSON CouponCreateRedemption_resource where
parseJSON :: Value -> Parser CouponCreateRedemption_resource
parseJSON Value
val =
CouponCreateRedemption_resource
-> Parser CouponCreateRedemption_resource
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
"account" -> CouponCreateRedemption_resource
CouponCreateRedemption_resourceEnumAccount
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"subscription" -> CouponCreateRedemption_resource
CouponCreateRedemption_resourceEnumSubscription
| Bool
GHC.Base.otherwise -> Value -> CouponCreateRedemption_resource
CouponCreateRedemption_resourceOther Value
val
)
data CouponCreateTemporal_unit
=
CouponCreateTemporal_unitOther Data.Aeson.Types.Internal.Value
|
CouponCreateTemporal_unitTyped Data.Text.Internal.Text
|
CouponCreateTemporal_unitEnumDay
|
CouponCreateTemporal_unitEnumMonth
|
CouponCreateTemporal_unitEnumWeek
|
CouponCreateTemporal_unitEnumYear
deriving (Int -> CouponCreateTemporal_unit -> ShowS
[CouponCreateTemporal_unit] -> ShowS
CouponCreateTemporal_unit -> String
(Int -> CouponCreateTemporal_unit -> ShowS)
-> (CouponCreateTemporal_unit -> String)
-> ([CouponCreateTemporal_unit] -> ShowS)
-> Show CouponCreateTemporal_unit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CouponCreateTemporal_unit -> ShowS
showsPrec :: Int -> CouponCreateTemporal_unit -> ShowS
$cshow :: CouponCreateTemporal_unit -> String
show :: CouponCreateTemporal_unit -> String
$cshowList :: [CouponCreateTemporal_unit] -> ShowS
showList :: [CouponCreateTemporal_unit] -> ShowS
GHC.Show.Show, CouponCreateTemporal_unit -> CouponCreateTemporal_unit -> Bool
(CouponCreateTemporal_unit -> CouponCreateTemporal_unit -> Bool)
-> (CouponCreateTemporal_unit -> CouponCreateTemporal_unit -> Bool)
-> Eq CouponCreateTemporal_unit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CouponCreateTemporal_unit -> CouponCreateTemporal_unit -> Bool
== :: CouponCreateTemporal_unit -> CouponCreateTemporal_unit -> Bool
$c/= :: CouponCreateTemporal_unit -> CouponCreateTemporal_unit -> Bool
/= :: CouponCreateTemporal_unit -> CouponCreateTemporal_unit -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON CouponCreateTemporal_unit where
toJSON :: CouponCreateTemporal_unit -> Value
toJSON (CouponCreateTemporal_unitOther Value
val) = Value
val
toJSON (CouponCreateTemporal_unitTyped Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (CouponCreateTemporal_unit
CouponCreateTemporal_unitEnumDay) = Value
"day"
toJSON (CouponCreateTemporal_unit
CouponCreateTemporal_unitEnumMonth) = Value
"month"
toJSON (CouponCreateTemporal_unit
CouponCreateTemporal_unitEnumWeek) = Value
"week"
toJSON (CouponCreateTemporal_unit
CouponCreateTemporal_unitEnumYear) = Value
"year"
instance Data.Aeson.Types.FromJSON.FromJSON CouponCreateTemporal_unit where
parseJSON :: Value -> Parser CouponCreateTemporal_unit
parseJSON Value
val =
CouponCreateTemporal_unit -> Parser CouponCreateTemporal_unit
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
( if
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"day" -> CouponCreateTemporal_unit
CouponCreateTemporal_unitEnumDay
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"month" -> CouponCreateTemporal_unit
CouponCreateTemporal_unitEnumMonth
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"week" -> CouponCreateTemporal_unit
CouponCreateTemporal_unitEnumWeek
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"year" -> CouponCreateTemporal_unit
CouponCreateTemporal_unitEnumYear
| Bool
GHC.Base.otherwise -> Value -> CouponCreateTemporal_unit
CouponCreateTemporal_unitOther Value
val
)