{-# 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 postIssuingAuthorizationsAuthorizationApprove
module StripeAPI.Operations.PostIssuingAuthorizationsAuthorizationApprove 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/issuing/authorizations/{authorization}/approve
--
-- \<p>Approves a pending Issuing \<code>Authorization\<\/code> object. This request should be made within the timeout window of the \<a href=\"\/docs\/issuing\/controls\/real-time-authorizations\">real-time authorization\<\/a> flow.\<\/p>
postIssuingAuthorizationsAuthorizationApprove ::
  forall m.
  StripeAPI.Common.MonadHTTP m =>
  -- | authorization | Constraints: Maximum length of 5000
  Data.Text.Internal.Text ->
  -- | The request body to send
  GHC.Maybe.Maybe PostIssuingAuthorizationsAuthorizationApproveRequestBody ->
  -- | Monadic computation which returns the result of the operation
  StripeAPI.Common.ClientT m (Network.HTTP.Client.Types.Response PostIssuingAuthorizationsAuthorizationApproveResponse)
postIssuingAuthorizationsAuthorizationApprove :: Text
-> Maybe PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> ClientT
     m (Response PostIssuingAuthorizationsAuthorizationApproveResponse)
postIssuingAuthorizationsAuthorizationApprove
  Text
authorization
  Maybe PostIssuingAuthorizationsAuthorizationApproveRequestBody
body =
    (Response ByteString
 -> Response PostIssuingAuthorizationsAuthorizationApproveResponse)
-> ClientT m (Response ByteString)
-> ClientT
     m (Response PostIssuingAuthorizationsAuthorizationApproveResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
      ( \Response ByteString
response_0 ->
          (ByteString
 -> PostIssuingAuthorizationsAuthorizationApproveResponse)
-> Response ByteString
-> Response PostIssuingAuthorizationsAuthorizationApproveResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
            ( (String -> PostIssuingAuthorizationsAuthorizationApproveResponse)
-> (PostIssuingAuthorizationsAuthorizationApproveResponse
    -> PostIssuingAuthorizationsAuthorizationApproveResponse)
-> Either
     String PostIssuingAuthorizationsAuthorizationApproveResponse
-> PostIssuingAuthorizationsAuthorizationApproveResponse
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
Data.Either.either String -> PostIssuingAuthorizationsAuthorizationApproveResponse
PostIssuingAuthorizationsAuthorizationApproveResponseError PostIssuingAuthorizationsAuthorizationApproveResponse
-> PostIssuingAuthorizationsAuthorizationApproveResponse
forall a. a -> a
GHC.Base.id
                (Either
   String PostIssuingAuthorizationsAuthorizationApproveResponse
 -> PostIssuingAuthorizationsAuthorizationApproveResponse)
-> (ByteString
    -> Either
         String PostIssuingAuthorizationsAuthorizationApproveResponse)
-> ByteString
-> PostIssuingAuthorizationsAuthorizationApproveResponse
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) ->
                                     Issuing'authorization
-> PostIssuingAuthorizationsAuthorizationApproveResponse
PostIssuingAuthorizationsAuthorizationApproveResponse200
                                       (Issuing'authorization
 -> PostIssuingAuthorizationsAuthorizationApproveResponse)
-> Either String Issuing'authorization
-> Either
     String PostIssuingAuthorizationsAuthorizationApproveResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String Issuing'authorization
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                            Data.Either.Either
                                                              GHC.Base.String
                                                              Issuing'authorization
                                                        )
                                   | 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 -> PostIssuingAuthorizationsAuthorizationApproveResponse
PostIssuingAuthorizationsAuthorizationApproveResponseDefault
                                       (Error -> PostIssuingAuthorizationsAuthorizationApproveResponse)
-> Either String Error
-> Either
     String PostIssuingAuthorizationsAuthorizationApproveResponse
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 PostIssuingAuthorizationsAuthorizationApproveResponse
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 PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> RequestBodyEncoding
-> ClientT m (Response ByteString)
forall (m :: * -> *) body.
(MonadHTTP m, ToJSON body) =>
Text
-> Text
-> [QueryParameter]
-> Maybe body
-> RequestBodyEncoding
-> ClientT 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/issuing/authorizations/" 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
authorization)) String -> String -> String
forall a. [a] -> [a] -> [a]
GHC.Base.++ String
"/approve"))) [QueryParameter]
forall a. Monoid a => a
GHC.Base.mempty Maybe PostIssuingAuthorizationsAuthorizationApproveRequestBody
body RequestBodyEncoding
StripeAPI.Common.RequestBodyEncodingFormData)

-- | Defines the object schema located at @paths.\/v1\/issuing\/authorizations\/{authorization}\/approve.POST.requestBody.content.application\/x-www-form-urlencoded.schema@ in the specification.
data PostIssuingAuthorizationsAuthorizationApproveRequestBody = PostIssuingAuthorizationsAuthorizationApproveRequestBody
  { -- | amount: If the authorization\'s \`pending_request.is_amount_controllable\` property is \`true\`, you may provide this value to control how much to hold for the authorization. Must be positive (use [\`decline\`](https:\/\/stripe.com\/docs\/api\/issuing\/authorizations\/decline) to decline an authorization request).
    PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> Maybe Int
postIssuingAuthorizationsAuthorizationApproveRequestBodyAmount :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | expand: Specifies which fields in the response should be expanded.
    PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> Maybe [Text]
postIssuingAuthorizationsAuthorizationApproveRequestBodyExpand :: (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\`.
    PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> Maybe
     PostIssuingAuthorizationsAuthorizationApproveRequestBodyMetadata'Variants
postIssuingAuthorizationsAuthorizationApproveRequestBodyMetadata :: (GHC.Maybe.Maybe PostIssuingAuthorizationsAuthorizationApproveRequestBodyMetadata'Variants)
  }
  deriving
    ( Int
-> PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> String
-> String
[PostIssuingAuthorizationsAuthorizationApproveRequestBody]
-> String -> String
PostIssuingAuthorizationsAuthorizationApproveRequestBody -> String
(Int
 -> PostIssuingAuthorizationsAuthorizationApproveRequestBody
 -> String
 -> String)
-> (PostIssuingAuthorizationsAuthorizationApproveRequestBody
    -> String)
-> ([PostIssuingAuthorizationsAuthorizationApproveRequestBody]
    -> String -> String)
-> Show PostIssuingAuthorizationsAuthorizationApproveRequestBody
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostIssuingAuthorizationsAuthorizationApproveRequestBody]
-> String -> String
$cshowList :: [PostIssuingAuthorizationsAuthorizationApproveRequestBody]
-> String -> String
show :: PostIssuingAuthorizationsAuthorizationApproveRequestBody -> String
$cshow :: PostIssuingAuthorizationsAuthorizationApproveRequestBody -> String
showsPrec :: Int
-> PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> String
-> String
$cshowsPrec :: Int
-> PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> String
-> String
GHC.Show.Show,
      PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> PostIssuingAuthorizationsAuthorizationApproveRequestBody -> Bool
(PostIssuingAuthorizationsAuthorizationApproveRequestBody
 -> PostIssuingAuthorizationsAuthorizationApproveRequestBody
 -> Bool)
-> (PostIssuingAuthorizationsAuthorizationApproveRequestBody
    -> PostIssuingAuthorizationsAuthorizationApproveRequestBody
    -> Bool)
-> Eq PostIssuingAuthorizationsAuthorizationApproveRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> PostIssuingAuthorizationsAuthorizationApproveRequestBody -> Bool
$c/= :: PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> PostIssuingAuthorizationsAuthorizationApproveRequestBody -> Bool
== :: PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> PostIssuingAuthorizationsAuthorizationApproveRequestBody -> Bool
$c== :: PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> PostIssuingAuthorizationsAuthorizationApproveRequestBody -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostIssuingAuthorizationsAuthorizationApproveRequestBody where
  toJSON :: PostIssuingAuthorizationsAuthorizationApproveRequestBody -> Value
toJSON PostIssuingAuthorizationsAuthorizationApproveRequestBody
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"amount" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> Maybe Int
postIssuingAuthorizationsAuthorizationApproveRequestBodyAmount PostIssuingAuthorizationsAuthorizationApproveRequestBody
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..= PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> Maybe [Text]
postIssuingAuthorizationsAuthorizationApproveRequestBodyExpand PostIssuingAuthorizationsAuthorizationApproveRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text
-> Maybe
     PostIssuingAuthorizationsAuthorizationApproveRequestBodyMetadata'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> Maybe
     PostIssuingAuthorizationsAuthorizationApproveRequestBodyMetadata'Variants
postIssuingAuthorizationsAuthorizationApproveRequestBodyMetadata PostIssuingAuthorizationsAuthorizationApproveRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> Encoding
toEncoding PostIssuingAuthorizationsAuthorizationApproveRequestBody
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"amount" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> Maybe Int
postIssuingAuthorizationsAuthorizationApproveRequestBodyAmount PostIssuingAuthorizationsAuthorizationApproveRequestBody
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..= PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> Maybe [Text]
postIssuingAuthorizationsAuthorizationApproveRequestBodyExpand PostIssuingAuthorizationsAuthorizationApproveRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"metadata" Text
-> Maybe
     PostIssuingAuthorizationsAuthorizationApproveRequestBodyMetadata'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostIssuingAuthorizationsAuthorizationApproveRequestBody
-> Maybe
     PostIssuingAuthorizationsAuthorizationApproveRequestBodyMetadata'Variants
postIssuingAuthorizationsAuthorizationApproveRequestBodyMetadata PostIssuingAuthorizationsAuthorizationApproveRequestBody
obj)))

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

-- | Create a new 'PostIssuingAuthorizationsAuthorizationApproveRequestBody' with all required fields.
mkPostIssuingAuthorizationsAuthorizationApproveRequestBody :: PostIssuingAuthorizationsAuthorizationApproveRequestBody
mkPostIssuingAuthorizationsAuthorizationApproveRequestBody :: PostIssuingAuthorizationsAuthorizationApproveRequestBody
mkPostIssuingAuthorizationsAuthorizationApproveRequestBody =
  PostIssuingAuthorizationsAuthorizationApproveRequestBody :: Maybe Int
-> Maybe [Text]
-> Maybe
     PostIssuingAuthorizationsAuthorizationApproveRequestBodyMetadata'Variants
-> PostIssuingAuthorizationsAuthorizationApproveRequestBody
PostIssuingAuthorizationsAuthorizationApproveRequestBody
    { postIssuingAuthorizationsAuthorizationApproveRequestBodyAmount :: Maybe Int
postIssuingAuthorizationsAuthorizationApproveRequestBodyAmount = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postIssuingAuthorizationsAuthorizationApproveRequestBodyExpand :: Maybe [Text]
postIssuingAuthorizationsAuthorizationApproveRequestBodyExpand = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      postIssuingAuthorizationsAuthorizationApproveRequestBodyMetadata :: Maybe
  PostIssuingAuthorizationsAuthorizationApproveRequestBodyMetadata'Variants
postIssuingAuthorizationsAuthorizationApproveRequestBodyMetadata = Maybe
  PostIssuingAuthorizationsAuthorizationApproveRequestBodyMetadata'Variants
forall a. Maybe a
GHC.Maybe.Nothing
    }

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

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

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

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