{-# 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 deleteSubscriptionItemsItem
module StripeAPI.Operations.DeleteSubscriptionItemsItem 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

-- | > DELETE /v1/subscription_items/{item}
--
-- \<p>Deletes an item from the subscription. Removing a subscription item from a subscription will not cancel the subscription.\<\/p>
deleteSubscriptionItemsItem ::
  forall m.
  StripeAPI.Common.MonadHTTP m =>
  -- | item | Constraints: Maximum length of 5000
  Data.Text.Internal.Text ->
  -- | The request body to send
  GHC.Maybe.Maybe DeleteSubscriptionItemsItemRequestBody ->
  -- | Monadic computation which returns the result of the operation
  StripeAPI.Common.StripeT m (Network.HTTP.Client.Types.Response DeleteSubscriptionItemsItemResponse)
deleteSubscriptionItemsItem :: Text
-> Maybe DeleteSubscriptionItemsItemRequestBody
-> StripeT m (Response DeleteSubscriptionItemsItemResponse)
deleteSubscriptionItemsItem
  Text
item
  Maybe DeleteSubscriptionItemsItemRequestBody
body =
    (Response ByteString
 -> Response DeleteSubscriptionItemsItemResponse)
-> StripeT m (Response ByteString)
-> StripeT m (Response DeleteSubscriptionItemsItemResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
      ( \Response ByteString
response_0 ->
          (ByteString -> DeleteSubscriptionItemsItemResponse)
-> Response ByteString
-> Response DeleteSubscriptionItemsItemResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
            ( (String -> DeleteSubscriptionItemsItemResponse)
-> (DeleteSubscriptionItemsItemResponse
    -> DeleteSubscriptionItemsItemResponse)
-> Either String DeleteSubscriptionItemsItemResponse
-> DeleteSubscriptionItemsItemResponse
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
Data.Either.either String -> DeleteSubscriptionItemsItemResponse
DeleteSubscriptionItemsItemResponseError DeleteSubscriptionItemsItemResponse
-> DeleteSubscriptionItemsItemResponse
forall a. a -> a
GHC.Base.id
                (Either String DeleteSubscriptionItemsItemResponse
 -> DeleteSubscriptionItemsItemResponse)
-> (ByteString
    -> Either String DeleteSubscriptionItemsItemResponse)
-> ByteString
-> DeleteSubscriptionItemsItemResponse
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) ->
                                     DeletedSubscriptionItem -> DeleteSubscriptionItemsItemResponse
DeleteSubscriptionItemsItemResponse200
                                       (DeletedSubscriptionItem -> DeleteSubscriptionItemsItemResponse)
-> Either String DeletedSubscriptionItem
-> Either String DeleteSubscriptionItemsItemResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String DeletedSubscriptionItem
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                            Data.Either.Either
                                                              GHC.Base.String
                                                              DeletedSubscriptionItem
                                                        )
                                   | 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 -> DeleteSubscriptionItemsItemResponse
DeleteSubscriptionItemsItemResponseDefault
                                       (Error -> DeleteSubscriptionItemsItemResponse)
-> Either String Error
-> Either String DeleteSubscriptionItemsItemResponse
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 DeleteSubscriptionItemsItemResponse
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 DeleteSubscriptionItemsItemRequestBody
-> 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
"DELETE") (String -> Text
Data.Text.pack (String
"/v1/subscription_items/" String -> String -> String
forall a. [a] -> [a] -> [a]
GHC.Base.++ (ByteString -> String
Data.ByteString.Char8.unpack (Bool -> ByteString -> ByteString
Network.HTTP.Types.URI.urlEncode Bool
GHC.Types.True (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
GHC.Base.$ (String -> ByteString
Data.ByteString.Char8.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
GHC.Base.$ Text -> String
forall a. StringifyModel a => a -> String
StripeAPI.Common.stringifyModel Text
item)) String -> String -> String
forall a. [a] -> [a] -> [a]
GHC.Base.++ String
""))) [QueryParameter]
forall a. Monoid a => a
GHC.Base.mempty Maybe DeleteSubscriptionItemsItemRequestBody
body RequestBodyEncoding
StripeAPI.Common.RequestBodyEncodingFormData)

-- | Defines the object schema located at @paths.\/v1\/subscription_items\/{item}.DELETE.requestBody.content.application\/x-www-form-urlencoded.schema@ in the specification.
data DeleteSubscriptionItemsItemRequestBody = DeleteSubscriptionItemsItemRequestBody
  { -- | clear_usage: Delete all usage for the given subscription item. Allowed only when the current plan\'s \`usage_type\` is \`metered\`.
    DeleteSubscriptionItemsItemRequestBody -> Maybe Bool
deleteSubscriptionItemsItemRequestBodyClearUsage :: (GHC.Maybe.Maybe GHC.Types.Bool),
    -- | proration_behavior: Determines how to handle [prorations](https:\/\/stripe.com\/docs\/subscriptions\/billing-cycle\#prorations) when the billing cycle changes (e.g., when switching plans, resetting \`billing_cycle_anchor=now\`, or starting a trial), or if an item\'s \`quantity\` changes. Valid values are \`create_prorations\`, \`none\`, or \`always_invoice\`.
    --
    -- Passing \`create_prorations\` will cause proration invoice items to be created when applicable. These proration items will only be invoiced immediately under [certain conditions](https:\/\/stripe.com\/docs\/subscriptions\/upgrading-downgrading\#immediate-payment). In order to always invoice immediately for prorations, pass \`always_invoice\`.
    --
    -- Prorations can be disabled by passing \`none\`.
    DeleteSubscriptionItemsItemRequestBody
-> Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
deleteSubscriptionItemsItemRequestBodyProrationBehavior :: (GHC.Maybe.Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior'),
    -- | proration_date: If set, the proration will be calculated as though the subscription was updated at the given time. This can be used to apply the same proration that was previewed with the [upcoming invoice](https:\/\/stripe.com\/docs\/api\#retrieve_customer_invoice) endpoint.
    DeleteSubscriptionItemsItemRequestBody -> Maybe Int
deleteSubscriptionItemsItemRequestBodyProrationDate :: (GHC.Maybe.Maybe GHC.Types.Int)
  }
  deriving
    ( Int -> DeleteSubscriptionItemsItemRequestBody -> String -> String
[DeleteSubscriptionItemsItemRequestBody] -> String -> String
DeleteSubscriptionItemsItemRequestBody -> String
(Int -> DeleteSubscriptionItemsItemRequestBody -> String -> String)
-> (DeleteSubscriptionItemsItemRequestBody -> String)
-> ([DeleteSubscriptionItemsItemRequestBody] -> String -> String)
-> Show DeleteSubscriptionItemsItemRequestBody
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DeleteSubscriptionItemsItemRequestBody] -> String -> String
$cshowList :: [DeleteSubscriptionItemsItemRequestBody] -> String -> String
show :: DeleteSubscriptionItemsItemRequestBody -> String
$cshow :: DeleteSubscriptionItemsItemRequestBody -> String
showsPrec :: Int -> DeleteSubscriptionItemsItemRequestBody -> String -> String
$cshowsPrec :: Int -> DeleteSubscriptionItemsItemRequestBody -> String -> String
GHC.Show.Show,
      DeleteSubscriptionItemsItemRequestBody
-> DeleteSubscriptionItemsItemRequestBody -> Bool
(DeleteSubscriptionItemsItemRequestBody
 -> DeleteSubscriptionItemsItemRequestBody -> Bool)
-> (DeleteSubscriptionItemsItemRequestBody
    -> DeleteSubscriptionItemsItemRequestBody -> Bool)
-> Eq DeleteSubscriptionItemsItemRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteSubscriptionItemsItemRequestBody
-> DeleteSubscriptionItemsItemRequestBody -> Bool
$c/= :: DeleteSubscriptionItemsItemRequestBody
-> DeleteSubscriptionItemsItemRequestBody -> Bool
== :: DeleteSubscriptionItemsItemRequestBody
-> DeleteSubscriptionItemsItemRequestBody -> Bool
$c== :: DeleteSubscriptionItemsItemRequestBody
-> DeleteSubscriptionItemsItemRequestBody -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON DeleteSubscriptionItemsItemRequestBody where
  toJSON :: DeleteSubscriptionItemsItemRequestBody -> Value
toJSON DeleteSubscriptionItemsItemRequestBody
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"clear_usage" Text -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= DeleteSubscriptionItemsItemRequestBody -> Maybe Bool
deleteSubscriptionItemsItemRequestBodyClearUsage DeleteSubscriptionItemsItemRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"proration_behavior" Text
-> Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= DeleteSubscriptionItemsItemRequestBody
-> Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
deleteSubscriptionItemsItemRequestBodyProrationBehavior DeleteSubscriptionItemsItemRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"proration_date" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= DeleteSubscriptionItemsItemRequestBody -> Maybe Int
deleteSubscriptionItemsItemRequestBodyProrationDate DeleteSubscriptionItemsItemRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: DeleteSubscriptionItemsItemRequestBody -> Encoding
toEncoding DeleteSubscriptionItemsItemRequestBody
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"clear_usage" Text -> Maybe Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= DeleteSubscriptionItemsItemRequestBody -> Maybe Bool
deleteSubscriptionItemsItemRequestBodyClearUsage DeleteSubscriptionItemsItemRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"proration_behavior" Text
-> Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= DeleteSubscriptionItemsItemRequestBody
-> Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
deleteSubscriptionItemsItemRequestBodyProrationBehavior DeleteSubscriptionItemsItemRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"proration_date" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= DeleteSubscriptionItemsItemRequestBody -> Maybe Int
deleteSubscriptionItemsItemRequestBodyProrationDate DeleteSubscriptionItemsItemRequestBody
obj)))

instance Data.Aeson.Types.FromJSON.FromJSON DeleteSubscriptionItemsItemRequestBody where
  parseJSON :: Value -> Parser DeleteSubscriptionItemsItemRequestBody
parseJSON = String
-> (Object -> Parser DeleteSubscriptionItemsItemRequestBody)
-> Value
-> Parser DeleteSubscriptionItemsItemRequestBody
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"DeleteSubscriptionItemsItemRequestBody" (\Object
obj -> (((Maybe Bool
 -> Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
 -> Maybe Int
 -> DeleteSubscriptionItemsItemRequestBody)
-> Parser
     (Maybe Bool
      -> Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
      -> Maybe Int
      -> DeleteSubscriptionItemsItemRequestBody)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Bool
-> Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
-> Maybe Int
-> DeleteSubscriptionItemsItemRequestBody
DeleteSubscriptionItemsItemRequestBody Parser
  (Maybe Bool
   -> Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
   -> Maybe Int
   -> DeleteSubscriptionItemsItemRequestBody)
-> Parser (Maybe Bool)
-> Parser
     (Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
      -> Maybe Int -> DeleteSubscriptionItemsItemRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"clear_usage")) Parser
  (Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
   -> Maybe Int -> DeleteSubscriptionItemsItemRequestBody)
-> Parser
     (Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior')
-> Parser (Maybe Int -> DeleteSubscriptionItemsItemRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"proration_behavior")) Parser (Maybe Int -> DeleteSubscriptionItemsItemRequestBody)
-> Parser (Maybe Int)
-> Parser DeleteSubscriptionItemsItemRequestBody
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
"proration_date"))

-- | Create a new 'DeleteSubscriptionItemsItemRequestBody' with all required fields.
mkDeleteSubscriptionItemsItemRequestBody :: DeleteSubscriptionItemsItemRequestBody
mkDeleteSubscriptionItemsItemRequestBody :: DeleteSubscriptionItemsItemRequestBody
mkDeleteSubscriptionItemsItemRequestBody =
  DeleteSubscriptionItemsItemRequestBody :: Maybe Bool
-> Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
-> Maybe Int
-> DeleteSubscriptionItemsItemRequestBody
DeleteSubscriptionItemsItemRequestBody
    { deleteSubscriptionItemsItemRequestBodyClearUsage :: Maybe Bool
deleteSubscriptionItemsItemRequestBodyClearUsage = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing,
      deleteSubscriptionItemsItemRequestBodyProrationBehavior :: Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
deleteSubscriptionItemsItemRequestBodyProrationBehavior = Maybe DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
forall a. Maybe a
GHC.Maybe.Nothing,
      deleteSubscriptionItemsItemRequestBodyProrationDate :: Maybe Int
deleteSubscriptionItemsItemRequestBodyProrationDate = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the enum schema located at @paths.\/v1\/subscription_items\/{item}.DELETE.requestBody.content.application\/x-www-form-urlencoded.schema.properties.proration_behavior@ in the specification.
--
-- Determines how to handle [prorations](https:\/\/stripe.com\/docs\/subscriptions\/billing-cycle\#prorations) when the billing cycle changes (e.g., when switching plans, resetting \`billing_cycle_anchor=now\`, or starting a trial), or if an item\'s \`quantity\` changes. Valid values are \`create_prorations\`, \`none\`, or \`always_invoice\`.
--
-- Passing \`create_prorations\` will cause proration invoice items to be created when applicable. These proration items will only be invoiced immediately under [certain conditions](https:\/\/stripe.com\/docs\/subscriptions\/upgrading-downgrading\#immediate-payment). In order to always invoice immediately for prorations, pass \`always_invoice\`.
--
-- Prorations can be disabled by passing \`none\`.
data DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    DeleteSubscriptionItemsItemRequestBodyProrationBehavior'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.
    DeleteSubscriptionItemsItemRequestBodyProrationBehavior'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"always_invoice"@
    DeleteSubscriptionItemsItemRequestBodyProrationBehavior'EnumAlwaysInvoice
  | -- | Represents the JSON value @"create_prorations"@
    DeleteSubscriptionItemsItemRequestBodyProrationBehavior'EnumCreateProrations
  | -- | Represents the JSON value @"none"@
    DeleteSubscriptionItemsItemRequestBodyProrationBehavior'EnumNone
  deriving (Int
-> DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
-> String
-> String
[DeleteSubscriptionItemsItemRequestBodyProrationBehavior']
-> String -> String
DeleteSubscriptionItemsItemRequestBodyProrationBehavior' -> String
(Int
 -> DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
 -> String
 -> String)
-> (DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
    -> String)
-> ([DeleteSubscriptionItemsItemRequestBodyProrationBehavior']
    -> String -> String)
-> Show DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DeleteSubscriptionItemsItemRequestBodyProrationBehavior']
-> String -> String
$cshowList :: [DeleteSubscriptionItemsItemRequestBodyProrationBehavior']
-> String -> String
show :: DeleteSubscriptionItemsItemRequestBodyProrationBehavior' -> String
$cshow :: DeleteSubscriptionItemsItemRequestBodyProrationBehavior' -> String
showsPrec :: Int
-> DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
-> String
-> String
$cshowsPrec :: Int
-> DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
-> String
-> String
GHC.Show.Show, DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
-> DeleteSubscriptionItemsItemRequestBodyProrationBehavior' -> Bool
(DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
 -> DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
 -> Bool)
-> (DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
    -> DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
    -> Bool)
-> Eq DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
-> DeleteSubscriptionItemsItemRequestBodyProrationBehavior' -> Bool
$c/= :: DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
-> DeleteSubscriptionItemsItemRequestBodyProrationBehavior' -> Bool
== :: DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
-> DeleteSubscriptionItemsItemRequestBodyProrationBehavior' -> Bool
$c== :: DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
-> DeleteSubscriptionItemsItemRequestBodyProrationBehavior' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON DeleteSubscriptionItemsItemRequestBodyProrationBehavior' where
  toJSON :: DeleteSubscriptionItemsItemRequestBodyProrationBehavior' -> Value
toJSON (DeleteSubscriptionItemsItemRequestBodyProrationBehavior'Other Value
val) = Value
val
  toJSON (DeleteSubscriptionItemsItemRequestBodyProrationBehavior'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
DeleteSubscriptionItemsItemRequestBodyProrationBehavior'EnumAlwaysInvoice) = Value
"always_invoice"
  toJSON (DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
DeleteSubscriptionItemsItemRequestBodyProrationBehavior'EnumCreateProrations) = Value
"create_prorations"
  toJSON (DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
DeleteSubscriptionItemsItemRequestBodyProrationBehavior'EnumNone) = Value
"none"

instance Data.Aeson.Types.FromJSON.FromJSON DeleteSubscriptionItemsItemRequestBodyProrationBehavior' where
  parseJSON :: Value
-> Parser DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
parseJSON Value
val =
    DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
-> Parser DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
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
"always_invoice" -> DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
DeleteSubscriptionItemsItemRequestBodyProrationBehavior'EnumAlwaysInvoice
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"create_prorations" -> DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
DeleteSubscriptionItemsItemRequestBodyProrationBehavior'EnumCreateProrations
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"none" -> DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
DeleteSubscriptionItemsItemRequestBodyProrationBehavior'EnumNone
            | Bool
GHC.Base.otherwise -> Value -> DeleteSubscriptionItemsItemRequestBodyProrationBehavior'
DeleteSubscriptionItemsItemRequestBodyProrationBehavior'Other Value
val
      )

-- | Represents a response of the operation 'deleteSubscriptionItemsItem'.
--
-- 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), 'DeleteSubscriptionItemsItemResponseError' is used.
data DeleteSubscriptionItemsItemResponse
  = -- | Means either no matching case available or a parse error
    DeleteSubscriptionItemsItemResponseError GHC.Base.String
  | -- | Successful response.
    DeleteSubscriptionItemsItemResponse200 DeletedSubscriptionItem
  | -- | Error response.
    DeleteSubscriptionItemsItemResponseDefault Error
  deriving (Int -> DeleteSubscriptionItemsItemResponse -> String -> String
[DeleteSubscriptionItemsItemResponse] -> String -> String
DeleteSubscriptionItemsItemResponse -> String
(Int -> DeleteSubscriptionItemsItemResponse -> String -> String)
-> (DeleteSubscriptionItemsItemResponse -> String)
-> ([DeleteSubscriptionItemsItemResponse] -> String -> String)
-> Show DeleteSubscriptionItemsItemResponse
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DeleteSubscriptionItemsItemResponse] -> String -> String
$cshowList :: [DeleteSubscriptionItemsItemResponse] -> String -> String
show :: DeleteSubscriptionItemsItemResponse -> String
$cshow :: DeleteSubscriptionItemsItemResponse -> String
showsPrec :: Int -> DeleteSubscriptionItemsItemResponse -> String -> String
$cshowsPrec :: Int -> DeleteSubscriptionItemsItemResponse -> String -> String
GHC.Show.Show, DeleteSubscriptionItemsItemResponse
-> DeleteSubscriptionItemsItemResponse -> Bool
(DeleteSubscriptionItemsItemResponse
 -> DeleteSubscriptionItemsItemResponse -> Bool)
-> (DeleteSubscriptionItemsItemResponse
    -> DeleteSubscriptionItemsItemResponse -> Bool)
-> Eq DeleteSubscriptionItemsItemResponse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteSubscriptionItemsItemResponse
-> DeleteSubscriptionItemsItemResponse -> Bool
$c/= :: DeleteSubscriptionItemsItemResponse
-> DeleteSubscriptionItemsItemResponse -> Bool
== :: DeleteSubscriptionItemsItemResponse
-> DeleteSubscriptionItemsItemResponse -> Bool
$c== :: DeleteSubscriptionItemsItemResponse
-> DeleteSubscriptionItemsItemResponse -> Bool
GHC.Classes.Eq)