{-# 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 postTopups
module StripeAPI.Operations.PostTopups 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/topups
--
-- \<p>Top up the balance of an account\<\/p>
postTopups ::
  forall m.
  StripeAPI.Common.MonadHTTP m =>
  -- | The request body to send
  PostTopupsRequestBody ->
  -- | Monadic computation which returns the result of the operation
  StripeAPI.Common.StripeT m (Network.HTTP.Client.Types.Response PostTopupsResponse)
postTopups :: PostTopupsRequestBody -> StripeT m (Response PostTopupsResponse)
postTopups PostTopupsRequestBody
body =
  (Response ByteString -> Response PostTopupsResponse)
-> StripeT m (Response ByteString)
-> StripeT m (Response PostTopupsResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
    ( \Response ByteString
response_0 ->
        (ByteString -> PostTopupsResponse)
-> Response ByteString -> Response PostTopupsResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
          ( (String -> PostTopupsResponse)
-> (PostTopupsResponse -> PostTopupsResponse)
-> Either String PostTopupsResponse
-> PostTopupsResponse
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
Data.Either.either String -> PostTopupsResponse
PostTopupsResponseError PostTopupsResponse -> PostTopupsResponse
forall a. a -> a
GHC.Base.id
              (Either String PostTopupsResponse -> PostTopupsResponse)
-> (ByteString -> Either String PostTopupsResponse)
-> ByteString
-> PostTopupsResponse
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) ->
                                   Topup -> PostTopupsResponse
PostTopupsResponse200
                                     (Topup -> PostTopupsResponse)
-> Either String Topup -> Either String PostTopupsResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String Topup
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                          Data.Either.Either
                                                            GHC.Base.String
                                                            Topup
                                                      )
                                 | 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 -> PostTopupsResponse
PostTopupsResponseDefault
                                     (Error -> PostTopupsResponse)
-> Either String Error -> Either String PostTopupsResponse
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 PostTopupsResponse
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 PostTopupsRequestBody
-> 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/topups") [QueryParameter]
forall a. Monoid a => a
GHC.Base.mempty (PostTopupsRequestBody -> Maybe PostTopupsRequestBody
forall a. a -> Maybe a
GHC.Maybe.Just PostTopupsRequestBody
body) RequestBodyEncoding
StripeAPI.Common.RequestBodyEncodingFormData)

-- | Defines the object schema located at @paths.\/v1\/topups.POST.requestBody.content.application\/x-www-form-urlencoded.schema@ in the specification.
data PostTopupsRequestBody = PostTopupsRequestBody
  { -- | amount: A positive integer representing how much to transfer.
    PostTopupsRequestBody -> Int
postTopupsRequestBodyAmount :: GHC.Types.Int,
    -- | currency: Three-letter [ISO currency code](https:\/\/www.iso.org\/iso-4217-currency-codes.html), in lowercase. Must be a [supported currency](https:\/\/stripe.com\/docs\/currencies).
    PostTopupsRequestBody -> Text
postTopupsRequestBodyCurrency :: Data.Text.Internal.Text,
    -- | description: An arbitrary string attached to the object. Often useful for displaying to users.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostTopupsRequestBody -> Maybe Text
postTopupsRequestBodyDescription :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | expand: Specifies which fields in the response should be expanded.
    PostTopupsRequestBody -> Maybe [Text]
postTopupsRequestBodyExpand :: (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\`.
    PostTopupsRequestBody
-> Maybe PostTopupsRequestBodyMetadata'Variants
postTopupsRequestBodyMetadata :: (GHC.Maybe.Maybe PostTopupsRequestBodyMetadata'Variants),
    -- | source: The ID of a source to transfer funds from. For most users, this should be left unspecified which will use the bank account that was set up in the dashboard for the specified currency. In test mode, this can be a test bank token (see [Testing Top-ups](https:\/\/stripe.com\/docs\/connect\/testing\#testing-top-ups)).
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostTopupsRequestBody -> Maybe Text
postTopupsRequestBodySource :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | statement_descriptor: Extra information about a top-up for the source\'s bank statement. Limited to 15 ASCII characters.
    --
    -- Constraints:
    --
    -- * Maximum length of 15
    PostTopupsRequestBody -> Maybe Text
postTopupsRequestBodyStatementDescriptor :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | transfer_group: A string that identifies this top-up as part of a group.
    PostTopupsRequestBody -> Maybe Text
postTopupsRequestBodyTransferGroup :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int -> PostTopupsRequestBody -> ShowS
[PostTopupsRequestBody] -> ShowS
PostTopupsRequestBody -> String
(Int -> PostTopupsRequestBody -> ShowS)
-> (PostTopupsRequestBody -> String)
-> ([PostTopupsRequestBody] -> ShowS)
-> Show PostTopupsRequestBody
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PostTopupsRequestBody] -> ShowS
$cshowList :: [PostTopupsRequestBody] -> ShowS
show :: PostTopupsRequestBody -> String
$cshow :: PostTopupsRequestBody -> String
showsPrec :: Int -> PostTopupsRequestBody -> ShowS
$cshowsPrec :: Int -> PostTopupsRequestBody -> ShowS
GHC.Show.Show,
      PostTopupsRequestBody -> PostTopupsRequestBody -> Bool
(PostTopupsRequestBody -> PostTopupsRequestBody -> Bool)
-> (PostTopupsRequestBody -> PostTopupsRequestBody -> Bool)
-> Eq PostTopupsRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostTopupsRequestBody -> PostTopupsRequestBody -> Bool
$c/= :: PostTopupsRequestBody -> PostTopupsRequestBody -> Bool
== :: PostTopupsRequestBody -> PostTopupsRequestBody -> Bool
$c== :: PostTopupsRequestBody -> PostTopupsRequestBody -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostTopupsRequestBody where
  toJSON :: PostTopupsRequestBody -> Value
toJSON PostTopupsRequestBody
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"amount" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostTopupsRequestBody -> Int
postTopupsRequestBodyAmount PostTopupsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"currency" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostTopupsRequestBody -> Text
postTopupsRequestBodyCurrency PostTopupsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"description" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostTopupsRequestBody -> Maybe Text
postTopupsRequestBodyDescription PostTopupsRequestBody
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..= PostTopupsRequestBody -> Maybe [Text]
postTopupsRequestBodyExpand PostTopupsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text -> Maybe PostTopupsRequestBodyMetadata'Variants -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostTopupsRequestBody
-> Maybe PostTopupsRequestBodyMetadata'Variants
postTopupsRequestBodyMetadata PostTopupsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"source" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostTopupsRequestBody -> Maybe Text
postTopupsRequestBodySource PostTopupsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"statement_descriptor" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostTopupsRequestBody -> Maybe Text
postTopupsRequestBodyStatementDescriptor PostTopupsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"transfer_group" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostTopupsRequestBody -> Maybe Text
postTopupsRequestBodyTransferGroup PostTopupsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostTopupsRequestBody -> Encoding
toEncoding PostTopupsRequestBody
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"amount" Text -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostTopupsRequestBody -> Int
postTopupsRequestBodyAmount PostTopupsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"currency" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostTopupsRequestBody -> Text
postTopupsRequestBodyCurrency PostTopupsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"description" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostTopupsRequestBody -> Maybe Text
postTopupsRequestBodyDescription PostTopupsRequestBody
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..= PostTopupsRequestBody -> Maybe [Text]
postTopupsRequestBodyExpand PostTopupsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"metadata" Text -> Maybe PostTopupsRequestBodyMetadata'Variants -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostTopupsRequestBody
-> Maybe PostTopupsRequestBodyMetadata'Variants
postTopupsRequestBodyMetadata PostTopupsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"source" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostTopupsRequestBody -> Maybe Text
postTopupsRequestBodySource PostTopupsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"statement_descriptor" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostTopupsRequestBody -> Maybe Text
postTopupsRequestBodyStatementDescriptor PostTopupsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"transfer_group" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostTopupsRequestBody -> Maybe Text
postTopupsRequestBodyTransferGroup PostTopupsRequestBody
obj))))))))

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

-- | Create a new 'PostTopupsRequestBody' with all required fields.
mkPostTopupsRequestBody ::
  -- | 'postTopupsRequestBodyAmount'
  GHC.Types.Int ->
  -- | 'postTopupsRequestBodyCurrency'
  Data.Text.Internal.Text ->
  PostTopupsRequestBody
mkPostTopupsRequestBody :: Int -> Text -> PostTopupsRequestBody
mkPostTopupsRequestBody Int
postTopupsRequestBodyAmount Text
postTopupsRequestBodyCurrency =
  PostTopupsRequestBody :: Int
-> Text
-> Maybe Text
-> Maybe [Text]
-> Maybe PostTopupsRequestBodyMetadata'Variants
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> PostTopupsRequestBody
PostTopupsRequestBody
    { postTopupsRequestBodyAmount :: Int
postTopupsRequestBodyAmount = Int
postTopupsRequestBodyAmount,
      postTopupsRequestBodyCurrency :: Text
postTopupsRequestBodyCurrency = Text
postTopupsRequestBodyCurrency,
      postTopupsRequestBodyDescription :: Maybe Text
postTopupsRequestBodyDescription = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postTopupsRequestBodyExpand :: Maybe [Text]
postTopupsRequestBodyExpand = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      postTopupsRequestBodyMetadata :: Maybe PostTopupsRequestBodyMetadata'Variants
postTopupsRequestBodyMetadata = Maybe PostTopupsRequestBodyMetadata'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postTopupsRequestBodySource :: Maybe Text
postTopupsRequestBodySource = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postTopupsRequestBodyStatementDescriptor :: Maybe Text
postTopupsRequestBodyStatementDescriptor = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postTopupsRequestBodyTransferGroup :: Maybe Text
postTopupsRequestBodyTransferGroup = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

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

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

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

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