{-# 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 postApplicationFeesFeeRefundsId
module StripeAPI.Operations.PostApplicationFeesFeeRefundsId 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/application_fees/{fee}/refunds/{id}
--
-- \<p>Updates the specified application fee refund by setting the values of the parameters passed. Any parameters not provided will be left unchanged.\<\/p>
--
-- \<p>This request only accepts metadata as an argument.\<\/p>
postApplicationFeesFeeRefundsId ::
  forall m.
  StripeAPI.Common.MonadHTTP m =>
  -- | Contains all available parameters of this operation (query and path parameters)
  PostApplicationFeesFeeRefundsIdParameters ->
  -- | The request body to send
  GHC.Maybe.Maybe PostApplicationFeesFeeRefundsIdRequestBody ->
  -- | Monadic computation which returns the result of the operation
  StripeAPI.Common.StripeT m (Network.HTTP.Client.Types.Response PostApplicationFeesFeeRefundsIdResponse)
postApplicationFeesFeeRefundsId :: PostApplicationFeesFeeRefundsIdParameters
-> Maybe PostApplicationFeesFeeRefundsIdRequestBody
-> StripeT m (Response PostApplicationFeesFeeRefundsIdResponse)
postApplicationFeesFeeRefundsId
  PostApplicationFeesFeeRefundsIdParameters
parameters
  Maybe PostApplicationFeesFeeRefundsIdRequestBody
body =
    (Response ByteString
 -> Response PostApplicationFeesFeeRefundsIdResponse)
-> StripeT m (Response ByteString)
-> StripeT m (Response PostApplicationFeesFeeRefundsIdResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
      ( \Response ByteString
response_0 ->
          (ByteString -> PostApplicationFeesFeeRefundsIdResponse)
-> Response ByteString
-> Response PostApplicationFeesFeeRefundsIdResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
            ( (String -> PostApplicationFeesFeeRefundsIdResponse)
-> (PostApplicationFeesFeeRefundsIdResponse
    -> PostApplicationFeesFeeRefundsIdResponse)
-> Either String PostApplicationFeesFeeRefundsIdResponse
-> PostApplicationFeesFeeRefundsIdResponse
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
Data.Either.either String -> PostApplicationFeesFeeRefundsIdResponse
PostApplicationFeesFeeRefundsIdResponseError PostApplicationFeesFeeRefundsIdResponse
-> PostApplicationFeesFeeRefundsIdResponse
forall a. a -> a
GHC.Base.id
                (Either String PostApplicationFeesFeeRefundsIdResponse
 -> PostApplicationFeesFeeRefundsIdResponse)
-> (ByteString
    -> Either String PostApplicationFeesFeeRefundsIdResponse)
-> ByteString
-> PostApplicationFeesFeeRefundsIdResponse
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) ->
                                     FeeRefund -> PostApplicationFeesFeeRefundsIdResponse
PostApplicationFeesFeeRefundsIdResponse200
                                       (FeeRefund -> PostApplicationFeesFeeRefundsIdResponse)
-> Either String FeeRefund
-> Either String PostApplicationFeesFeeRefundsIdResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String FeeRefund
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                            Data.Either.Either
                                                              GHC.Base.String
                                                              FeeRefund
                                                        )
                                   | 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 -> PostApplicationFeesFeeRefundsIdResponse
PostApplicationFeesFeeRefundsIdResponseDefault
                                       (Error -> PostApplicationFeesFeeRefundsIdResponse)
-> Either String Error
-> Either String PostApplicationFeesFeeRefundsIdResponse
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 PostApplicationFeesFeeRefundsIdResponse
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 PostApplicationFeesFeeRefundsIdRequestBody
-> 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/application_fees/" 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 (PostApplicationFeesFeeRefundsIdParameters -> Text
postApplicationFeesFeeRefundsIdParametersPathFee PostApplicationFeesFeeRefundsIdParameters
parameters))) String -> String -> String
forall a. [a] -> [a] -> [a]
GHC.Base.++ (String
"/refunds/" 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 (PostApplicationFeesFeeRefundsIdParameters -> Text
postApplicationFeesFeeRefundsIdParametersPathId PostApplicationFeesFeeRefundsIdParameters
parameters))) String -> String -> String
forall a. [a] -> [a] -> [a]
GHC.Base.++ String
""))))) [QueryParameter]
forall a. Monoid a => a
GHC.Base.mempty Maybe PostApplicationFeesFeeRefundsIdRequestBody
body RequestBodyEncoding
StripeAPI.Common.RequestBodyEncodingFormData)

-- | Defines the object schema located at @paths.\/v1\/application_fees\/{fee}\/refunds\/{id}.POST.parameters@ in the specification.
data PostApplicationFeesFeeRefundsIdParameters = PostApplicationFeesFeeRefundsIdParameters
  { -- | pathFee: Represents the parameter named \'fee\'
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostApplicationFeesFeeRefundsIdParameters -> Text
postApplicationFeesFeeRefundsIdParametersPathFee :: Data.Text.Internal.Text,
    -- | pathId: Represents the parameter named \'id\'
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostApplicationFeesFeeRefundsIdParameters -> Text
postApplicationFeesFeeRefundsIdParametersPathId :: Data.Text.Internal.Text
  }
  deriving
    ( Int
-> PostApplicationFeesFeeRefundsIdParameters -> String -> String
[PostApplicationFeesFeeRefundsIdParameters] -> String -> String
PostApplicationFeesFeeRefundsIdParameters -> String
(Int
 -> PostApplicationFeesFeeRefundsIdParameters -> String -> String)
-> (PostApplicationFeesFeeRefundsIdParameters -> String)
-> ([PostApplicationFeesFeeRefundsIdParameters]
    -> String -> String)
-> Show PostApplicationFeesFeeRefundsIdParameters
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostApplicationFeesFeeRefundsIdParameters] -> String -> String
$cshowList :: [PostApplicationFeesFeeRefundsIdParameters] -> String -> String
show :: PostApplicationFeesFeeRefundsIdParameters -> String
$cshow :: PostApplicationFeesFeeRefundsIdParameters -> String
showsPrec :: Int
-> PostApplicationFeesFeeRefundsIdParameters -> String -> String
$cshowsPrec :: Int
-> PostApplicationFeesFeeRefundsIdParameters -> String -> String
GHC.Show.Show,
      PostApplicationFeesFeeRefundsIdParameters
-> PostApplicationFeesFeeRefundsIdParameters -> Bool
(PostApplicationFeesFeeRefundsIdParameters
 -> PostApplicationFeesFeeRefundsIdParameters -> Bool)
-> (PostApplicationFeesFeeRefundsIdParameters
    -> PostApplicationFeesFeeRefundsIdParameters -> Bool)
-> Eq PostApplicationFeesFeeRefundsIdParameters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostApplicationFeesFeeRefundsIdParameters
-> PostApplicationFeesFeeRefundsIdParameters -> Bool
$c/= :: PostApplicationFeesFeeRefundsIdParameters
-> PostApplicationFeesFeeRefundsIdParameters -> Bool
== :: PostApplicationFeesFeeRefundsIdParameters
-> PostApplicationFeesFeeRefundsIdParameters -> Bool
$c== :: PostApplicationFeesFeeRefundsIdParameters
-> PostApplicationFeesFeeRefundsIdParameters -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostApplicationFeesFeeRefundsIdParameters where
  toJSON :: PostApplicationFeesFeeRefundsIdParameters -> Value
toJSON PostApplicationFeesFeeRefundsIdParameters
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"pathFee" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostApplicationFeesFeeRefundsIdParameters -> Text
postApplicationFeesFeeRefundsIdParametersPathFee PostApplicationFeesFeeRefundsIdParameters
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"pathId" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostApplicationFeesFeeRefundsIdParameters -> Text
postApplicationFeesFeeRefundsIdParametersPathId PostApplicationFeesFeeRefundsIdParameters
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostApplicationFeesFeeRefundsIdParameters -> Encoding
toEncoding PostApplicationFeesFeeRefundsIdParameters
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"pathFee" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostApplicationFeesFeeRefundsIdParameters -> Text
postApplicationFeesFeeRefundsIdParametersPathFee PostApplicationFeesFeeRefundsIdParameters
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"pathId" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostApplicationFeesFeeRefundsIdParameters -> Text
postApplicationFeesFeeRefundsIdParametersPathId PostApplicationFeesFeeRefundsIdParameters
obj))

instance Data.Aeson.Types.FromJSON.FromJSON PostApplicationFeesFeeRefundsIdParameters where
  parseJSON :: Value -> Parser PostApplicationFeesFeeRefundsIdParameters
parseJSON = String
-> (Object -> Parser PostApplicationFeesFeeRefundsIdParameters)
-> Value
-> Parser PostApplicationFeesFeeRefundsIdParameters
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostApplicationFeesFeeRefundsIdParameters" (\Object
obj -> ((Text -> Text -> PostApplicationFeesFeeRefundsIdParameters)
-> Parser
     (Text -> Text -> PostApplicationFeesFeeRefundsIdParameters)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Text -> Text -> PostApplicationFeesFeeRefundsIdParameters
PostApplicationFeesFeeRefundsIdParameters Parser (Text -> Text -> PostApplicationFeesFeeRefundsIdParameters)
-> Parser Text
-> Parser (Text -> PostApplicationFeesFeeRefundsIdParameters)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"pathFee")) Parser (Text -> PostApplicationFeesFeeRefundsIdParameters)
-> Parser Text -> Parser PostApplicationFeesFeeRefundsIdParameters
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"pathId"))

-- | Create a new 'PostApplicationFeesFeeRefundsIdParameters' with all required fields.
mkPostApplicationFeesFeeRefundsIdParameters ::
  -- | 'postApplicationFeesFeeRefundsIdParametersPathFee'
  Data.Text.Internal.Text ->
  -- | 'postApplicationFeesFeeRefundsIdParametersPathId'
  Data.Text.Internal.Text ->
  PostApplicationFeesFeeRefundsIdParameters
mkPostApplicationFeesFeeRefundsIdParameters :: Text -> Text -> PostApplicationFeesFeeRefundsIdParameters
mkPostApplicationFeesFeeRefundsIdParameters Text
postApplicationFeesFeeRefundsIdParametersPathFee Text
postApplicationFeesFeeRefundsIdParametersPathId =
  PostApplicationFeesFeeRefundsIdParameters :: Text -> Text -> PostApplicationFeesFeeRefundsIdParameters
PostApplicationFeesFeeRefundsIdParameters
    { postApplicationFeesFeeRefundsIdParametersPathFee :: Text
postApplicationFeesFeeRefundsIdParametersPathFee = Text
postApplicationFeesFeeRefundsIdParametersPathFee,
      postApplicationFeesFeeRefundsIdParametersPathId :: Text
postApplicationFeesFeeRefundsIdParametersPathId = Text
postApplicationFeesFeeRefundsIdParametersPathId
    }

-- | Defines the object schema located at @paths.\/v1\/application_fees\/{fee}\/refunds\/{id}.POST.requestBody.content.application\/x-www-form-urlencoded.schema@ in the specification.
data PostApplicationFeesFeeRefundsIdRequestBody = PostApplicationFeesFeeRefundsIdRequestBody
  { -- | expand: Specifies which fields in the response should be expanded.
    PostApplicationFeesFeeRefundsIdRequestBody -> Maybe [Text]
postApplicationFeesFeeRefundsIdRequestBodyExpand :: (GHC.Maybe.Maybe ([Data.Text.Internal.Text])),
    -- | 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\`.
    PostApplicationFeesFeeRefundsIdRequestBody
-> Maybe
     PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
postApplicationFeesFeeRefundsIdRequestBodyMetadata :: (GHC.Maybe.Maybe PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants)
  }
  deriving
    ( Int
-> PostApplicationFeesFeeRefundsIdRequestBody -> String -> String
[PostApplicationFeesFeeRefundsIdRequestBody] -> String -> String
PostApplicationFeesFeeRefundsIdRequestBody -> String
(Int
 -> PostApplicationFeesFeeRefundsIdRequestBody -> String -> String)
-> (PostApplicationFeesFeeRefundsIdRequestBody -> String)
-> ([PostApplicationFeesFeeRefundsIdRequestBody]
    -> String -> String)
-> Show PostApplicationFeesFeeRefundsIdRequestBody
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostApplicationFeesFeeRefundsIdRequestBody] -> String -> String
$cshowList :: [PostApplicationFeesFeeRefundsIdRequestBody] -> String -> String
show :: PostApplicationFeesFeeRefundsIdRequestBody -> String
$cshow :: PostApplicationFeesFeeRefundsIdRequestBody -> String
showsPrec :: Int
-> PostApplicationFeesFeeRefundsIdRequestBody -> String -> String
$cshowsPrec :: Int
-> PostApplicationFeesFeeRefundsIdRequestBody -> String -> String
GHC.Show.Show,
      PostApplicationFeesFeeRefundsIdRequestBody
-> PostApplicationFeesFeeRefundsIdRequestBody -> Bool
(PostApplicationFeesFeeRefundsIdRequestBody
 -> PostApplicationFeesFeeRefundsIdRequestBody -> Bool)
-> (PostApplicationFeesFeeRefundsIdRequestBody
    -> PostApplicationFeesFeeRefundsIdRequestBody -> Bool)
-> Eq PostApplicationFeesFeeRefundsIdRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostApplicationFeesFeeRefundsIdRequestBody
-> PostApplicationFeesFeeRefundsIdRequestBody -> Bool
$c/= :: PostApplicationFeesFeeRefundsIdRequestBody
-> PostApplicationFeesFeeRefundsIdRequestBody -> Bool
== :: PostApplicationFeesFeeRefundsIdRequestBody
-> PostApplicationFeesFeeRefundsIdRequestBody -> Bool
$c== :: PostApplicationFeesFeeRefundsIdRequestBody
-> PostApplicationFeesFeeRefundsIdRequestBody -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostApplicationFeesFeeRefundsIdRequestBody where
  toJSON :: PostApplicationFeesFeeRefundsIdRequestBody -> Value
toJSON PostApplicationFeesFeeRefundsIdRequestBody
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"expand" Text -> Maybe [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostApplicationFeesFeeRefundsIdRequestBody -> Maybe [Text]
postApplicationFeesFeeRefundsIdRequestBodyExpand PostApplicationFeesFeeRefundsIdRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text
-> Maybe
     PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostApplicationFeesFeeRefundsIdRequestBody
-> Maybe
     PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
postApplicationFeesFeeRefundsIdRequestBodyMetadata PostApplicationFeesFeeRefundsIdRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostApplicationFeesFeeRefundsIdRequestBody -> Encoding
toEncoding PostApplicationFeesFeeRefundsIdRequestBody
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"expand" Text -> Maybe [Text] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostApplicationFeesFeeRefundsIdRequestBody -> Maybe [Text]
postApplicationFeesFeeRefundsIdRequestBodyExpand PostApplicationFeesFeeRefundsIdRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"metadata" Text
-> Maybe
     PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostApplicationFeesFeeRefundsIdRequestBody
-> Maybe
     PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
postApplicationFeesFeeRefundsIdRequestBodyMetadata PostApplicationFeesFeeRefundsIdRequestBody
obj))

instance Data.Aeson.Types.FromJSON.FromJSON PostApplicationFeesFeeRefundsIdRequestBody where
  parseJSON :: Value -> Parser PostApplicationFeesFeeRefundsIdRequestBody
parseJSON = String
-> (Object -> Parser PostApplicationFeesFeeRefundsIdRequestBody)
-> Value
-> Parser PostApplicationFeesFeeRefundsIdRequestBody
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostApplicationFeesFeeRefundsIdRequestBody" (\Object
obj -> ((Maybe [Text]
 -> Maybe
      PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
 -> PostApplicationFeesFeeRefundsIdRequestBody)
-> Parser
     (Maybe [Text]
      -> Maybe
           PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
      -> PostApplicationFeesFeeRefundsIdRequestBody)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe [Text]
-> Maybe
     PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> PostApplicationFeesFeeRefundsIdRequestBody
PostApplicationFeesFeeRefundsIdRequestBody Parser
  (Maybe [Text]
   -> Maybe
        PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
   -> PostApplicationFeesFeeRefundsIdRequestBody)
-> Parser (Maybe [Text])
-> Parser
     (Maybe PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
      -> PostApplicationFeesFeeRefundsIdRequestBody)
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 PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
   -> PostApplicationFeesFeeRefundsIdRequestBody)
-> Parser
     (Maybe PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants)
-> Parser PostApplicationFeesFeeRefundsIdRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"metadata"))

-- | Create a new 'PostApplicationFeesFeeRefundsIdRequestBody' with all required fields.
mkPostApplicationFeesFeeRefundsIdRequestBody :: PostApplicationFeesFeeRefundsIdRequestBody
mkPostApplicationFeesFeeRefundsIdRequestBody :: PostApplicationFeesFeeRefundsIdRequestBody
mkPostApplicationFeesFeeRefundsIdRequestBody =
  PostApplicationFeesFeeRefundsIdRequestBody :: Maybe [Text]
-> Maybe
     PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> PostApplicationFeesFeeRefundsIdRequestBody
PostApplicationFeesFeeRefundsIdRequestBody
    { postApplicationFeesFeeRefundsIdRequestBodyExpand :: Maybe [Text]
postApplicationFeesFeeRefundsIdRequestBodyExpand = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      postApplicationFeesFeeRefundsIdRequestBodyMetadata :: Maybe PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
postApplicationFeesFeeRefundsIdRequestBodyMetadata = Maybe PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the oneOf schema located at @paths.\/v1\/application_fees\/{fee}\/refunds\/{id}.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 PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
  = -- | Represents the JSON value @""@
    PostApplicationFeesFeeRefundsIdRequestBodyMetadata'EmptyString
  | PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Object Data.Aeson.Types.Internal.Object
  deriving (Int
-> PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> String
-> String
[PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants]
-> String -> String
PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> String
(Int
 -> PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
 -> String
 -> String)
-> (PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
    -> String)
-> ([PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants]
    -> String -> String)
-> Show PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants]
-> String -> String
$cshowList :: [PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants]
-> String -> String
show :: PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> String
$cshow :: PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> String
showsPrec :: Int
-> PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> String
-> String
$cshowsPrec :: Int
-> PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> String
-> String
GHC.Show.Show, PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> Bool
(PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
 -> PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
 -> Bool)
-> (PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
    -> PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
    -> Bool)
-> Eq PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> Bool
$c/= :: PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> Bool
== :: PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> Bool
$c== :: PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> PostApplicationFeesFeeRefundsIdRequestBodyMetadata'Variants
-> Bool
GHC.Classes.Eq)

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

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

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