{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE MultiWayIf #-}
-- CHANGE WITH CAUTION: This is a generated code file generated by https://github.com/Haskell-OpenAPI-Code-Generator/Haskell-OpenAPI-Client-Code-Generator.
{-# LANGUAGE OverloadedStrings #-}

-- | Contains the different functions to run the operation postCoupons
module StripeAPI.Operations.PostCoupons where

import qualified Control.Monad.Fail
import qualified Control.Monad.Trans.Reader
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.Char8
import qualified Data.ByteString.Char8 as Data.ByteString.Internal
import qualified Data.Either
import qualified Data.Functor
import qualified Data.Scientific
import qualified Data.Text
import qualified 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 Data.Vector
import qualified GHC.Base
import qualified GHC.Classes
import qualified GHC.Int
import qualified GHC.Show
import qualified GHC.Types
import qualified Network.HTTP.Client
import qualified Network.HTTP.Client as Network.HTTP.Client.Request
import qualified Network.HTTP.Client as Network.HTTP.Client.Types
import qualified Network.HTTP.Simple
import qualified Network.HTTP.Types
import qualified Network.HTTP.Types as Network.HTTP.Types.Status
import qualified Network.HTTP.Types as Network.HTTP.Types.URI
import qualified StripeAPI.Common
import StripeAPI.Types
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe

-- | > POST /v1/coupons
--
-- \<p>You can create coupons easily via the \<a href=\"https:\/\/dashboard.stripe.com\/coupons\">coupon management\<\/a> page of the Stripe dashboard. Coupon creation is also accessible via the API if you need to create coupons on the fly.\<\/p>
--
-- \<p>A coupon has either a \<code>percent_off\<\/code> or an \<code>amount_off\<\/code> and \<code>currency\<\/code>. If you set an \<code>amount_off\<\/code>, that amount will be subtracted from any invoice’s subtotal. For example, an invoice with a subtotal of \<currency>100\<\/currency> will have a final total of \<currency>0\<\/currency> if a coupon with an \<code>amount_off\<\/code> of \<amount>200\<\/amount> is applied to it and an invoice with a subtotal of \<currency>300\<\/currency> will have a final total of \<currency>100\<\/currency> if a coupon with an \<code>amount_off\<\/code> of \<amount>200\<\/amount> is applied to it.\<\/p>
postCoupons ::
  forall m.
  StripeAPI.Common.MonadHTTP m =>
  -- | The request body to send
  GHC.Maybe.Maybe PostCouponsRequestBody ->
  -- | Monadic computation which returns the result of the operation
  StripeAPI.Common.StripeT m (Network.HTTP.Client.Types.Response PostCouponsResponse)
postCoupons :: Maybe PostCouponsRequestBody
-> StripeT m (Response PostCouponsResponse)
postCoupons Maybe PostCouponsRequestBody
body =
  (Response ByteString -> Response PostCouponsResponse)
-> StripeT m (Response ByteString)
-> StripeT m (Response PostCouponsResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
    ( \Response ByteString
response_0 ->
        (ByteString -> PostCouponsResponse)
-> Response ByteString -> Response PostCouponsResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
          ( (String -> PostCouponsResponse)
-> (PostCouponsResponse -> PostCouponsResponse)
-> Either String PostCouponsResponse
-> PostCouponsResponse
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
Data.Either.either String -> PostCouponsResponse
PostCouponsResponseError PostCouponsResponse -> PostCouponsResponse
forall a. a -> a
GHC.Base.id
              (Either String PostCouponsResponse -> PostCouponsResponse)
-> (ByteString -> Either String PostCouponsResponse)
-> ByteString
-> PostCouponsResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. ( \Response ByteString
response ByteString
body ->
                             if
                                 | (\Status
status_1 -> Status -> Int
Network.HTTP.Types.Status.statusCode Status
status_1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Int
200) (Response ByteString -> Status
forall body. Response body -> Status
Network.HTTP.Client.Types.responseStatus Response ByteString
response) ->
                                   Coupon -> PostCouponsResponse
PostCouponsResponse200
                                     (Coupon -> PostCouponsResponse)
-> Either String Coupon -> Either String PostCouponsResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String Coupon
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                          Data.Either.Either
                                                            GHC.Base.String
                                                            Coupon
                                                      )
                                 | Bool -> Status -> Bool
forall a b. a -> b -> a
GHC.Base.const Bool
GHC.Types.True (Response ByteString -> Status
forall body. Response body -> Status
Network.HTTP.Client.Types.responseStatus Response ByteString
response) ->
                                   Error -> PostCouponsResponse
PostCouponsResponseDefault
                                     (Error -> PostCouponsResponse)
-> Either String Error -> Either String PostCouponsResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String Error
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                          Data.Either.Either
                                                            GHC.Base.String
                                                            Error
                                                      )
                                 | Bool
GHC.Base.otherwise -> String -> Either String PostCouponsResponse
forall a b. a -> Either a b
Data.Either.Left String
"Missing default response type"
                         )
                Response ByteString
response_0
          )
          Response ByteString
response_0
    )
    (Text
-> Text
-> [QueryParameter]
-> Maybe PostCouponsRequestBody
-> RequestBodyEncoding
-> StripeT m (Response ByteString)
forall (m :: * -> *) body.
(MonadHTTP m, ToJSON body) =>
Text
-> Text
-> [QueryParameter]
-> Maybe body
-> RequestBodyEncoding
-> StripeT m (Response ByteString)
StripeAPI.Common.doBodyCallWithConfigurationM (Text -> Text
Data.Text.toUpper (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
GHC.Base.$ String -> Text
Data.Text.pack String
"POST") (String -> Text
Data.Text.pack String
"/v1/coupons") [QueryParameter]
forall a. Monoid a => a
GHC.Base.mempty Maybe PostCouponsRequestBody
body RequestBodyEncoding
StripeAPI.Common.RequestBodyEncodingFormData)

-- | Defines the object schema located at @paths.\/v1\/coupons.POST.requestBody.content.application\/x-www-form-urlencoded.schema@ in the specification.
data PostCouponsRequestBody = PostCouponsRequestBody
  { -- | amount_off: A positive integer representing the amount to subtract from an invoice total (required if \`percent_off\` is not passed).
    PostCouponsRequestBody -> Maybe Int
postCouponsRequestBodyAmountOff :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | applies_to: A hash containing directions for what this Coupon will apply discounts to.
    PostCouponsRequestBody -> Maybe PostCouponsRequestBodyAppliesTo'
postCouponsRequestBodyAppliesTo :: (GHC.Maybe.Maybe PostCouponsRequestBodyAppliesTo'),
    -- | currency: Three-letter [ISO code for the currency](https:\/\/stripe.com\/docs\/currencies) of the \`amount_off\` parameter (required if \`amount_off\` is passed).
    PostCouponsRequestBody -> Maybe Text
postCouponsRequestBodyCurrency :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | duration: Specifies how long the discount will be in effect if used on a subscription. Can be \`forever\`, \`once\`, or \`repeating\`. Defaults to \`once\`.
    PostCouponsRequestBody -> Maybe PostCouponsRequestBodyDuration'
postCouponsRequestBodyDuration :: (GHC.Maybe.Maybe PostCouponsRequestBodyDuration'),
    -- | duration_in_months: Required only if \`duration\` is \`repeating\`, in which case it must be a positive integer that specifies the number of months the discount will be in effect.
    PostCouponsRequestBody -> Maybe Int
postCouponsRequestBodyDurationInMonths :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | expand: Specifies which fields in the response should be expanded.
    PostCouponsRequestBody -> Maybe [Text]
postCouponsRequestBodyExpand :: (GHC.Maybe.Maybe ([Data.Text.Internal.Text])),
    -- | id: Unique string of your choice that will be used to identify this coupon when applying it to a customer. If you don\'t want to specify a particular code, you can leave the ID blank and we\'ll generate a random code for you.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCouponsRequestBody -> Maybe Text
postCouponsRequestBodyId :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | max_redemptions: A positive integer specifying the number of times the coupon can be redeemed before it\'s no longer valid. For example, you might have a 50% off coupon that the first 20 readers of your blog can use.
    PostCouponsRequestBody -> Maybe Int
postCouponsRequestBodyMaxRedemptions :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | metadata: Set of [key-value pairs](https:\/\/stripe.com\/docs\/api\/metadata) that you can attach to an object. This can be useful for storing additional information about the object in a structured format. Individual keys can be unset by posting an empty value to them. All keys can be unset by posting an empty value to \`metadata\`.
    PostCouponsRequestBody
-> Maybe PostCouponsRequestBodyMetadata'Variants
postCouponsRequestBodyMetadata :: (GHC.Maybe.Maybe PostCouponsRequestBodyMetadata'Variants),
    -- | name: Name of the coupon displayed to customers on, for instance invoices, or receipts. By default the \`id\` is shown if \`name\` is not set.
    --
    -- Constraints:
    --
    -- * Maximum length of 40
    PostCouponsRequestBody -> Maybe Text
postCouponsRequestBodyName :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | percent_off: A positive float larger than 0, and smaller or equal to 100, that represents the discount the coupon will apply (required if \`amount_off\` is not passed).
    PostCouponsRequestBody -> Maybe Double
postCouponsRequestBodyPercentOff :: (GHC.Maybe.Maybe GHC.Types.Double),
    -- | redeem_by: Unix timestamp specifying the last time at which the coupon can be redeemed. After the redeem_by date, the coupon can no longer be applied to new customers.
    PostCouponsRequestBody -> Maybe Int
postCouponsRequestBodyRedeemBy :: (GHC.Maybe.Maybe GHC.Types.Int)
  }
  deriving
    ( Int -> PostCouponsRequestBody -> ShowS
[PostCouponsRequestBody] -> ShowS
PostCouponsRequestBody -> String
(Int -> PostCouponsRequestBody -> ShowS)
-> (PostCouponsRequestBody -> String)
-> ([PostCouponsRequestBody] -> ShowS)
-> Show PostCouponsRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCouponsRequestBody] -> ShowS
$cshowList :: [PostCouponsRequestBody] -> ShowS
show :: PostCouponsRequestBody -> String
$cshow :: PostCouponsRequestBody -> String
showsPrec :: Int -> PostCouponsRequestBody -> ShowS
$cshowsPrec :: Int -> PostCouponsRequestBody -> ShowS
GHC.Show.Show,
      PostCouponsRequestBody -> PostCouponsRequestBody -> Bool
(PostCouponsRequestBody -> PostCouponsRequestBody -> Bool)
-> (PostCouponsRequestBody -> PostCouponsRequestBody -> Bool)
-> Eq PostCouponsRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCouponsRequestBody -> PostCouponsRequestBody -> Bool
$c/= :: PostCouponsRequestBody -> PostCouponsRequestBody -> Bool
== :: PostCouponsRequestBody -> PostCouponsRequestBody -> Bool
$c== :: PostCouponsRequestBody -> PostCouponsRequestBody -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCouponsRequestBody where
  toJSON :: PostCouponsRequestBody -> Value
toJSON PostCouponsRequestBody
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"amount_off" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Int
postCouponsRequestBodyAmountOff PostCouponsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"applies_to" Text -> Maybe PostCouponsRequestBodyAppliesTo' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe PostCouponsRequestBodyAppliesTo'
postCouponsRequestBodyAppliesTo PostCouponsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"currency" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Text
postCouponsRequestBodyCurrency PostCouponsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"duration" Text -> Maybe PostCouponsRequestBodyDuration' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe PostCouponsRequestBodyDuration'
postCouponsRequestBodyDuration PostCouponsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"duration_in_months" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Int
postCouponsRequestBodyDurationInMonths PostCouponsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"expand" Text -> Maybe [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe [Text]
postCouponsRequestBodyExpand PostCouponsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"id" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Text
postCouponsRequestBodyId PostCouponsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"max_redemptions" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Int
postCouponsRequestBodyMaxRedemptions PostCouponsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text -> Maybe PostCouponsRequestBodyMetadata'Variants -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody
-> Maybe PostCouponsRequestBodyMetadata'Variants
postCouponsRequestBodyMetadata PostCouponsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"name" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Text
postCouponsRequestBodyName PostCouponsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"percent_off" Text -> Maybe Double -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Double
postCouponsRequestBodyPercentOff PostCouponsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"redeem_by" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Int
postCouponsRequestBodyRedeemBy PostCouponsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCouponsRequestBody -> Encoding
toEncoding PostCouponsRequestBody
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"amount_off" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Int
postCouponsRequestBodyAmountOff PostCouponsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"applies_to" Text -> Maybe PostCouponsRequestBodyAppliesTo' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe PostCouponsRequestBodyAppliesTo'
postCouponsRequestBodyAppliesTo PostCouponsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"currency" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Text
postCouponsRequestBodyCurrency PostCouponsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"duration" Text -> Maybe PostCouponsRequestBodyDuration' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe PostCouponsRequestBodyDuration'
postCouponsRequestBodyDuration PostCouponsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"duration_in_months" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Int
postCouponsRequestBodyDurationInMonths PostCouponsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"expand" Text -> Maybe [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe [Text]
postCouponsRequestBodyExpand PostCouponsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"id" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Text
postCouponsRequestBodyId PostCouponsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"max_redemptions" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Int
postCouponsRequestBodyMaxRedemptions PostCouponsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"metadata" Text -> Maybe PostCouponsRequestBodyMetadata'Variants -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody
-> Maybe PostCouponsRequestBodyMetadata'Variants
postCouponsRequestBodyMetadata PostCouponsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"name" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Text
postCouponsRequestBodyName PostCouponsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"percent_off" Text -> Maybe Double -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Double
postCouponsRequestBodyPercentOff PostCouponsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"redeem_by" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBody -> Maybe Int
postCouponsRequestBodyRedeemBy PostCouponsRequestBody
obj))))))))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCouponsRequestBody where
  parseJSON :: Value -> Parser PostCouponsRequestBody
parseJSON = String
-> (Object -> Parser PostCouponsRequestBody)
-> Value
-> Parser PostCouponsRequestBody
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCouponsRequestBody" (\Object
obj -> ((((((((((((Maybe Int
 -> Maybe PostCouponsRequestBodyAppliesTo'
 -> Maybe Text
 -> Maybe PostCouponsRequestBodyDuration'
 -> Maybe Int
 -> Maybe [Text]
 -> Maybe Text
 -> Maybe Int
 -> Maybe PostCouponsRequestBodyMetadata'Variants
 -> Maybe Text
 -> Maybe Double
 -> Maybe Int
 -> PostCouponsRequestBody)
-> Parser
     (Maybe Int
      -> Maybe PostCouponsRequestBodyAppliesTo'
      -> Maybe Text
      -> Maybe PostCouponsRequestBodyDuration'
      -> Maybe Int
      -> Maybe [Text]
      -> Maybe Text
      -> Maybe Int
      -> Maybe PostCouponsRequestBodyMetadata'Variants
      -> Maybe Text
      -> Maybe Double
      -> Maybe Int
      -> PostCouponsRequestBody)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Int
-> Maybe PostCouponsRequestBodyAppliesTo'
-> Maybe Text
-> Maybe PostCouponsRequestBodyDuration'
-> Maybe Int
-> Maybe [Text]
-> Maybe Text
-> Maybe Int
-> Maybe PostCouponsRequestBodyMetadata'Variants
-> Maybe Text
-> Maybe Double
-> Maybe Int
-> PostCouponsRequestBody
PostCouponsRequestBody Parser
  (Maybe Int
   -> Maybe PostCouponsRequestBodyAppliesTo'
   -> Maybe Text
   -> Maybe PostCouponsRequestBodyDuration'
   -> Maybe Int
   -> Maybe [Text]
   -> Maybe Text
   -> Maybe Int
   -> Maybe PostCouponsRequestBodyMetadata'Variants
   -> Maybe Text
   -> Maybe Double
   -> Maybe Int
   -> PostCouponsRequestBody)
-> Parser (Maybe Int)
-> Parser
     (Maybe PostCouponsRequestBodyAppliesTo'
      -> Maybe Text
      -> Maybe PostCouponsRequestBodyDuration'
      -> Maybe Int
      -> Maybe [Text]
      -> Maybe Text
      -> Maybe Int
      -> Maybe PostCouponsRequestBodyMetadata'Variants
      -> Maybe Text
      -> Maybe Double
      -> Maybe Int
      -> PostCouponsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"amount_off")) Parser
  (Maybe PostCouponsRequestBodyAppliesTo'
   -> Maybe Text
   -> Maybe PostCouponsRequestBodyDuration'
   -> Maybe Int
   -> Maybe [Text]
   -> Maybe Text
   -> Maybe Int
   -> Maybe PostCouponsRequestBodyMetadata'Variants
   -> Maybe Text
   -> Maybe Double
   -> Maybe Int
   -> PostCouponsRequestBody)
-> Parser (Maybe PostCouponsRequestBodyAppliesTo')
-> Parser
     (Maybe Text
      -> Maybe PostCouponsRequestBodyDuration'
      -> Maybe Int
      -> Maybe [Text]
      -> Maybe Text
      -> Maybe Int
      -> Maybe PostCouponsRequestBodyMetadata'Variants
      -> Maybe Text
      -> Maybe Double
      -> Maybe Int
      -> PostCouponsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe PostCouponsRequestBodyAppliesTo')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"applies_to")) Parser
  (Maybe Text
   -> Maybe PostCouponsRequestBodyDuration'
   -> Maybe Int
   -> Maybe [Text]
   -> Maybe Text
   -> Maybe Int
   -> Maybe PostCouponsRequestBodyMetadata'Variants
   -> Maybe Text
   -> Maybe Double
   -> Maybe Int
   -> PostCouponsRequestBody)
-> Parser (Maybe Text)
-> Parser
     (Maybe PostCouponsRequestBodyDuration'
      -> Maybe Int
      -> Maybe [Text]
      -> Maybe Text
      -> Maybe Int
      -> Maybe PostCouponsRequestBodyMetadata'Variants
      -> Maybe Text
      -> Maybe Double
      -> Maybe Int
      -> PostCouponsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"currency")) Parser
  (Maybe PostCouponsRequestBodyDuration'
   -> Maybe Int
   -> Maybe [Text]
   -> Maybe Text
   -> Maybe Int
   -> Maybe PostCouponsRequestBodyMetadata'Variants
   -> Maybe Text
   -> Maybe Double
   -> Maybe Int
   -> PostCouponsRequestBody)
-> Parser (Maybe PostCouponsRequestBodyDuration')
-> Parser
     (Maybe Int
      -> Maybe [Text]
      -> Maybe Text
      -> Maybe Int
      -> Maybe PostCouponsRequestBodyMetadata'Variants
      -> Maybe Text
      -> Maybe Double
      -> Maybe Int
      -> PostCouponsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe PostCouponsRequestBodyDuration')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"duration")) Parser
  (Maybe Int
   -> Maybe [Text]
   -> Maybe Text
   -> Maybe Int
   -> Maybe PostCouponsRequestBodyMetadata'Variants
   -> Maybe Text
   -> Maybe Double
   -> Maybe Int
   -> PostCouponsRequestBody)
-> Parser (Maybe Int)
-> Parser
     (Maybe [Text]
      -> Maybe Text
      -> Maybe Int
      -> Maybe PostCouponsRequestBodyMetadata'Variants
      -> Maybe Text
      -> Maybe Double
      -> Maybe Int
      -> PostCouponsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"duration_in_months")) Parser
  (Maybe [Text]
   -> Maybe Text
   -> Maybe Int
   -> Maybe PostCouponsRequestBodyMetadata'Variants
   -> Maybe Text
   -> Maybe Double
   -> Maybe Int
   -> PostCouponsRequestBody)
-> Parser (Maybe [Text])
-> Parser
     (Maybe Text
      -> Maybe Int
      -> Maybe PostCouponsRequestBodyMetadata'Variants
      -> Maybe Text
      -> Maybe Double
      -> Maybe Int
      -> PostCouponsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"expand")) Parser
  (Maybe Text
   -> Maybe Int
   -> Maybe PostCouponsRequestBodyMetadata'Variants
   -> Maybe Text
   -> Maybe Double
   -> Maybe Int
   -> PostCouponsRequestBody)
-> Parser (Maybe Text)
-> Parser
     (Maybe Int
      -> Maybe PostCouponsRequestBodyMetadata'Variants
      -> Maybe Text
      -> Maybe Double
      -> Maybe Int
      -> PostCouponsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"id")) Parser
  (Maybe Int
   -> Maybe PostCouponsRequestBodyMetadata'Variants
   -> Maybe Text
   -> Maybe Double
   -> Maybe Int
   -> PostCouponsRequestBody)
-> Parser (Maybe Int)
-> Parser
     (Maybe PostCouponsRequestBodyMetadata'Variants
      -> Maybe Text
      -> Maybe Double
      -> Maybe Int
      -> PostCouponsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"max_redemptions")) Parser
  (Maybe PostCouponsRequestBodyMetadata'Variants
   -> Maybe Text
   -> Maybe Double
   -> Maybe Int
   -> PostCouponsRequestBody)
-> Parser (Maybe PostCouponsRequestBodyMetadata'Variants)
-> Parser
     (Maybe Text -> Maybe Double -> Maybe Int -> PostCouponsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text -> Parser (Maybe PostCouponsRequestBodyMetadata'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"metadata")) Parser
  (Maybe Text -> Maybe Double -> Maybe Int -> PostCouponsRequestBody)
-> Parser (Maybe Text)
-> Parser (Maybe Double -> Maybe Int -> PostCouponsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"name")) Parser (Maybe Double -> Maybe Int -> PostCouponsRequestBody)
-> Parser (Maybe Double)
-> Parser (Maybe Int -> PostCouponsRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Double)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"percent_off")) Parser (Maybe Int -> PostCouponsRequestBody)
-> Parser (Maybe Int) -> Parser PostCouponsRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"redeem_by"))

-- | Create a new 'PostCouponsRequestBody' with all required fields.
mkPostCouponsRequestBody :: PostCouponsRequestBody
mkPostCouponsRequestBody :: PostCouponsRequestBody
mkPostCouponsRequestBody =
  PostCouponsRequestBody :: Maybe Int
-> Maybe PostCouponsRequestBodyAppliesTo'
-> Maybe Text
-> Maybe PostCouponsRequestBodyDuration'
-> Maybe Int
-> Maybe [Text]
-> Maybe Text
-> Maybe Int
-> Maybe PostCouponsRequestBodyMetadata'Variants
-> Maybe Text
-> Maybe Double
-> Maybe Int
-> PostCouponsRequestBody
PostCouponsRequestBody
    { postCouponsRequestBodyAmountOff :: Maybe Int
postCouponsRequestBodyAmountOff = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCouponsRequestBodyAppliesTo :: Maybe PostCouponsRequestBodyAppliesTo'
postCouponsRequestBodyAppliesTo = Maybe PostCouponsRequestBodyAppliesTo'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCouponsRequestBodyCurrency :: Maybe Text
postCouponsRequestBodyCurrency = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCouponsRequestBodyDuration :: Maybe PostCouponsRequestBodyDuration'
postCouponsRequestBodyDuration = Maybe PostCouponsRequestBodyDuration'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCouponsRequestBodyDurationInMonths :: Maybe Int
postCouponsRequestBodyDurationInMonths = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCouponsRequestBodyExpand :: Maybe [Text]
postCouponsRequestBodyExpand = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      postCouponsRequestBodyId :: Maybe Text
postCouponsRequestBodyId = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCouponsRequestBodyMaxRedemptions :: Maybe Int
postCouponsRequestBodyMaxRedemptions = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCouponsRequestBodyMetadata :: Maybe PostCouponsRequestBodyMetadata'Variants
postCouponsRequestBodyMetadata = Maybe PostCouponsRequestBodyMetadata'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCouponsRequestBodyName :: Maybe Text
postCouponsRequestBodyName = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCouponsRequestBodyPercentOff :: Maybe Double
postCouponsRequestBodyPercentOff = Maybe Double
forall a. Maybe a
GHC.Maybe.Nothing,
      postCouponsRequestBodyRedeemBy :: Maybe Int
postCouponsRequestBodyRedeemBy = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/coupons.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.applies_to@ in the specification.
--
-- A hash containing directions for what this Coupon will apply discounts to.
data PostCouponsRequestBodyAppliesTo' = PostCouponsRequestBodyAppliesTo'
  { -- | products
    PostCouponsRequestBodyAppliesTo' -> Maybe [Text]
postCouponsRequestBodyAppliesTo'Products :: (GHC.Maybe.Maybe ([Data.Text.Internal.Text]))
  }
  deriving
    ( Int -> PostCouponsRequestBodyAppliesTo' -> ShowS
[PostCouponsRequestBodyAppliesTo'] -> ShowS
PostCouponsRequestBodyAppliesTo' -> String
(Int -> PostCouponsRequestBodyAppliesTo' -> ShowS)
-> (PostCouponsRequestBodyAppliesTo' -> String)
-> ([PostCouponsRequestBodyAppliesTo'] -> ShowS)
-> Show PostCouponsRequestBodyAppliesTo'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCouponsRequestBodyAppliesTo'] -> ShowS
$cshowList :: [PostCouponsRequestBodyAppliesTo'] -> ShowS
show :: PostCouponsRequestBodyAppliesTo' -> String
$cshow :: PostCouponsRequestBodyAppliesTo' -> String
showsPrec :: Int -> PostCouponsRequestBodyAppliesTo' -> ShowS
$cshowsPrec :: Int -> PostCouponsRequestBodyAppliesTo' -> ShowS
GHC.Show.Show,
      PostCouponsRequestBodyAppliesTo'
-> PostCouponsRequestBodyAppliesTo' -> Bool
(PostCouponsRequestBodyAppliesTo'
 -> PostCouponsRequestBodyAppliesTo' -> Bool)
-> (PostCouponsRequestBodyAppliesTo'
    -> PostCouponsRequestBodyAppliesTo' -> Bool)
-> Eq PostCouponsRequestBodyAppliesTo'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCouponsRequestBodyAppliesTo'
-> PostCouponsRequestBodyAppliesTo' -> Bool
$c/= :: PostCouponsRequestBodyAppliesTo'
-> PostCouponsRequestBodyAppliesTo' -> Bool
== :: PostCouponsRequestBodyAppliesTo'
-> PostCouponsRequestBodyAppliesTo' -> Bool
$c== :: PostCouponsRequestBodyAppliesTo'
-> PostCouponsRequestBodyAppliesTo' -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCouponsRequestBodyAppliesTo' where
  toJSON :: PostCouponsRequestBodyAppliesTo' -> Value
toJSON PostCouponsRequestBodyAppliesTo'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"products" Text -> Maybe [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBodyAppliesTo' -> Maybe [Text]
postCouponsRequestBodyAppliesTo'Products PostCouponsRequestBodyAppliesTo'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCouponsRequestBodyAppliesTo' -> Encoding
toEncoding PostCouponsRequestBodyAppliesTo'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs (Text
"products" Text -> Maybe [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCouponsRequestBodyAppliesTo' -> Maybe [Text]
postCouponsRequestBodyAppliesTo'Products PostCouponsRequestBodyAppliesTo'
obj)

instance Data.Aeson.Types.FromJSON.FromJSON PostCouponsRequestBodyAppliesTo' where
  parseJSON :: Value -> Parser PostCouponsRequestBodyAppliesTo'
parseJSON = String
-> (Object -> Parser PostCouponsRequestBodyAppliesTo')
-> Value
-> Parser PostCouponsRequestBodyAppliesTo'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCouponsRequestBodyAppliesTo'" (\Object
obj -> (Maybe [Text] -> PostCouponsRequestBodyAppliesTo')
-> Parser (Maybe [Text] -> PostCouponsRequestBodyAppliesTo')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe [Text] -> PostCouponsRequestBodyAppliesTo'
PostCouponsRequestBodyAppliesTo' Parser (Maybe [Text] -> PostCouponsRequestBodyAppliesTo')
-> Parser (Maybe [Text]) -> Parser PostCouponsRequestBodyAppliesTo'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"products"))

-- | Create a new 'PostCouponsRequestBodyAppliesTo'' with all required fields.
mkPostCouponsRequestBodyAppliesTo' :: PostCouponsRequestBodyAppliesTo'
mkPostCouponsRequestBodyAppliesTo' :: PostCouponsRequestBodyAppliesTo'
mkPostCouponsRequestBodyAppliesTo' = PostCouponsRequestBodyAppliesTo' :: Maybe [Text] -> PostCouponsRequestBodyAppliesTo'
PostCouponsRequestBodyAppliesTo' {postCouponsRequestBodyAppliesTo'Products :: Maybe [Text]
postCouponsRequestBodyAppliesTo'Products = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing}

-- | Defines the enum schema located at @paths.\/v1\/coupons.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.duration@ in the specification.
--
-- Specifies how long the discount will be in effect if used on a subscription. Can be \`forever\`, \`once\`, or \`repeating\`. Defaults to \`once\`.
data PostCouponsRequestBodyDuration'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCouponsRequestBodyDuration'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCouponsRequestBodyDuration'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"forever"@
    PostCouponsRequestBodyDuration'EnumForever
  | -- | Represents the JSON value @"once"@
    PostCouponsRequestBodyDuration'EnumOnce
  | -- | Represents the JSON value @"repeating"@
    PostCouponsRequestBodyDuration'EnumRepeating
  deriving (Int -> PostCouponsRequestBodyDuration' -> ShowS
[PostCouponsRequestBodyDuration'] -> ShowS
PostCouponsRequestBodyDuration' -> String
(Int -> PostCouponsRequestBodyDuration' -> ShowS)
-> (PostCouponsRequestBodyDuration' -> String)
-> ([PostCouponsRequestBodyDuration'] -> ShowS)
-> Show PostCouponsRequestBodyDuration'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCouponsRequestBodyDuration'] -> ShowS
$cshowList :: [PostCouponsRequestBodyDuration'] -> ShowS
show :: PostCouponsRequestBodyDuration' -> String
$cshow :: PostCouponsRequestBodyDuration' -> String
showsPrec :: Int -> PostCouponsRequestBodyDuration' -> ShowS
$cshowsPrec :: Int -> PostCouponsRequestBodyDuration' -> ShowS
GHC.Show.Show, PostCouponsRequestBodyDuration'
-> PostCouponsRequestBodyDuration' -> Bool
(PostCouponsRequestBodyDuration'
 -> PostCouponsRequestBodyDuration' -> Bool)
-> (PostCouponsRequestBodyDuration'
    -> PostCouponsRequestBodyDuration' -> Bool)
-> Eq PostCouponsRequestBodyDuration'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCouponsRequestBodyDuration'
-> PostCouponsRequestBodyDuration' -> Bool
$c/= :: PostCouponsRequestBodyDuration'
-> PostCouponsRequestBodyDuration' -> Bool
== :: PostCouponsRequestBodyDuration'
-> PostCouponsRequestBodyDuration' -> Bool
$c== :: PostCouponsRequestBodyDuration'
-> PostCouponsRequestBodyDuration' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCouponsRequestBodyDuration' where
  toJSON :: PostCouponsRequestBodyDuration' -> Value
toJSON (PostCouponsRequestBodyDuration'Other Value
val) = Value
val
  toJSON (PostCouponsRequestBodyDuration'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCouponsRequestBodyDuration'
PostCouponsRequestBodyDuration'EnumForever) = Value
"forever"
  toJSON (PostCouponsRequestBodyDuration'
PostCouponsRequestBodyDuration'EnumOnce) = Value
"once"
  toJSON (PostCouponsRequestBodyDuration'
PostCouponsRequestBodyDuration'EnumRepeating) = Value
"repeating"

instance Data.Aeson.Types.FromJSON.FromJSON PostCouponsRequestBodyDuration' where
  parseJSON :: Value -> Parser PostCouponsRequestBodyDuration'
parseJSON Value
val =
    PostCouponsRequestBodyDuration'
-> Parser PostCouponsRequestBodyDuration'
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" -> PostCouponsRequestBodyDuration'
PostCouponsRequestBodyDuration'EnumForever
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"once" -> PostCouponsRequestBodyDuration'
PostCouponsRequestBodyDuration'EnumOnce
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"repeating" -> PostCouponsRequestBodyDuration'
PostCouponsRequestBodyDuration'EnumRepeating
            | Bool
GHC.Base.otherwise -> Value -> PostCouponsRequestBodyDuration'
PostCouponsRequestBodyDuration'Other Value
val
      )

-- | Defines the oneOf schema located at @paths.\/v1\/coupons.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.metadata.anyOf@ in the specification.
--
-- Set of [key-value pairs](https:\/\/stripe.com\/docs\/api\/metadata) that you can attach to an object. This can be useful for storing additional information about the object in a structured format. Individual keys can be unset by posting an empty value to them. All keys can be unset by posting an empty value to \`metadata\`.
data PostCouponsRequestBodyMetadata'Variants
  = -- | Represents the JSON value @""@
    PostCouponsRequestBodyMetadata'EmptyString
  | PostCouponsRequestBodyMetadata'Object Data.Aeson.Types.Internal.Object
  deriving (Int -> PostCouponsRequestBodyMetadata'Variants -> ShowS
[PostCouponsRequestBodyMetadata'Variants] -> ShowS
PostCouponsRequestBodyMetadata'Variants -> String
(Int -> PostCouponsRequestBodyMetadata'Variants -> ShowS)
-> (PostCouponsRequestBodyMetadata'Variants -> String)
-> ([PostCouponsRequestBodyMetadata'Variants] -> ShowS)
-> Show PostCouponsRequestBodyMetadata'Variants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCouponsRequestBodyMetadata'Variants] -> ShowS
$cshowList :: [PostCouponsRequestBodyMetadata'Variants] -> ShowS
show :: PostCouponsRequestBodyMetadata'Variants -> String
$cshow :: PostCouponsRequestBodyMetadata'Variants -> String
showsPrec :: Int -> PostCouponsRequestBodyMetadata'Variants -> ShowS
$cshowsPrec :: Int -> PostCouponsRequestBodyMetadata'Variants -> ShowS
GHC.Show.Show, PostCouponsRequestBodyMetadata'Variants
-> PostCouponsRequestBodyMetadata'Variants -> Bool
(PostCouponsRequestBodyMetadata'Variants
 -> PostCouponsRequestBodyMetadata'Variants -> Bool)
-> (PostCouponsRequestBodyMetadata'Variants
    -> PostCouponsRequestBodyMetadata'Variants -> Bool)
-> Eq PostCouponsRequestBodyMetadata'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCouponsRequestBodyMetadata'Variants
-> PostCouponsRequestBodyMetadata'Variants -> Bool
$c/= :: PostCouponsRequestBodyMetadata'Variants
-> PostCouponsRequestBodyMetadata'Variants -> Bool
== :: PostCouponsRequestBodyMetadata'Variants
-> PostCouponsRequestBodyMetadata'Variants -> Bool
$c== :: PostCouponsRequestBodyMetadata'Variants
-> PostCouponsRequestBodyMetadata'Variants -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCouponsRequestBodyMetadata'Variants where
  toJSON :: PostCouponsRequestBodyMetadata'Variants -> Value
toJSON (PostCouponsRequestBodyMetadata'Object Object
a) = Object -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Object
a
  toJSON (PostCouponsRequestBodyMetadata'Variants
PostCouponsRequestBodyMetadata'EmptyString) = Value
""

instance Data.Aeson.Types.FromJSON.FromJSON PostCouponsRequestBodyMetadata'Variants where
  parseJSON :: Value -> Parser PostCouponsRequestBodyMetadata'Variants
parseJSON Value
val =
    if
        | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"" -> PostCouponsRequestBodyMetadata'Variants
-> Parser PostCouponsRequestBodyMetadata'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCouponsRequestBodyMetadata'Variants
PostCouponsRequestBodyMetadata'EmptyString
        | Bool
GHC.Base.otherwise -> case (Object -> PostCouponsRequestBodyMetadata'Variants
PostCouponsRequestBodyMetadata'Object (Object -> PostCouponsRequestBodyMetadata'Variants)
-> Result Object -> Result PostCouponsRequestBodyMetadata'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Object
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result PostCouponsRequestBodyMetadata'Variants
-> Result PostCouponsRequestBodyMetadata'Variants
-> Result PostCouponsRequestBodyMetadata'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String -> Result PostCouponsRequestBodyMetadata'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched" of
          Data.Aeson.Types.Internal.Success PostCouponsRequestBodyMetadata'Variants
a -> PostCouponsRequestBodyMetadata'Variants
-> Parser PostCouponsRequestBodyMetadata'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCouponsRequestBodyMetadata'Variants
a
          Data.Aeson.Types.Internal.Error String
a -> String -> Parser PostCouponsRequestBodyMetadata'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a

-- | Represents a response of the operation 'postCoupons'.
--
-- The response constructor is chosen by the status code of the response. If no case matches (no specific case for the response code, no range case, no default case), 'PostCouponsResponseError' is used.
data PostCouponsResponse
  = -- | Means either no matching case available or a parse error
    PostCouponsResponseError GHC.Base.String
  | -- | Successful response.
    PostCouponsResponse200 Coupon
  | -- | Error response.
    PostCouponsResponseDefault Error
  deriving (Int -> PostCouponsResponse -> ShowS
[PostCouponsResponse] -> ShowS
PostCouponsResponse -> String
(Int -> PostCouponsResponse -> ShowS)
-> (PostCouponsResponse -> String)
-> ([PostCouponsResponse] -> ShowS)
-> Show PostCouponsResponse
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostCouponsResponse] -> ShowS
$cshowList :: [PostCouponsResponse] -> ShowS
show :: PostCouponsResponse -> String
$cshow :: PostCouponsResponse -> String
showsPrec :: Int -> PostCouponsResponse -> ShowS
$cshowsPrec :: Int -> PostCouponsResponse -> ShowS
GHC.Show.Show, PostCouponsResponse -> PostCouponsResponse -> Bool
(PostCouponsResponse -> PostCouponsResponse -> Bool)
-> (PostCouponsResponse -> PostCouponsResponse -> Bool)
-> Eq PostCouponsResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCouponsResponse -> PostCouponsResponse -> Bool
$c/= :: PostCouponsResponse -> PostCouponsResponse -> Bool
== :: PostCouponsResponse -> PostCouponsResponse -> Bool
$c== :: PostCouponsResponse -> PostCouponsResponse -> Bool
GHC.Classes.Eq)