{-# 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 postCustomersCustomerBankAccounts
module StripeAPI.Operations.PostCustomersCustomerBankAccounts 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/customers/{customer}/bank_accounts
--
-- \<p>When you create a new credit card, you must specify a customer or recipient on which to create it.\<\/p>
--
-- \<p>If the card’s owner has no default card, then the new card will become the default.
-- However, if the owner already has a default, then it will not change.
-- To change the default, you should \<a href=\"\/docs\/api\#update_customer\">update the customer\<\/a> to have a new \<code>default_source\<\/code>.\<\/p>
postCustomersCustomerBankAccounts ::
  forall m.
  StripeAPI.Common.MonadHTTP m =>
  -- | customer | Constraints: Maximum length of 5000
  Data.Text.Internal.Text ->
  -- | The request body to send
  GHC.Maybe.Maybe PostCustomersCustomerBankAccountsRequestBody ->
  -- | Monadic computation which returns the result of the operation
  StripeAPI.Common.ClientT m (Network.HTTP.Client.Types.Response PostCustomersCustomerBankAccountsResponse)
postCustomersCustomerBankAccounts :: Text
-> Maybe PostCustomersCustomerBankAccountsRequestBody
-> ClientT m (Response PostCustomersCustomerBankAccountsResponse)
postCustomersCustomerBankAccounts
  Text
customer
  Maybe PostCustomersCustomerBankAccountsRequestBody
body =
    (Response ByteString
 -> Response PostCustomersCustomerBankAccountsResponse)
-> ClientT m (Response ByteString)
-> ClientT m (Response PostCustomersCustomerBankAccountsResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
      ( \Response ByteString
response_0 ->
          (ByteString -> PostCustomersCustomerBankAccountsResponse)
-> Response ByteString
-> Response PostCustomersCustomerBankAccountsResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
            ( (String -> PostCustomersCustomerBankAccountsResponse)
-> (PostCustomersCustomerBankAccountsResponse
    -> PostCustomersCustomerBankAccountsResponse)
-> Either String PostCustomersCustomerBankAccountsResponse
-> PostCustomersCustomerBankAccountsResponse
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
Data.Either.either String -> PostCustomersCustomerBankAccountsResponse
PostCustomersCustomerBankAccountsResponseError PostCustomersCustomerBankAccountsResponse
-> PostCustomersCustomerBankAccountsResponse
forall a. a -> a
GHC.Base.id
                (Either String PostCustomersCustomerBankAccountsResponse
 -> PostCustomersCustomerBankAccountsResponse)
-> (ByteString
    -> Either String PostCustomersCustomerBankAccountsResponse)
-> ByteString
-> PostCustomersCustomerBankAccountsResponse
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) ->
                                     PaymentSource -> PostCustomersCustomerBankAccountsResponse
PostCustomersCustomerBankAccountsResponse200
                                       (PaymentSource -> PostCustomersCustomerBankAccountsResponse)
-> Either String PaymentSource
-> Either String PostCustomersCustomerBankAccountsResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String PaymentSource
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                            Data.Either.Either
                                                              GHC.Base.String
                                                              PaymentSource
                                                        )
                                   | 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 -> PostCustomersCustomerBankAccountsResponse
PostCustomersCustomerBankAccountsResponseDefault
                                       (Error -> PostCustomersCustomerBankAccountsResponse)
-> Either String Error
-> Either String PostCustomersCustomerBankAccountsResponse
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 PostCustomersCustomerBankAccountsResponse
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 PostCustomersCustomerBankAccountsRequestBody
-> 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/customers/" 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
customer)) String -> String -> String
forall a. [a] -> [a] -> [a]
GHC.Base.++ String
"/bank_accounts"))) [QueryParameter]
forall a. Monoid a => a
GHC.Base.mempty Maybe PostCustomersCustomerBankAccountsRequestBody
body RequestBodyEncoding
StripeAPI.Common.RequestBodyEncodingFormData)

-- | Defines the object schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts.POST.requestBody.content.application\/x-www-form-urlencoded.schema@ in the specification.
data PostCustomersCustomerBankAccountsRequestBody = PostCustomersCustomerBankAccountsRequestBody
  { -- | alipay_account: A token returned by [Stripe.js](https:\/\/stripe.com\/docs\/stripe.js) representing the user’s Alipay account details.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBody -> Maybe Text
postCustomersCustomerBankAccountsRequestBodyAlipayAccount :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | bank_account: Either a token, like the ones returned by [Stripe.js](https:\/\/stripe.com\/docs\/stripe.js), or a dictionary containing a user\'s bank account details.
    PostCustomersCustomerBankAccountsRequestBody
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
postCustomersCustomerBankAccountsRequestBodyBankAccount :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants),
    -- | card: A token, like the ones returned by [Stripe.js](https:\/\/stripe.com\/docs\/stripe.js).
    PostCustomersCustomerBankAccountsRequestBody
-> Maybe PostCustomersCustomerBankAccountsRequestBodyCard'Variants
postCustomersCustomerBankAccountsRequestBodyCard :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsRequestBodyCard'Variants),
    -- | expand: Specifies which fields in the response should be expanded.
    PostCustomersCustomerBankAccountsRequestBody -> Maybe [Text]
postCustomersCustomerBankAccountsRequestBodyExpand :: (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\`.
    PostCustomersCustomerBankAccountsRequestBody -> Maybe Object
postCustomersCustomerBankAccountsRequestBodyMetadata :: (GHC.Maybe.Maybe Data.Aeson.Types.Internal.Object),
    -- | source: Please refer to full [documentation](https:\/\/stripe.com\/docs\/api) instead.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBody -> Maybe Text
postCustomersCustomerBankAccountsRequestBodySource :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int
-> PostCustomersCustomerBankAccountsRequestBody -> String -> String
[PostCustomersCustomerBankAccountsRequestBody] -> String -> String
PostCustomersCustomerBankAccountsRequestBody -> String
(Int
 -> PostCustomersCustomerBankAccountsRequestBody
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsRequestBody -> String)
-> ([PostCustomersCustomerBankAccountsRequestBody]
    -> String -> String)
-> Show PostCustomersCustomerBankAccountsRequestBody
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsRequestBody] -> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsRequestBody] -> String -> String
show :: PostCustomersCustomerBankAccountsRequestBody -> String
$cshow :: PostCustomersCustomerBankAccountsRequestBody -> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBody -> String -> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBody -> String -> String
GHC.Show.Show,
      PostCustomersCustomerBankAccountsRequestBody
-> PostCustomersCustomerBankAccountsRequestBody -> Bool
(PostCustomersCustomerBankAccountsRequestBody
 -> PostCustomersCustomerBankAccountsRequestBody -> Bool)
-> (PostCustomersCustomerBankAccountsRequestBody
    -> PostCustomersCustomerBankAccountsRequestBody -> Bool)
-> Eq PostCustomersCustomerBankAccountsRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsRequestBody
-> PostCustomersCustomerBankAccountsRequestBody -> Bool
$c/= :: PostCustomersCustomerBankAccountsRequestBody
-> PostCustomersCustomerBankAccountsRequestBody -> Bool
== :: PostCustomersCustomerBankAccountsRequestBody
-> PostCustomersCustomerBankAccountsRequestBody -> Bool
$c== :: PostCustomersCustomerBankAccountsRequestBody
-> PostCustomersCustomerBankAccountsRequestBody -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsRequestBody where
  toJSON :: PostCustomersCustomerBankAccountsRequestBody -> Value
toJSON PostCustomersCustomerBankAccountsRequestBody
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"alipay_account" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBody -> Maybe Text
postCustomersCustomerBankAccountsRequestBodyAlipayAccount PostCustomersCustomerBankAccountsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"bank_account" Text
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBody
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
postCustomersCustomerBankAccountsRequestBodyBankAccount PostCustomersCustomerBankAccountsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"card" Text
-> Maybe PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBody
-> Maybe PostCustomersCustomerBankAccountsRequestBodyCard'Variants
postCustomersCustomerBankAccountsRequestBodyCard PostCustomersCustomerBankAccountsRequestBody
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..= PostCustomersCustomerBankAccountsRequestBody -> Maybe [Text]
postCustomersCustomerBankAccountsRequestBodyExpand PostCustomersCustomerBankAccountsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text -> Maybe Object -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBody -> Maybe Object
postCustomersCustomerBankAccountsRequestBodyMetadata PostCustomersCustomerBankAccountsRequestBody
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..= PostCustomersCustomerBankAccountsRequestBody -> Maybe Text
postCustomersCustomerBankAccountsRequestBodySource PostCustomersCustomerBankAccountsRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerBankAccountsRequestBody -> Encoding
toEncoding PostCustomersCustomerBankAccountsRequestBody
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"alipay_account" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBody -> Maybe Text
postCustomersCustomerBankAccountsRequestBodyAlipayAccount PostCustomersCustomerBankAccountsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"bank_account" Text
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBody
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
postCustomersCustomerBankAccountsRequestBodyBankAccount PostCustomersCustomerBankAccountsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"card" Text
-> Maybe PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBody
-> Maybe PostCustomersCustomerBankAccountsRequestBodyCard'Variants
postCustomersCustomerBankAccountsRequestBodyCard PostCustomersCustomerBankAccountsRequestBody
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..= PostCustomersCustomerBankAccountsRequestBody -> Maybe [Text]
postCustomersCustomerBankAccountsRequestBodyExpand PostCustomersCustomerBankAccountsRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"metadata" Text -> Maybe Object -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBody -> Maybe Object
postCustomersCustomerBankAccountsRequestBodyMetadata PostCustomersCustomerBankAccountsRequestBody
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..= PostCustomersCustomerBankAccountsRequestBody -> Maybe Text
postCustomersCustomerBankAccountsRequestBodySource PostCustomersCustomerBankAccountsRequestBody
obj))))))

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

-- | Create a new 'PostCustomersCustomerBankAccountsRequestBody' with all required fields.
mkPostCustomersCustomerBankAccountsRequestBody :: PostCustomersCustomerBankAccountsRequestBody
mkPostCustomersCustomerBankAccountsRequestBody :: PostCustomersCustomerBankAccountsRequestBody
mkPostCustomersCustomerBankAccountsRequestBody =
  PostCustomersCustomerBankAccountsRequestBody :: Maybe Text
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> Maybe PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> Maybe [Text]
-> Maybe Object
-> Maybe Text
-> PostCustomersCustomerBankAccountsRequestBody
PostCustomersCustomerBankAccountsRequestBody
    { postCustomersCustomerBankAccountsRequestBodyAlipayAccount :: Maybe Text
postCustomersCustomerBankAccountsRequestBodyAlipayAccount = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyBankAccount :: Maybe
  PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
postCustomersCustomerBankAccountsRequestBodyBankAccount = Maybe
  PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyCard :: Maybe PostCustomersCustomerBankAccountsRequestBodyCard'Variants
postCustomersCustomerBankAccountsRequestBodyCard = Maybe PostCustomersCustomerBankAccountsRequestBodyCard'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyExpand :: Maybe [Text]
postCustomersCustomerBankAccountsRequestBodyExpand = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyMetadata :: Maybe Object
postCustomersCustomerBankAccountsRequestBodyMetadata = Maybe Object
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodySource :: Maybe Text
postCustomersCustomerBankAccountsRequestBodySource = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.bank_account.anyOf@ in the specification.
data PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1 = PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
  { -- | account_holder_name
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderName :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | account_holder_type
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'),
    -- | account_number
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountNumber :: Data.Text.Internal.Text,
    -- | country
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Country :: Data.Text.Internal.Text,
    -- | currency
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Currency :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | object
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'),
    -- | routing_number
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1RoutingNumber :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> String
-> String
[PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1]
-> String -> String
PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> String
(Int
 -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
    -> String)
-> ([PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1]
    -> String -> String)
-> Show
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1]
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1]
-> String -> String
show :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> String
$cshow :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Bool
(PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
 -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
 -> Bool)
-> (PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
    -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
    -> Bool)
-> Eq
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Bool
$c/= :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Bool
== :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Bool
$c== :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1 where
  toJSON :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Value
toJSON PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"account_holder_name" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderName PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"account_holder_type" Text
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"account_number" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountNumber PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"country" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Country PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"currency" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Currency PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"object" Text
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"routing_number" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1RoutingNumber PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Encoding
toEncoding PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"account_holder_name" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderName PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"account_holder_type" Text
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"account_number" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountNumber PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"country" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Country PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"currency" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Currency PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"object" Text
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"routing_number" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1RoutingNumber PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
obj)))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1 where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
parseJSON = String
-> (Object
    -> Parser
         PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
-> Value
-> Parser
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1" (\Object
obj -> (((((((Maybe Text
 -> Maybe
      PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
 -> Text
 -> Text
 -> Maybe Text
 -> Maybe
      PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
 -> Maybe Text
 -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
-> Parser
     (Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
      -> Text
      -> Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> Text
-> Text
-> Maybe Text
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> Maybe Text
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1 Parser
  (Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
   -> Text
   -> Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
-> Parser (Maybe Text)
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
      -> Text
      -> Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
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
"account_holder_name")) Parser
  (Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
   -> Text
   -> Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType')
-> Parser
     (Text
      -> Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"account_holder_type")) Parser
  (Text
   -> Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
-> Parser Text
-> Parser
     (Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
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
"account_number")) Parser
  (Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
-> Parser Text
-> Parser
     (Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
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
"country")) Parser
  (Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
-> Parser (Maybe Text)
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"currency")) Parser
  (Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object')
-> Parser
     (Maybe Text
      -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"object")) Parser
  (Maybe Text
   -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1)
-> Parser (Maybe Text)
-> Parser
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
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
"routing_number"))

-- | Create a new 'PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1' with all required fields.
mkPostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1 ::
  -- | 'postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountNumber'
  Data.Text.Internal.Text ->
  -- | 'postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Country'
  Data.Text.Internal.Text ->
  PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
mkPostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1 :: Text
-> Text
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
mkPostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1 Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountNumber Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Country =
  PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1 :: Maybe Text
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> Text
-> Text
-> Maybe Text
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> Maybe Text
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
    { postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderName :: Maybe Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderName = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType :: Maybe
  PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType = Maybe
  PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountNumber :: Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountNumber = Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountNumber,
      postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Country :: Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Country = Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Country,
      postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Currency :: Maybe Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Currency = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object :: Maybe
  PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object = Maybe
  PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1RoutingNumber :: Maybe Text
postCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1RoutingNumber = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the enum schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.bank_account.anyOf.properties.account_holder_type@ in the specification.
data PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'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.
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"company"@
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'EnumCompany
  | -- | Represents the JSON value @"individual"@
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'EnumIndividual
  deriving (Int
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> String
-> String
[PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType']
-> String -> String
PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> String
(Int
 -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
    -> String)
-> ([PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType']
    -> String -> String)
-> Show
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType']
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType']
-> String -> String
show :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> String
$cshow :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> String
-> String
GHC.Show.Show, PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> Bool
(PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
 -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
 -> Bool)
-> (PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
    -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
    -> Bool)
-> Eq
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> Bool
$c/= :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> Bool
== :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> Bool
$c== :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType' where
  toJSON :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> Value
toJSON (PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'Other Value
val) = Value
val
  toJSON (PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'EnumCompany) = Value
"company"
  toJSON (PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'EnumIndividual) = Value
"individual"

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
parseJSON Value
val =
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
-> Parser
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
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
"company" -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'EnumCompany
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"individual" -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'EnumIndividual
            | Bool
GHC.Base.otherwise -> Value
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'
PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1AccountHolderType'Other Value
val
      )

-- | Defines the enum schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.bank_account.anyOf.properties.object@ in the specification.
data PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'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.
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"bank_account"@
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'EnumBankAccount
  deriving (Int
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> String
-> String
[PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object']
-> String -> String
PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> String
(Int
 -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
    -> String)
-> ([PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object']
    -> String -> String)
-> Show
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object']
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object']
-> String -> String
show :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> String
$cshow :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> String
-> String
GHC.Show.Show, PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> Bool
(PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
 -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
 -> Bool)
-> (PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
    -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
    -> Bool)
-> Eq
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> Bool
$c/= :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> Bool
== :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> Bool
$c== :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object' where
  toJSON :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> Value
toJSON (PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'Other Value
val) = Value
val
  toJSON (PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'EnumBankAccount) = Value
"bank_account"

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
parseJSON Value
val =
    PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
-> Parser
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
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
"bank_account" -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'EnumBankAccount
            | Bool
GHC.Base.otherwise -> Value
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'
PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1Object'Other Value
val
      )

-- | Defines the oneOf schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.bank_account.anyOf@ in the specification.
--
-- Either a token, like the ones returned by [Stripe.js](https:\/\/stripe.com\/docs\/stripe.js), or a dictionary containing a user\'s bank account details.
data PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
  = PostCustomersCustomerBankAccountsRequestBodyBankAccount'PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1 PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
  | PostCustomersCustomerBankAccountsRequestBodyBankAccount'Text Data.Text.Internal.Text
  deriving (Int
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> String
-> String
[PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants]
-> String -> String
PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> String
(Int
 -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
    -> String)
-> ([PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants]
    -> String -> String)
-> Show
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants]
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants]
-> String -> String
show :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> String
$cshow :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> String
-> String
GHC.Show.Show, PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> Bool
(PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
 -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
 -> Bool)
-> (PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
    -> PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
    -> Bool)
-> Eq
     PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> Bool
$c/= :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> Bool
== :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> Bool
$c== :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants where
  toJSON :: PostCustomersCustomerBankAccountsRequestBodyBankAccount'Variants
-> Value
toJSON (PostCustomersCustomerBankAccountsRequestBodyBankAccount'PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1 PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
a) = PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
-> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON PostCustomersCustomerBankAccountsRequestBodyBankAccount'OneOf1
a
  toJSON (PostCustomersCustomerBankAccountsRequestBodyBankAccount'Text Text
a) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
a

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

-- | Defines the object schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.card.anyOf@ in the specification.
data PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 = PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
  { -- | address_city
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressCity :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_country
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressCountry :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_line1
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressLine1 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_line2
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressLine2 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_state
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressState :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_zip
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressZip :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | cvc
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Cvc :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | exp_month
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Int
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpMonth :: GHC.Types.Int,
    -- | exp_year
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Int
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpYear :: GHC.Types.Int,
    -- | metadata
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Object
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Metadata :: (GHC.Maybe.Maybe Data.Aeson.Types.Internal.Object),
    -- | name
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Name :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | number
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Number :: Data.Text.Internal.Text,
    -- | object
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object')
  }
  deriving
    ( Int
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> String
-> String
[PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1]
-> String -> String
PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> String
(Int
 -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
    -> String)
-> ([PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1]
    -> String -> String)
-> Show PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1]
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1]
-> String -> String
show :: PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> String
$cshow :: PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Bool
(PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
 -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Bool)
-> (PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
    -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Bool)
-> Eq PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Bool
$c/= :: PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Bool
== :: PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Bool
$c== :: PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 where
  toJSON :: PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Value
toJSON PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"address_city" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressCity PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_country" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressCountry PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_line1" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressLine1 PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_line2" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressLine2 PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_state" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressState PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_zip" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressZip PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"cvc" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Cvc PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"exp_month" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Int
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpMonth PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"exp_year" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Int
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpYear PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text -> Maybe Object -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Object
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Metadata PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"name" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Name PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"number" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Number PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"object" Text
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Encoding
toEncoding PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"address_city" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressCity PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_country" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressCountry PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_line1" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressLine1 PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_line2" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressLine2 PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_state" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressState PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_zip" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressZip PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"cvc" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Cvc PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"exp_month" Text -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Int
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpMonth PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"exp_year" Text -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Int
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpYear PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"metadata" Text -> Maybe Object -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Object
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Metadata PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"name" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Name PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"number" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Number PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"object" Text
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
obj)))))))))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 where
  parseJSON :: Value
-> Parser PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
parseJSON = String
-> (Object
    -> Parser PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
-> Value
-> Parser PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1" (\Object
obj -> (((((((((((((Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Int
 -> Int
 -> Maybe Object
 -> Maybe Text
 -> Text
 -> Maybe
      PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
 -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Object
      -> Maybe Text
      -> Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
      -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> Int
-> Maybe Object
-> Maybe Text
-> Text
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Object
   -> Maybe Text
   -> Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
   -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Object
      -> Maybe Text
      -> Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
      -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
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
"address_city")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Object
   -> Maybe Text
   -> Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
   -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Object
      -> Maybe Text
      -> Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
      -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
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
"address_country")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Object
   -> Maybe Text
   -> Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
   -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Object
      -> Maybe Text
      -> Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
      -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
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
"address_line1")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Object
   -> Maybe Text
   -> Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
   -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Object
      -> Maybe Text
      -> Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
      -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
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
"address_line2")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Object
   -> Maybe Text
   -> Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
   -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Object
      -> Maybe Text
      -> Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
      -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
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
"address_state")) Parser
  (Maybe Text
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Object
   -> Maybe Text
   -> Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
   -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Int
      -> Int
      -> Maybe Object
      -> Maybe Text
      -> Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
      -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
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
"address_zip")) Parser
  (Maybe Text
   -> Int
   -> Int
   -> Maybe Object
   -> Maybe Text
   -> Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
   -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
-> Parser (Maybe Text)
-> Parser
     (Int
      -> Int
      -> Maybe Object
      -> Maybe Text
      -> Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
      -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
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
"cvc")) Parser
  (Int
   -> Int
   -> Maybe Object
   -> Maybe Text
   -> Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
   -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
-> Parser Int
-> Parser
     (Int
      -> Maybe Object
      -> Maybe Text
      -> Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
      -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
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
"exp_month")) Parser
  (Int
   -> Maybe Object
   -> Maybe Text
   -> Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
   -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
-> Parser Int
-> Parser
     (Maybe Object
      -> Maybe Text
      -> Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
      -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
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
"exp_year")) Parser
  (Maybe Object
   -> Maybe Text
   -> Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
   -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
-> Parser (Maybe Object)
-> Parser
     (Maybe Text
      -> Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
      -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"metadata")) Parser
  (Maybe Text
   -> Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
   -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
-> Parser (Maybe Text)
-> Parser
     (Text
      -> Maybe
           PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
      -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"name")) Parser
  (Text
   -> Maybe
        PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
   -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
-> Parser Text
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
      -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
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
"number")) Parser
  (Maybe
     PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
   -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1)
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object')
-> Parser PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"object"))

-- | Create a new 'PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1' with all required fields.
mkPostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 ::
  -- | 'postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpMonth'
  GHC.Types.Int ->
  -- | 'postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpYear'
  GHC.Types.Int ->
  -- | 'postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Number'
  Data.Text.Internal.Text ->
  PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
mkPostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 :: Int
-> Int
-> Text
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
mkPostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 Int
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpMonth Int
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpYear Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Number =
  PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 :: Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> Int
-> Maybe Object
-> Maybe Text
-> Text
-> Maybe
     PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
    { postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressCity :: Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressCity = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressCountry :: Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressCountry = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressLine1 :: Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressLine1 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressLine2 :: Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressLine2 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressState :: Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressState = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressZip :: Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1AddressZip = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Cvc :: Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Cvc = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpMonth :: Int
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpMonth = Int
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpMonth,
      postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpYear :: Int
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpYear = Int
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1ExpYear,
      postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Metadata :: Maybe Object
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Metadata = Maybe Object
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Name :: Maybe Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Name = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Number :: Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Number = Text
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Number,
      postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object :: Maybe
  PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
postCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object = Maybe
  PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the enum schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.card.anyOf.properties.object@ in the specification.
data PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'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.
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"card"@
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'EnumCard
  deriving (Int
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> String
-> String
[PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object']
-> String -> String
PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> String
(Int
 -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
    -> String)
-> ([PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object']
    -> String -> String)
-> Show
     PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object']
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object']
-> String -> String
show :: PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> String
$cshow :: PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> String
-> String
GHC.Show.Show, PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> Bool
(PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
 -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
 -> Bool)
-> (PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
    -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
    -> Bool)
-> Eq
     PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> Bool
$c/= :: PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> Bool
== :: PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> Bool
$c== :: PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object' where
  toJSON :: PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> Value
toJSON (PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'Other Value
val) = Value
val
  toJSON (PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'EnumCard) = Value
"card"

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
parseJSON Value
val =
    PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
-> Parser
     PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
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
"card" -> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'EnumCard
            | Bool
GHC.Base.otherwise -> Value
-> PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'
PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1Object'Other Value
val
      )

-- | Defines the oneOf schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.card.anyOf@ in the specification.
--
-- A token, like the ones returned by [Stripe.js](https:\/\/stripe.com\/docs\/stripe.js).
data PostCustomersCustomerBankAccountsRequestBodyCard'Variants
  = PostCustomersCustomerBankAccountsRequestBodyCard'PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
  | PostCustomersCustomerBankAccountsRequestBodyCard'Text Data.Text.Internal.Text
  deriving (Int
-> PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> String
-> String
[PostCustomersCustomerBankAccountsRequestBodyCard'Variants]
-> String -> String
PostCustomersCustomerBankAccountsRequestBodyCard'Variants -> String
(Int
 -> PostCustomersCustomerBankAccountsRequestBodyCard'Variants
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsRequestBodyCard'Variants
    -> String)
-> ([PostCustomersCustomerBankAccountsRequestBodyCard'Variants]
    -> String -> String)
-> Show PostCustomersCustomerBankAccountsRequestBodyCard'Variants
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsRequestBodyCard'Variants]
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsRequestBodyCard'Variants]
-> String -> String
show :: PostCustomersCustomerBankAccountsRequestBodyCard'Variants -> String
$cshow :: PostCustomersCustomerBankAccountsRequestBodyCard'Variants -> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> String
-> String
GHC.Show.Show, PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> Bool
(PostCustomersCustomerBankAccountsRequestBodyCard'Variants
 -> PostCustomersCustomerBankAccountsRequestBodyCard'Variants
 -> Bool)
-> (PostCustomersCustomerBankAccountsRequestBodyCard'Variants
    -> PostCustomersCustomerBankAccountsRequestBodyCard'Variants
    -> Bool)
-> Eq PostCustomersCustomerBankAccountsRequestBodyCard'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> Bool
$c/= :: PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> Bool
== :: PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> Bool
$c== :: PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> PostCustomersCustomerBankAccountsRequestBodyCard'Variants
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsRequestBodyCard'Variants where
  toJSON :: PostCustomersCustomerBankAccountsRequestBodyCard'Variants -> Value
toJSON (PostCustomersCustomerBankAccountsRequestBodyCard'PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
a) = PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1 -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON PostCustomersCustomerBankAccountsRequestBodyCard'OneOf1
a
  toJSON (PostCustomersCustomerBankAccountsRequestBodyCard'Text Text
a) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
a

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

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