{-# 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 postCustomersCustomerBankAccountsId
module StripeAPI.Operations.PostCustomersCustomerBankAccountsId 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/{id}
--
-- \<p>Update a specified source for a given customer.\<\/p>
postCustomersCustomerBankAccountsId ::
  forall m.
  StripeAPI.Common.MonadHTTP m =>
  -- | Contains all available parameters of this operation (query and path parameters)
  PostCustomersCustomerBankAccountsIdParameters ->
  -- | The request body to send
  GHC.Maybe.Maybe PostCustomersCustomerBankAccountsIdRequestBody ->
  -- | Monadic computation which returns the result of the operation
  StripeAPI.Common.StripeT m (Network.HTTP.Client.Types.Response PostCustomersCustomerBankAccountsIdResponse)
postCustomersCustomerBankAccountsId :: PostCustomersCustomerBankAccountsIdParameters
-> Maybe PostCustomersCustomerBankAccountsIdRequestBody
-> StripeT m (Response PostCustomersCustomerBankAccountsIdResponse)
postCustomersCustomerBankAccountsId
  PostCustomersCustomerBankAccountsIdParameters
parameters
  Maybe PostCustomersCustomerBankAccountsIdRequestBody
body =
    (Response ByteString
 -> Response PostCustomersCustomerBankAccountsIdResponse)
-> StripeT m (Response ByteString)
-> StripeT m (Response PostCustomersCustomerBankAccountsIdResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
      ( \Response ByteString
response_0 ->
          (ByteString -> PostCustomersCustomerBankAccountsIdResponse)
-> Response ByteString
-> Response PostCustomersCustomerBankAccountsIdResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
            ( (String -> PostCustomersCustomerBankAccountsIdResponse)
-> (PostCustomersCustomerBankAccountsIdResponse
    -> PostCustomersCustomerBankAccountsIdResponse)
-> Either String PostCustomersCustomerBankAccountsIdResponse
-> PostCustomersCustomerBankAccountsIdResponse
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
Data.Either.either String -> PostCustomersCustomerBankAccountsIdResponse
PostCustomersCustomerBankAccountsIdResponseError PostCustomersCustomerBankAccountsIdResponse
-> PostCustomersCustomerBankAccountsIdResponse
forall a. a -> a
GHC.Base.id
                (Either String PostCustomersCustomerBankAccountsIdResponse
 -> PostCustomersCustomerBankAccountsIdResponse)
-> (ByteString
    -> Either String PostCustomersCustomerBankAccountsIdResponse)
-> ByteString
-> PostCustomersCustomerBankAccountsIdResponse
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) ->
                                     PostCustomersCustomerBankAccountsIdResponseBody200
-> PostCustomersCustomerBankAccountsIdResponse
PostCustomersCustomerBankAccountsIdResponse200
                                       (PostCustomersCustomerBankAccountsIdResponseBody200
 -> PostCustomersCustomerBankAccountsIdResponse)
-> Either String PostCustomersCustomerBankAccountsIdResponseBody200
-> Either String PostCustomersCustomerBankAccountsIdResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString
-> Either String PostCustomersCustomerBankAccountsIdResponseBody200
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                            Data.Either.Either
                                                              GHC.Base.String
                                                              PostCustomersCustomerBankAccountsIdResponseBody200
                                                        )
                                   | 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 -> PostCustomersCustomerBankAccountsIdResponse
PostCustomersCustomerBankAccountsIdResponseDefault
                                       (Error -> PostCustomersCustomerBankAccountsIdResponse)
-> Either String Error
-> Either String PostCustomersCustomerBankAccountsIdResponse
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 PostCustomersCustomerBankAccountsIdResponse
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 PostCustomersCustomerBankAccountsIdRequestBody
-> RequestBodyEncoding
-> StripeT m (Response ByteString)
forall (m :: * -> *) body.
(MonadHTTP m, ToJSON body) =>
Text
-> Text
-> [QueryParameter]
-> Maybe body
-> RequestBodyEncoding
-> StripeT m (Response ByteString)
StripeAPI.Common.doBodyCallWithConfigurationM (Text -> Text
Data.Text.toUpper (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
GHC.Base.$ String -> Text
Data.Text.pack String
"POST") (String -> Text
Data.Text.pack (String
"/v1/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 (PostCustomersCustomerBankAccountsIdParameters -> Text
postCustomersCustomerBankAccountsIdParametersPathCustomer PostCustomersCustomerBankAccountsIdParameters
parameters))) String -> String -> String
forall a. [a] -> [a] -> [a]
GHC.Base.++ (String
"/bank_accounts/" 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 (PostCustomersCustomerBankAccountsIdParameters -> Text
postCustomersCustomerBankAccountsIdParametersPathId PostCustomersCustomerBankAccountsIdParameters
parameters))) String -> String -> String
forall a. [a] -> [a] -> [a]
GHC.Base.++ String
""))))) [QueryParameter]
forall a. Monoid a => a
GHC.Base.mempty Maybe PostCustomersCustomerBankAccountsIdRequestBody
body RequestBodyEncoding
StripeAPI.Common.RequestBodyEncodingFormData)

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

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

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsIdParameters where
  parseJSON :: Value -> Parser PostCustomersCustomerBankAccountsIdParameters
parseJSON = String
-> (Object -> Parser PostCustomersCustomerBankAccountsIdParameters)
-> Value
-> Parser PostCustomersCustomerBankAccountsIdParameters
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerBankAccountsIdParameters" (\Object
obj -> ((Text -> Text -> PostCustomersCustomerBankAccountsIdParameters)
-> Parser
     (Text -> Text -> PostCustomersCustomerBankAccountsIdParameters)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Text -> Text -> PostCustomersCustomerBankAccountsIdParameters
PostCustomersCustomerBankAccountsIdParameters Parser
  (Text -> Text -> PostCustomersCustomerBankAccountsIdParameters)
-> Parser Text
-> Parser (Text -> PostCustomersCustomerBankAccountsIdParameters)
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
"pathCustomer")) Parser (Text -> PostCustomersCustomerBankAccountsIdParameters)
-> Parser Text
-> Parser PostCustomersCustomerBankAccountsIdParameters
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"pathId"))

-- | Create a new 'PostCustomersCustomerBankAccountsIdParameters' with all required fields.
mkPostCustomersCustomerBankAccountsIdParameters ::
  -- | 'postCustomersCustomerBankAccountsIdParametersPathCustomer'
  Data.Text.Internal.Text ->
  -- | 'postCustomersCustomerBankAccountsIdParametersPathId'
  Data.Text.Internal.Text ->
  PostCustomersCustomerBankAccountsIdParameters
mkPostCustomersCustomerBankAccountsIdParameters :: Text -> Text -> PostCustomersCustomerBankAccountsIdParameters
mkPostCustomersCustomerBankAccountsIdParameters Text
postCustomersCustomerBankAccountsIdParametersPathCustomer Text
postCustomersCustomerBankAccountsIdParametersPathId =
  PostCustomersCustomerBankAccountsIdParameters :: Text -> Text -> PostCustomersCustomerBankAccountsIdParameters
PostCustomersCustomerBankAccountsIdParameters
    { postCustomersCustomerBankAccountsIdParametersPathCustomer :: Text
postCustomersCustomerBankAccountsIdParametersPathCustomer = Text
postCustomersCustomerBankAccountsIdParametersPathCustomer,
      postCustomersCustomerBankAccountsIdParametersPathId :: Text
postCustomersCustomerBankAccountsIdParametersPathId = Text
postCustomersCustomerBankAccountsIdParametersPathId
    }

-- | Defines the object schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts\/{id}.POST.requestBody.content.application\/x-www-form-urlencoded.schema@ in the specification.
data PostCustomersCustomerBankAccountsIdRequestBody = PostCustomersCustomerBankAccountsIdRequestBody
  { -- | account_holder_name: The name of the person or business that owns the bank account.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAccountHolderName :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | account_holder_type: The type of entity that holds the account. This can be either \`individual\` or \`company\`.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBody
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyAccountHolderType'
postCustomersCustomerBankAccountsIdRequestBodyAccountHolderType :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsIdRequestBodyAccountHolderType'),
    -- | address_city: City\/District\/Suburb\/Town\/Village.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressCity :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_country: Billing address country, if provided when creating card.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressCountry :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_line1: Address line 1 (Street address\/PO Box\/Company name).
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressLine1 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_line2: Address line 2 (Apartment\/Suite\/Unit\/Building).
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressLine2 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_state: State\/County\/Province\/Region.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressState :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_zip: ZIP or postal code.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressZip :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | exp_month: Two digit number representing the card’s expiration month.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyExpMonth :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | exp_year: Four digit number representing the card’s expiration year.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyExpYear :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | expand: Specifies which fields in the response should be expanded.
    PostCustomersCustomerBankAccountsIdRequestBody -> Maybe [Text]
postCustomersCustomerBankAccountsIdRequestBodyExpand :: (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\`.
    PostCustomersCustomerBankAccountsIdRequestBody
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
postCustomersCustomerBankAccountsIdRequestBodyMetadata :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants),
    -- | name: Cardholder name.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyName :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | owner
    PostCustomersCustomerBankAccountsIdRequestBody
-> Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'
postCustomersCustomerBankAccountsIdRequestBodyOwner :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner')
  }
  deriving
    ( Int
-> PostCustomersCustomerBankAccountsIdRequestBody
-> String
-> String
[PostCustomersCustomerBankAccountsIdRequestBody]
-> String -> String
PostCustomersCustomerBankAccountsIdRequestBody -> String
(Int
 -> PostCustomersCustomerBankAccountsIdRequestBody
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsIdRequestBody -> String)
-> ([PostCustomersCustomerBankAccountsIdRequestBody]
    -> String -> String)
-> Show PostCustomersCustomerBankAccountsIdRequestBody
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsIdRequestBody]
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsIdRequestBody]
-> String -> String
show :: PostCustomersCustomerBankAccountsIdRequestBody -> String
$cshow :: PostCustomersCustomerBankAccountsIdRequestBody -> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsIdRequestBody
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsIdRequestBody
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerBankAccountsIdRequestBody
-> PostCustomersCustomerBankAccountsIdRequestBody -> Bool
(PostCustomersCustomerBankAccountsIdRequestBody
 -> PostCustomersCustomerBankAccountsIdRequestBody -> Bool)
-> (PostCustomersCustomerBankAccountsIdRequestBody
    -> PostCustomersCustomerBankAccountsIdRequestBody -> Bool)
-> Eq PostCustomersCustomerBankAccountsIdRequestBody
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsIdRequestBody
-> PostCustomersCustomerBankAccountsIdRequestBody -> Bool
$c/= :: PostCustomersCustomerBankAccountsIdRequestBody
-> PostCustomersCustomerBankAccountsIdRequestBody -> Bool
== :: PostCustomersCustomerBankAccountsIdRequestBody
-> PostCustomersCustomerBankAccountsIdRequestBody -> Bool
$c== :: PostCustomersCustomerBankAccountsIdRequestBody
-> PostCustomersCustomerBankAccountsIdRequestBody -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsIdRequestBody where
  toJSON :: PostCustomersCustomerBankAccountsIdRequestBody -> Value
toJSON PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAccountHolderName PostCustomersCustomerBankAccountsIdRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"account_holder_type" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyAccountHolderType'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBody
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyAccountHolderType'
postCustomersCustomerBankAccountsIdRequestBodyAccountHolderType PostCustomersCustomerBankAccountsIdRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_city" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressCity PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressCountry PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressLine1 PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressLine2 PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressState PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressZip PostCustomersCustomerBankAccountsIdRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"exp_month" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyExpMonth PostCustomersCustomerBankAccountsIdRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"exp_year" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyExpYear PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe [Text]
postCustomersCustomerBankAccountsIdRequestBodyExpand PostCustomersCustomerBankAccountsIdRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBody
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
postCustomersCustomerBankAccountsIdRequestBodyMetadata PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyName PostCustomersCustomerBankAccountsIdRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"owner" Text
-> Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBody
-> Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'
postCustomersCustomerBankAccountsIdRequestBodyOwner PostCustomersCustomerBankAccountsIdRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerBankAccountsIdRequestBody -> Encoding
toEncoding PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAccountHolderName PostCustomersCustomerBankAccountsIdRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"account_holder_type" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyAccountHolderType'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBody
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyAccountHolderType'
postCustomersCustomerBankAccountsIdRequestBodyAccountHolderType PostCustomersCustomerBankAccountsIdRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_city" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressCity PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressCountry PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressLine1 PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressLine2 PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressState PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressZip PostCustomersCustomerBankAccountsIdRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"exp_month" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyExpMonth PostCustomersCustomerBankAccountsIdRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"exp_year" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyExpYear PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe [Text]
postCustomersCustomerBankAccountsIdRequestBodyExpand PostCustomersCustomerBankAccountsIdRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"metadata" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBody
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
postCustomersCustomerBankAccountsIdRequestBodyMetadata PostCustomersCustomerBankAccountsIdRequestBody
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..= PostCustomersCustomerBankAccountsIdRequestBody -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyName PostCustomersCustomerBankAccountsIdRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"owner" Text
-> Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBody
-> Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'
postCustomersCustomerBankAccountsIdRequestBodyOwner PostCustomersCustomerBankAccountsIdRequestBody
obj))))))))))))))

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

-- | Create a new 'PostCustomersCustomerBankAccountsIdRequestBody' with all required fields.
mkPostCustomersCustomerBankAccountsIdRequestBody :: PostCustomersCustomerBankAccountsIdRequestBody
mkPostCustomersCustomerBankAccountsIdRequestBody :: PostCustomersCustomerBankAccountsIdRequestBody
mkPostCustomersCustomerBankAccountsIdRequestBody =
  PostCustomersCustomerBankAccountsIdRequestBody :: Maybe Text
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyAccountHolderType'
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [Text]
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> Maybe Text
-> Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'
-> PostCustomersCustomerBankAccountsIdRequestBody
PostCustomersCustomerBankAccountsIdRequestBody
    { postCustomersCustomerBankAccountsIdRequestBodyAccountHolderName :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAccountHolderName = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyAccountHolderType :: Maybe
  PostCustomersCustomerBankAccountsIdRequestBodyAccountHolderType'
postCustomersCustomerBankAccountsIdRequestBodyAccountHolderType = Maybe
  PostCustomersCustomerBankAccountsIdRequestBodyAccountHolderType'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyAddressCity :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressCity = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyAddressCountry :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressCountry = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyAddressLine1 :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressLine1 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyAddressLine2 :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressLine2 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyAddressState :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressState = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyAddressZip :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyAddressZip = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyExpMonth :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyExpMonth = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyExpYear :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyExpYear = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyExpand :: Maybe [Text]
postCustomersCustomerBankAccountsIdRequestBodyExpand = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyMetadata :: Maybe
  PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
postCustomersCustomerBankAccountsIdRequestBodyMetadata = Maybe
  PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyName :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyName = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyOwner :: Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'
postCustomersCustomerBankAccountsIdRequestBodyOwner = Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'
forall a. Maybe a
GHC.Maybe.Nothing
    }

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

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

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

-- | Defines the oneOf schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts\/{id}.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.metadata.anyOf@ in the specification.
--
-- Set of [key-value pairs](https:\/\/stripe.com\/docs\/api\/metadata) that you can attach to an object. This can be useful for storing additional information about the object in a structured format. Individual keys can be unset by posting an empty value to them. All keys can be unset by posting an empty value to \`metadata\`.
data PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
  = -- | Represents the JSON value @""@
    PostCustomersCustomerBankAccountsIdRequestBodyMetadata'EmptyString
  | PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Object Data.Aeson.Types.Internal.Object
  deriving (Int
-> PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> String
-> String
[PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants]
-> String -> String
PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> String
(Int
 -> PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
    -> String)
-> ([PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants]
    -> String -> String)
-> Show
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants]
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants]
-> String -> String
show :: PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> String
$cshow :: PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> String
-> String
GHC.Show.Show, PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> Bool
(PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
 -> PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
 -> Bool)
-> (PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
    -> PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
    -> Bool)
-> Eq
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> Bool
$c/= :: PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> Bool
== :: PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> Bool
$c== :: PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> Bool
GHC.Classes.Eq)

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

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
parseJSON Value
val =
    if
        | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"" -> PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> Parser
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
PostCustomersCustomerBankAccountsIdRequestBodyMetadata'EmptyString
        | Bool
GHC.Base.otherwise -> case (Object
-> PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Object (Object
 -> PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants)
-> Result Object
-> Result
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Object
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result
  PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> Result
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> Result
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched" of
          Data.Aeson.Types.Internal.Success PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
a -> PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
-> Parser
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerBankAccountsIdRequestBodyMetadata'Variants
a
          Data.Aeson.Types.Internal.Error String
a -> String
-> Parser
     PostCustomersCustomerBankAccountsIdRequestBodyMetadata'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\/{id}.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.owner@ in the specification.
data PostCustomersCustomerBankAccountsIdRequestBodyOwner' = PostCustomersCustomerBankAccountsIdRequestBodyOwner'
  { -- | address
    PostCustomersCustomerBankAccountsIdRequestBodyOwner'
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'),
    -- | email
    PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Email :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | name
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Name :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | phone
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Phone :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner'
-> String
-> String
[PostCustomersCustomerBankAccountsIdRequestBodyOwner']
-> String -> String
PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> String
(Int
 -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> String)
-> ([PostCustomersCustomerBankAccountsIdRequestBodyOwner']
    -> String -> String)
-> Show PostCustomersCustomerBankAccountsIdRequestBodyOwner'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsIdRequestBodyOwner']
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsIdRequestBodyOwner']
-> String -> String
show :: PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> String
$cshow :: PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner'
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerBankAccountsIdRequestBodyOwner'
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Bool
(PostCustomersCustomerBankAccountsIdRequestBodyOwner'
 -> PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Bool)
-> (PostCustomersCustomerBankAccountsIdRequestBodyOwner'
    -> PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Bool)
-> Eq PostCustomersCustomerBankAccountsIdRequestBodyOwner'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Bool
$c/= :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Bool
== :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Bool
$c== :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsIdRequestBodyOwner' where
  toJSON :: PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Value
toJSON PostCustomersCustomerBankAccountsIdRequestBodyOwner'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"address" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner'
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address PostCustomersCustomerBankAccountsIdRequestBodyOwner'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"email" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Email PostCustomersCustomerBankAccountsIdRequestBodyOwner'
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..= PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Name PostCustomersCustomerBankAccountsIdRequestBodyOwner'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"phone" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Phone PostCustomersCustomerBankAccountsIdRequestBodyOwner'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Encoding
toEncoding PostCustomersCustomerBankAccountsIdRequestBodyOwner'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"address" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner'
-> Maybe
     PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address PostCustomersCustomerBankAccountsIdRequestBodyOwner'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"email" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Email PostCustomersCustomerBankAccountsIdRequestBodyOwner'
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..= PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Name PostCustomersCustomerBankAccountsIdRequestBodyOwner'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"phone" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner' -> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Phone PostCustomersCustomerBankAccountsIdRequestBodyOwner'
obj))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsIdRequestBodyOwner' where
  parseJSON :: Value
-> Parser PostCustomersCustomerBankAccountsIdRequestBodyOwner'
parseJSON = String
-> (Object
    -> Parser PostCustomersCustomerBankAccountsIdRequestBodyOwner')
-> Value
-> Parser PostCustomersCustomerBankAccountsIdRequestBodyOwner'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerBankAccountsIdRequestBodyOwner'" (\Object
obj -> ((((Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> PostCustomersCustomerBankAccountsIdRequestBodyOwner')
-> Parser
     (Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdRequestBodyOwner')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner'
PostCustomersCustomerBankAccountsIdRequestBodyOwner' Parser
  (Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdRequestBodyOwner')
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdRequestBodyOwner')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"address")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdRequestBodyOwner')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdRequestBodyOwner')
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
"email")) Parser
  (Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdRequestBodyOwner')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> PostCustomersCustomerBankAccountsIdRequestBodyOwner')
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
  (Maybe Text
   -> PostCustomersCustomerBankAccountsIdRequestBodyOwner')
-> Parser (Maybe Text)
-> Parser PostCustomersCustomerBankAccountsIdRequestBodyOwner'
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
"phone"))

-- | Create a new 'PostCustomersCustomerBankAccountsIdRequestBodyOwner'' with all required fields.
mkPostCustomersCustomerBankAccountsIdRequestBodyOwner' :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'
mkPostCustomersCustomerBankAccountsIdRequestBodyOwner' :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'
mkPostCustomersCustomerBankAccountsIdRequestBodyOwner' =
  PostCustomersCustomerBankAccountsIdRequestBodyOwner' :: Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner'
PostCustomersCustomerBankAccountsIdRequestBodyOwner'
    { postCustomersCustomerBankAccountsIdRequestBodyOwner'Address :: Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address = Maybe PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyOwner'Email :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Email = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyOwner'Name :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Name = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyOwner'Phone :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Phone = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts\/{id}.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.owner.properties.address@ in the specification.
data PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address' = PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
  { -- | city
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'City :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | country
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'Country :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | line1
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'Line1 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | line2
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'Line2 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | postal_code
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'PostalCode :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | state
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'State :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> String
-> String
[PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address']
-> String -> String
PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> String
(Int
 -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
    -> String)
-> ([PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address']
    -> String -> String)
-> Show
     PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address']
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address']
-> String -> String
show :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> String
$cshow :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Bool
(PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
 -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
 -> Bool)
-> (PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
    -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
    -> Bool)
-> Eq PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Bool
$c/= :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Bool
== :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Bool
$c== :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address' where
  toJSON :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Value
toJSON PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"city" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'City PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"country" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'Country PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"line1" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'Line1 PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"line2" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'Line2 PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"postal_code" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'PostalCode PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"state" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'State PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Encoding
toEncoding PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"city" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'City PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"country" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'Country PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"line1" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'Line1 PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"line2" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'Line2 PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"postal_code" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'PostalCode PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"state" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'State PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
obj))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
parseJSON = String
-> (Object
    -> Parser
         PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
-> Value
-> Parser
     PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'" (\Object
obj -> ((((((Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address' Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
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
"city")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
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
"country")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
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
"line1")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
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
"line2")) Parser
  (Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
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
"postal_code")) Parser
  (Maybe Text
   -> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address')
-> Parser (Maybe Text)
-> Parser
     PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
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
"state"))

-- | Create a new 'PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'' with all required fields.
mkPostCustomersCustomerBankAccountsIdRequestBodyOwner'Address' :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
mkPostCustomersCustomerBankAccountsIdRequestBodyOwner'Address' :: PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
mkPostCustomersCustomerBankAccountsIdRequestBodyOwner'Address' =
  PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address' :: Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
PostCustomersCustomerBankAccountsIdRequestBodyOwner'Address'
    { postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'City :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'City = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'Country :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'Country = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'Line1 :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'Line1 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'Line2 :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'Line2 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'PostalCode :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'PostalCode = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'State :: Maybe Text
postCustomersCustomerBankAccountsIdRequestBodyOwner'Address'State = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

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

-- | Defines the object schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts\/{id}.POST.responses.200.content.application\/json.schema.anyOf@ in the specification.
data PostCustomersCustomerBankAccountsIdResponseBody200 = PostCustomersCustomerBankAccountsIdResponseBody200
  { -- | account: The account this card belongs to. This attribute will not be in the card object if the card belongs to a customer or recipient instead.
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
postCustomersCustomerBankAccountsIdResponseBody200Account :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants),
    -- | account_holder_name: The name of the person or business that owns the bank account.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AccountHolderName :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | account_holder_type: The type of entity that holds the account. This can be either \`individual\` or \`company\`.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AccountHolderType :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | ach_credit_transfer
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeAchCreditTransfer
postCustomersCustomerBankAccountsIdResponseBody200AchCreditTransfer :: (GHC.Maybe.Maybe SourceTypeAchCreditTransfer),
    -- | ach_debit
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeAchDebit
postCustomersCustomerBankAccountsIdResponseBody200AchDebit :: (GHC.Maybe.Maybe SourceTypeAchDebit),
    -- | acss_debit
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeAcssDebit
postCustomersCustomerBankAccountsIdResponseBody200AcssDebit :: (GHC.Maybe.Maybe SourceTypeAcssDebit),
    -- | address_city: City\/District\/Suburb\/Town\/Village.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressCity :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_country: Billing address country, if provided when creating card.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressCountry :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_line1: Address line 1 (Street address\/PO Box\/Company name).
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressLine1 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_line1_check: If \`address_line1\` was provided, results of the check: \`pass\`, \`fail\`, \`unavailable\`, or \`unchecked\`.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressLine1Check :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_line2: Address line 2 (Apartment\/Suite\/Unit\/Building).
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressLine2 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_state: State\/County\/Province\/Region.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressState :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_zip: ZIP or postal code.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressZip :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_zip_check: If \`address_zip\` was provided, results of the check: \`pass\`, \`fail\`, \`unavailable\`, or \`unchecked\`.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressZipCheck :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | alipay
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeAlipay
postCustomersCustomerBankAccountsIdResponseBody200Alipay :: (GHC.Maybe.Maybe SourceTypeAlipay),
    -- | amount: A positive integer in the smallest currency unit (that is, 100 cents for \$1.00, or 1 for ¥1, Japanese Yen being a zero-decimal currency) representing the total amount associated with the source. This is the amount for which the source will be chargeable once ready. Required for \`single_use\` sources.
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200Amount :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | au_becs_debit
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeAuBecsDebit
postCustomersCustomerBankAccountsIdResponseBody200AuBecsDebit :: (GHC.Maybe.Maybe SourceTypeAuBecsDebit),
    -- | available_payout_methods: A set of available payout methods for this card. Only values from this set should be passed as the \`method\` when creating a payout.
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe
     [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
postCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods :: (GHC.Maybe.Maybe ([PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'])),
    -- | bancontact
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeBancontact
postCustomersCustomerBankAccountsIdResponseBody200Bancontact :: (GHC.Maybe.Maybe SourceTypeBancontact),
    -- | bank_name: Name of the bank associated with the routing number (e.g., \`WELLS FARGO\`).
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200BankName :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | brand: Card brand. Can be \`American Express\`, \`Diners Club\`, \`Discover\`, \`JCB\`, \`MasterCard\`, \`UnionPay\`, \`Visa\`, or \`Unknown\`.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Brand :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | card
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeCard
postCustomersCustomerBankAccountsIdResponseBody200Card :: (GHC.Maybe.Maybe SourceTypeCard),
    -- | card_present
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeCardPresent
postCustomersCustomerBankAccountsIdResponseBody200CardPresent :: (GHC.Maybe.Maybe SourceTypeCardPresent),
    -- | client_secret: The client secret of the source. Used for client-side retrieval using a publishable key.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200ClientSecret :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | code_verification:
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceCodeVerificationFlow
postCustomersCustomerBankAccountsIdResponseBody200CodeVerification :: (GHC.Maybe.Maybe SourceCodeVerificationFlow),
    -- | country: Two-letter ISO code representing the country of the card. You could use this attribute to get a sense of the international breakdown of cards you\'ve collected.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Country :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | created: Time at which the object was created. Measured in seconds since the Unix epoch.
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200Created :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | currency: Three-letter [ISO code for currency](https:\/\/stripe.com\/docs\/payouts). Only applicable on accounts (not customers or recipients). The card can be used as a transfer destination for funds in this currency.
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Currency :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | customer: The customer that this card belongs to. This attribute will not be in the card object if the card belongs to an account or recipient instead.
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
postCustomersCustomerBankAccountsIdResponseBody200Customer :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants),
    -- | cvc_check: If a CVC was provided, results of the check: \`pass\`, \`fail\`, \`unavailable\`, or \`unchecked\`. A result of unchecked indicates that CVC was provided but hasn\'t been checked yet. Checks are typically performed when attaching a card to a Customer object, or when creating a charge. For more details, see [Check if a card is valid without a charge](https:\/\/support.stripe.com\/questions\/check-if-a-card-is-valid-without-a-charge).
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200CvcCheck :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | default_for_currency: Whether this card is the default external account for its currency.
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Bool
postCustomersCustomerBankAccountsIdResponseBody200DefaultForCurrency :: (GHC.Maybe.Maybe GHC.Types.Bool),
    -- | dynamic_last4: (For tokenized numbers only.) The last four digits of the device account number.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200DynamicLast4 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | eps
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeEps
postCustomersCustomerBankAccountsIdResponseBody200Eps :: (GHC.Maybe.Maybe SourceTypeEps),
    -- | exp_month: Two-digit number representing the card\'s expiration month.
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200ExpMonth :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | exp_year: Four-digit number representing the card\'s expiration year.
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200ExpYear :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | fingerprint: Uniquely identifies this particular card number. You can use this attribute to check whether two customers who’ve signed up with you are using the same card number, for example. For payment methods that tokenize card information (Apple Pay, Google Pay), the tokenized number might be provided instead of the underlying card number.
    --
    -- *Starting May 1, 2021, card fingerprint in India for Connect will change to allow two fingerprints for the same card --- one for India and one for the rest of the world.*
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Fingerprint :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | flow: The authentication \`flow\` of the source. \`flow\` is one of \`redirect\`, \`receiver\`, \`code_verification\`, \`none\`.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Flow :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | funding: Card funding type. Can be \`credit\`, \`debit\`, \`prepaid\`, or \`unknown\`.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Funding :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | giropay
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeGiropay
postCustomersCustomerBankAccountsIdResponseBody200Giropay :: (GHC.Maybe.Maybe SourceTypeGiropay),
    -- | id: Unique identifier for the object.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Id :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | ideal
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeIdeal
postCustomersCustomerBankAccountsIdResponseBody200Ideal :: (GHC.Maybe.Maybe SourceTypeIdeal),
    -- | klarna
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeKlarna
postCustomersCustomerBankAccountsIdResponseBody200Klarna :: (GHC.Maybe.Maybe SourceTypeKlarna),
    -- | last4: The last four digits of the card.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Last4 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | livemode: Has the value \`true\` if the object exists in live mode or the value \`false\` if the object exists in test mode.
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Bool
postCustomersCustomerBankAccountsIdResponseBody200Livemode :: (GHC.Maybe.Maybe GHC.Types.Bool),
    -- | 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.
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Object
postCustomersCustomerBankAccountsIdResponseBody200Metadata :: (GHC.Maybe.Maybe Data.Aeson.Types.Internal.Object),
    -- | multibanco
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeMultibanco
postCustomersCustomerBankAccountsIdResponseBody200Multibanco :: (GHC.Maybe.Maybe SourceTypeMultibanco),
    -- | name: Cardholder name.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Name :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | owner: Information about the owner of the payment instrument that may be used or required by particular source types.
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
postCustomersCustomerBankAccountsIdResponseBody200Owner :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'),
    -- | p24
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeP24
postCustomersCustomerBankAccountsIdResponseBody200P24 :: (GHC.Maybe.Maybe SourceTypeP24),
    -- | receiver:
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceReceiverFlow
postCustomersCustomerBankAccountsIdResponseBody200Receiver :: (GHC.Maybe.Maybe SourceReceiverFlow),
    -- | recipient: The recipient that this card belongs to. This attribute will not be in the card object if the card belongs to a customer or account instead.
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
postCustomersCustomerBankAccountsIdResponseBody200Recipient :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants),
    -- | redirect:
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceRedirectFlow
postCustomersCustomerBankAccountsIdResponseBody200Redirect :: (GHC.Maybe.Maybe SourceRedirectFlow),
    -- | routing_number: The routing transit number for the bank account.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200RoutingNumber :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | sepa_debit
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeSepaDebit
postCustomersCustomerBankAccountsIdResponseBody200SepaDebit :: (GHC.Maybe.Maybe SourceTypeSepaDebit),
    -- | sofort
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeSofort
postCustomersCustomerBankAccountsIdResponseBody200Sofort :: (GHC.Maybe.Maybe SourceTypeSofort),
    -- | source_order:
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceOrder
postCustomersCustomerBankAccountsIdResponseBody200SourceOrder :: (GHC.Maybe.Maybe SourceOrder),
    -- | statement_descriptor: Extra information about a source. This will appear on your customer\'s statement every time you charge the source.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200StatementDescriptor :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | status: For bank accounts, possible values are \`new\`, \`validated\`, \`verified\`, \`verification_failed\`, or \`errored\`. A bank account that hasn\'t had any activity or validation performed is \`new\`. If Stripe can determine that the bank account exists, its status will be \`validated\`. Note that there often isn’t enough information to know (e.g., for smaller credit unions), and the validation is not always run. If customer bank account verification has succeeded, the bank account status will be \`verified\`. If the verification failed for any reason, such as microdeposit failure, the status will be \`verification_failed\`. If a transfer sent to this bank account fails, we\'ll set the status to \`errored\` and will not continue to send transfers until the bank details are updated.
    --
    -- For external accounts, possible values are \`new\` and \`errored\`. Validations aren\'t run against external accounts because they\'re only used for payouts. This means the other statuses don\'t apply. If a transfer fails, the status is set to \`errored\` and transfers are stopped until account details are updated.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Status :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | three_d_secure
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeThreeDSecure
postCustomersCustomerBankAccountsIdResponseBody200ThreeDSecure :: (GHC.Maybe.Maybe SourceTypeThreeDSecure),
    -- | tokenization_method: If the card number is tokenized, this is the method that was used. Can be \`android_pay\` (includes Google Pay), \`apple_pay\`, \`masterpass\`, \`visa_checkout\`, or null.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200TokenizationMethod :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | type: The \`type\` of the source. The \`type\` is a payment method, one of \`ach_credit_transfer\`, \`ach_debit\`, \`alipay\`, \`bancontact\`, \`card\`, \`card_present\`, \`eps\`, \`giropay\`, \`ideal\`, \`multibanco\`, \`klarna\`, \`p24\`, \`sepa_debit\`, \`sofort\`, \`three_d_secure\`, or \`wechat\`. An additional hash is included on the source with a name matching this value. It contains additional information specific to the [payment method](https:\/\/stripe.com\/docs\/sources) used.
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
postCustomersCustomerBankAccountsIdResponseBody200Type :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'),
    -- | usage: Either \`reusable\` or \`single_use\`. Whether this source should be reusable or not. Some source types may or may not be reusable by construction, while others may leave the option at creation. If an incompatible value is passed, an error will be returned.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Usage :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | wechat
    PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeWechat
postCustomersCustomerBankAccountsIdResponseBody200Wechat :: (GHC.Maybe.Maybe SourceTypeWechat)
  }
  deriving
    ( Int
-> PostCustomersCustomerBankAccountsIdResponseBody200
-> String
-> String
[PostCustomersCustomerBankAccountsIdResponseBody200]
-> String -> String
PostCustomersCustomerBankAccountsIdResponseBody200 -> String
(Int
 -> PostCustomersCustomerBankAccountsIdResponseBody200
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsIdResponseBody200 -> String)
-> ([PostCustomersCustomerBankAccountsIdResponseBody200]
    -> String -> String)
-> Show PostCustomersCustomerBankAccountsIdResponseBody200
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsIdResponseBody200]
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsIdResponseBody200]
-> String -> String
show :: PostCustomersCustomerBankAccountsIdResponseBody200 -> String
$cshow :: PostCustomersCustomerBankAccountsIdResponseBody200 -> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerBankAccountsIdResponseBody200
-> PostCustomersCustomerBankAccountsIdResponseBody200 -> Bool
(PostCustomersCustomerBankAccountsIdResponseBody200
 -> PostCustomersCustomerBankAccountsIdResponseBody200 -> Bool)
-> (PostCustomersCustomerBankAccountsIdResponseBody200
    -> PostCustomersCustomerBankAccountsIdResponseBody200 -> Bool)
-> Eq PostCustomersCustomerBankAccountsIdResponseBody200
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsIdResponseBody200
-> PostCustomersCustomerBankAccountsIdResponseBody200 -> Bool
$c/= :: PostCustomersCustomerBankAccountsIdResponseBody200
-> PostCustomersCustomerBankAccountsIdResponseBody200 -> Bool
== :: PostCustomersCustomerBankAccountsIdResponseBody200
-> PostCustomersCustomerBankAccountsIdResponseBody200 -> Bool
$c== :: PostCustomersCustomerBankAccountsIdResponseBody200
-> PostCustomersCustomerBankAccountsIdResponseBody200 -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsIdResponseBody200 where
  toJSON :: PostCustomersCustomerBankAccountsIdResponseBody200 -> Value
toJSON PostCustomersCustomerBankAccountsIdResponseBody200
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"account" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
postCustomersCustomerBankAccountsIdResponseBody200Account PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"account_holder_name" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AccountHolderName PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"account_holder_type" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AccountHolderType PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"ach_credit_transfer" Text -> Maybe SourceTypeAchCreditTransfer -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeAchCreditTransfer
postCustomersCustomerBankAccountsIdResponseBody200AchCreditTransfer PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"ach_debit" Text -> Maybe SourceTypeAchDebit -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeAchDebit
postCustomersCustomerBankAccountsIdResponseBody200AchDebit PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"acss_debit" Text -> Maybe SourceTypeAcssDebit -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeAcssDebit
postCustomersCustomerBankAccountsIdResponseBody200AcssDebit PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_city" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressCity PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressCountry PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressLine1 PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_line1_check" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressLine1Check PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressLine2 PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressState PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressZip PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_zip_check" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressZipCheck PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"alipay" Text -> Maybe SourceTypeAlipay -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeAlipay
postCustomersCustomerBankAccountsIdResponseBody200Alipay PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"amount" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200Amount PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"au_becs_debit" Text -> Maybe SourceTypeAuBecsDebit -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeAuBecsDebit
postCustomersCustomerBankAccountsIdResponseBody200AuBecsDebit PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"available_payout_methods" Text
-> Maybe
     [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe
     [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
postCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"bancontact" Text -> Maybe SourceTypeBancontact -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeBancontact
postCustomersCustomerBankAccountsIdResponseBody200Bancontact PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"bank_name" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200BankName PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"brand" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Brand PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"card" Text -> Maybe SourceTypeCard -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeCard
postCustomersCustomerBankAccountsIdResponseBody200Card PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"card_present" Text -> Maybe SourceTypeCardPresent -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeCardPresent
postCustomersCustomerBankAccountsIdResponseBody200CardPresent PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"client_secret" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200ClientSecret PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"code_verification" Text -> Maybe SourceCodeVerificationFlow -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceCodeVerificationFlow
postCustomersCustomerBankAccountsIdResponseBody200CodeVerification PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"country" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Country PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"created" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200Created PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Currency PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"customer" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
postCustomersCustomerBankAccountsIdResponseBody200Customer PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"cvc_check" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200CvcCheck PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"default_for_currency" Text -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Bool
postCustomersCustomerBankAccountsIdResponseBody200DefaultForCurrency PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"dynamic_last4" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200DynamicLast4 PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"eps" Text -> Maybe SourceTypeEps -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeEps
postCustomersCustomerBankAccountsIdResponseBody200Eps PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"exp_month" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200ExpMonth PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"exp_year" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200ExpYear PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"fingerprint" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Fingerprint PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"flow" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Flow PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"funding" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Funding PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"giropay" Text -> Maybe SourceTypeGiropay -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeGiropay
postCustomersCustomerBankAccountsIdResponseBody200Giropay PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"id" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Id PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"ideal" Text -> Maybe SourceTypeIdeal -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeIdeal
postCustomersCustomerBankAccountsIdResponseBody200Ideal PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"klarna" Text -> Maybe SourceTypeKlarna -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeKlarna
postCustomersCustomerBankAccountsIdResponseBody200Klarna PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"last4" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Last4 PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"livemode" Text -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Bool
postCustomersCustomerBankAccountsIdResponseBody200Livemode PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Object
postCustomersCustomerBankAccountsIdResponseBody200Metadata PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"multibanco" Text -> Maybe SourceTypeMultibanco -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeMultibanco
postCustomersCustomerBankAccountsIdResponseBody200Multibanco PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Name PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"owner" Text
-> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
postCustomersCustomerBankAccountsIdResponseBody200Owner PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"p24" Text -> Maybe SourceTypeP24 -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeP24
postCustomersCustomerBankAccountsIdResponseBody200P24 PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"receiver" Text -> Maybe SourceReceiverFlow -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceReceiverFlow
postCustomersCustomerBankAccountsIdResponseBody200Receiver PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"recipient" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
postCustomersCustomerBankAccountsIdResponseBody200Recipient PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"redirect" Text -> Maybe SourceRedirectFlow -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceRedirectFlow
postCustomersCustomerBankAccountsIdResponseBody200Redirect PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200RoutingNumber PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"sepa_debit" Text -> Maybe SourceTypeSepaDebit -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeSepaDebit
postCustomersCustomerBankAccountsIdResponseBody200SepaDebit PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"sofort" Text -> Maybe SourceTypeSofort -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeSofort
postCustomersCustomerBankAccountsIdResponseBody200Sofort PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"source_order" Text -> Maybe SourceOrder -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceOrder
postCustomersCustomerBankAccountsIdResponseBody200SourceOrder PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"statement_descriptor" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200StatementDescriptor PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"status" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Status PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"three_d_secure" Text -> Maybe SourceTypeThreeDSecure -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeThreeDSecure
postCustomersCustomerBankAccountsIdResponseBody200ThreeDSecure PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"tokenization_method" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200TokenizationMethod PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"type" Text
-> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
postCustomersCustomerBankAccountsIdResponseBody200Type PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"usage" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Usage PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"wechat" Text -> Maybe SourceTypeWechat -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeWechat
postCustomersCustomerBankAccountsIdResponseBody200Wechat PostCustomersCustomerBankAccountsIdResponseBody200
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"object" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Text -> Value
Data.Aeson.Types.Internal.String Text
"card" Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerBankAccountsIdResponseBody200 -> Encoding
toEncoding PostCustomersCustomerBankAccountsIdResponseBody200
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"account" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
postCustomersCustomerBankAccountsIdResponseBody200Account PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"account_holder_name" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AccountHolderName PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"account_holder_type" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AccountHolderType PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"ach_credit_transfer" Text -> Maybe SourceTypeAchCreditTransfer -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeAchCreditTransfer
postCustomersCustomerBankAccountsIdResponseBody200AchCreditTransfer PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"ach_debit" Text -> Maybe SourceTypeAchDebit -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeAchDebit
postCustomersCustomerBankAccountsIdResponseBody200AchDebit PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"acss_debit" Text -> Maybe SourceTypeAcssDebit -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeAcssDebit
postCustomersCustomerBankAccountsIdResponseBody200AcssDebit PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_city" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressCity PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressCountry PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressLine1 PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_line1_check" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressLine1Check PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressLine2 PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressState PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressZip PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_zip_check" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressZipCheck PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"alipay" Text -> Maybe SourceTypeAlipay -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeAlipay
postCustomersCustomerBankAccountsIdResponseBody200Alipay PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"amount" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200Amount PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"au_becs_debit" Text -> Maybe SourceTypeAuBecsDebit -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeAuBecsDebit
postCustomersCustomerBankAccountsIdResponseBody200AuBecsDebit PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"available_payout_methods" Text
-> Maybe
     [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe
     [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
postCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"bancontact" Text -> Maybe SourceTypeBancontact -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeBancontact
postCustomersCustomerBankAccountsIdResponseBody200Bancontact PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"bank_name" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200BankName PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"brand" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Brand PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"card" Text -> Maybe SourceTypeCard -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeCard
postCustomersCustomerBankAccountsIdResponseBody200Card PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"card_present" Text -> Maybe SourceTypeCardPresent -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeCardPresent
postCustomersCustomerBankAccountsIdResponseBody200CardPresent PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"client_secret" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200ClientSecret PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"code_verification" Text -> Maybe SourceCodeVerificationFlow -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceCodeVerificationFlow
postCustomersCustomerBankAccountsIdResponseBody200CodeVerification PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"country" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Country PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"created" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200Created PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Currency PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"customer" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
postCustomersCustomerBankAccountsIdResponseBody200Customer PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"cvc_check" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200CvcCheck PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"default_for_currency" Text -> Maybe Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Bool
postCustomersCustomerBankAccountsIdResponseBody200DefaultForCurrency PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"dynamic_last4" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200DynamicLast4 PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"eps" Text -> Maybe SourceTypeEps -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeEps
postCustomersCustomerBankAccountsIdResponseBody200Eps PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"exp_month" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200ExpMonth PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"exp_year" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200ExpYear PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"fingerprint" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Fingerprint PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"flow" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Flow PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"funding" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Funding PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"giropay" Text -> Maybe SourceTypeGiropay -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeGiropay
postCustomersCustomerBankAccountsIdResponseBody200Giropay PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"id" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Id PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"ideal" Text -> Maybe SourceTypeIdeal -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeIdeal
postCustomersCustomerBankAccountsIdResponseBody200Ideal PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"klarna" Text -> Maybe SourceTypeKlarna -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeKlarna
postCustomersCustomerBankAccountsIdResponseBody200Klarna PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"last4" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Last4 PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"livemode" Text -> Maybe Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Bool
postCustomersCustomerBankAccountsIdResponseBody200Livemode PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Object
postCustomersCustomerBankAccountsIdResponseBody200Metadata PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"multibanco" Text -> Maybe SourceTypeMultibanco -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeMultibanco
postCustomersCustomerBankAccountsIdResponseBody200Multibanco PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Name PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"owner" Text
-> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
postCustomersCustomerBankAccountsIdResponseBody200Owner PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"p24" Text -> Maybe SourceTypeP24 -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeP24
postCustomersCustomerBankAccountsIdResponseBody200P24 PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"receiver" Text -> Maybe SourceReceiverFlow -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceReceiverFlow
postCustomersCustomerBankAccountsIdResponseBody200Receiver PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"recipient" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
postCustomersCustomerBankAccountsIdResponseBody200Recipient PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"redirect" Text -> Maybe SourceRedirectFlow -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceRedirectFlow
postCustomersCustomerBankAccountsIdResponseBody200Redirect PostCustomersCustomerBankAccountsIdResponseBody200
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..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200RoutingNumber PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"sepa_debit" Text -> Maybe SourceTypeSepaDebit -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeSepaDebit
postCustomersCustomerBankAccountsIdResponseBody200SepaDebit PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"sofort" Text -> Maybe SourceTypeSofort -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeSofort
postCustomersCustomerBankAccountsIdResponseBody200Sofort PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"source_order" Text -> Maybe SourceOrder -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceOrder
postCustomersCustomerBankAccountsIdResponseBody200SourceOrder PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"statement_descriptor" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200StatementDescriptor PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"status" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Status PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"three_d_secure" Text -> Maybe SourceTypeThreeDSecure -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeThreeDSecure
postCustomersCustomerBankAccountsIdResponseBody200ThreeDSecure PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"tokenization_method" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200TokenizationMethod PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"type" Text
-> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
postCustomersCustomerBankAccountsIdResponseBody200Type PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"usage" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200 -> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Usage PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"wechat" Text -> Maybe SourceTypeWechat -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200
-> Maybe SourceTypeWechat
postCustomersCustomerBankAccountsIdResponseBody200Wechat PostCustomersCustomerBankAccountsIdResponseBody200
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"object" Text -> Value -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Text -> Value
Data.Aeson.Types.Internal.String Text
"card"))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsIdResponseBody200 where
  parseJSON :: Value -> Parser PostCustomersCustomerBankAccountsIdResponseBody200
parseJSON = String
-> (Object
    -> Parser PostCustomersCustomerBankAccountsIdResponseBody200)
-> Value
-> Parser PostCustomersCustomerBankAccountsIdResponseBody200
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerBankAccountsIdResponseBody200" (\Object
obj -> (((((((((((((((((((((((((((((((((((((((((((((((((((((((((((((((Maybe
   PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
 -> Maybe Text
 -> Maybe Text
 -> Maybe SourceTypeAchCreditTransfer
 -> Maybe SourceTypeAchDebit
 -> Maybe SourceTypeAcssDebit
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe SourceTypeAlipay
 -> Maybe Int
 -> Maybe SourceTypeAuBecsDebit
 -> Maybe
      [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
 -> Maybe SourceTypeBancontact
 -> Maybe Text
 -> Maybe Text
 -> Maybe SourceTypeCard
 -> Maybe SourceTypeCardPresent
 -> Maybe Text
 -> Maybe SourceCodeVerificationFlow
 -> Maybe Text
 -> Maybe Int
 -> Maybe Text
 -> Maybe
      PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
 -> Maybe Text
 -> Maybe Bool
 -> Maybe Text
 -> Maybe SourceTypeEps
 -> Maybe Int
 -> Maybe Int
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe SourceTypeGiropay
 -> Maybe Text
 -> Maybe SourceTypeIdeal
 -> Maybe SourceTypeKlarna
 -> Maybe Text
 -> Maybe Bool
 -> Maybe Object
 -> Maybe SourceTypeMultibanco
 -> Maybe Text
 -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
 -> Maybe SourceTypeP24
 -> Maybe SourceReceiverFlow
 -> Maybe
      PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
 -> Maybe SourceRedirectFlow
 -> Maybe Text
 -> Maybe SourceTypeSepaDebit
 -> Maybe SourceTypeSofort
 -> Maybe SourceOrder
 -> Maybe Text
 -> Maybe Text
 -> Maybe SourceTypeThreeDSecure
 -> Maybe Text
 -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
 -> Maybe Text
 -> Maybe SourceTypeWechat
 -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeAchCreditTransfer
      -> Maybe SourceTypeAchDebit
      -> Maybe SourceTypeAcssDebit
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeAlipay
      -> Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe
  PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> Maybe Text
-> Maybe Text
-> Maybe SourceTypeAchCreditTransfer
-> Maybe SourceTypeAchDebit
-> Maybe SourceTypeAcssDebit
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe SourceTypeAlipay
-> Maybe Int
-> Maybe SourceTypeAuBecsDebit
-> Maybe
     [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
-> Maybe SourceTypeBancontact
-> Maybe Text
-> Maybe Text
-> Maybe SourceTypeCard
-> Maybe SourceTypeCardPresent
-> Maybe Text
-> Maybe SourceCodeVerificationFlow
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe SourceTypeEps
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe SourceTypeGiropay
-> Maybe Text
-> Maybe SourceTypeIdeal
-> Maybe SourceTypeKlarna
-> Maybe Text
-> Maybe Bool
-> Maybe Object
-> Maybe SourceTypeMultibanco
-> Maybe Text
-> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe SourceTypeP24
-> Maybe SourceReceiverFlow
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> Maybe SourceRedirectFlow
-> Maybe Text
-> Maybe SourceTypeSepaDebit
-> Maybe SourceTypeSofort
-> Maybe SourceOrder
-> Maybe Text
-> Maybe Text
-> Maybe SourceTypeThreeDSecure
-> Maybe Text
-> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
-> Maybe Text
-> Maybe SourceTypeWechat
-> PostCustomersCustomerBankAccountsIdResponseBody200
PostCustomersCustomerBankAccountsIdResponseBody200 Parser
  (Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeAchCreditTransfer
   -> Maybe SourceTypeAchDebit
   -> Maybe SourceTypeAcssDebit
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeAlipay
   -> Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeAchCreditTransfer
      -> Maybe SourceTypeAchDebit
      -> Maybe SourceTypeAcssDebit
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeAlipay
      -> Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"account")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeAchCreditTransfer
   -> Maybe SourceTypeAchDebit
   -> Maybe SourceTypeAcssDebit
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeAlipay
   -> Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe SourceTypeAchCreditTransfer
      -> Maybe SourceTypeAchDebit
      -> Maybe SourceTypeAcssDebit
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeAlipay
      -> Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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 Text
   -> Maybe SourceTypeAchCreditTransfer
   -> Maybe SourceTypeAchDebit
   -> Maybe SourceTypeAcssDebit
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeAlipay
   -> Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe SourceTypeAchCreditTransfer
      -> Maybe SourceTypeAchDebit
      -> Maybe SourceTypeAcssDebit
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeAlipay
      -> Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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_type")) Parser
  (Maybe SourceTypeAchCreditTransfer
   -> Maybe SourceTypeAchDebit
   -> Maybe SourceTypeAcssDebit
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeAlipay
   -> Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeAchCreditTransfer)
-> Parser
     (Maybe SourceTypeAchDebit
      -> Maybe SourceTypeAcssDebit
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeAlipay
      -> Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeAchCreditTransfer)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"ach_credit_transfer")) Parser
  (Maybe SourceTypeAchDebit
   -> Maybe SourceTypeAcssDebit
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeAlipay
   -> Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeAchDebit)
-> Parser
     (Maybe SourceTypeAcssDebit
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeAlipay
      -> Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeAchDebit)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"ach_debit")) Parser
  (Maybe SourceTypeAcssDebit
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeAlipay
   -> Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeAcssDebit)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeAlipay
      -> Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeAcssDebit)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"acss_debit")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeAlipay
   -> Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeAlipay
      -> Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
   -> Maybe Text
   -> Maybe SourceTypeAlipay
   -> Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeAlipay
      -> Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
   -> Maybe Text
   -> Maybe SourceTypeAlipay
   -> Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeAlipay
      -> Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
   -> Maybe Text
   -> Maybe SourceTypeAlipay
   -> Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeAlipay
      -> Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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_check")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeAlipay
   -> Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeAlipay
      -> Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
   -> Maybe SourceTypeAlipay
   -> Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeAlipay
      -> Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
   -> Maybe SourceTypeAlipay
   -> Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe SourceTypeAlipay
      -> Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
   -> Maybe SourceTypeAlipay
   -> Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe SourceTypeAlipay
      -> Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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_check")) Parser
  (Maybe SourceTypeAlipay
   -> Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeAlipay)
-> Parser
     (Maybe Int
      -> Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeAlipay)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"alipay")) Parser
  (Maybe Int
   -> Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Int)
-> Parser
     (Maybe SourceTypeAuBecsDebit
      -> Maybe
           [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"amount")) Parser
  (Maybe SourceTypeAuBecsDebit
   -> Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeAuBecsDebit)
-> Parser
     (Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
      -> Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeAuBecsDebit)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"au_becs_debit")) Parser
  (Maybe
     [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
   -> Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser
     (Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'])
-> Parser
     (Maybe SourceTypeBancontact
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"available_payout_methods")) Parser
  (Maybe SourceTypeBancontact
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeBancontact)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeBancontact)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"bancontact")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
"bank_name")) Parser
  (Maybe Text
   -> Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe SourceTypeCard
      -> Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
"brand")) Parser
  (Maybe SourceTypeCard
   -> Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeCard)
-> Parser
     (Maybe SourceTypeCardPresent
      -> Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeCard)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"card")) Parser
  (Maybe SourceTypeCardPresent
   -> Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeCardPresent)
-> Parser
     (Maybe Text
      -> Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeCardPresent)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"card_present")) Parser
  (Maybe Text
   -> Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe SourceCodeVerificationFlow
      -> Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
"client_secret")) Parser
  (Maybe SourceCodeVerificationFlow
   -> Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceCodeVerificationFlow)
-> Parser
     (Maybe Text
      -> Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceCodeVerificationFlow)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"code_verification")) Parser
  (Maybe Text
   -> Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe Int
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
"country")) Parser
  (Maybe Int
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Int)
-> Parser
     (Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"created")) Parser
  (Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants)
-> Parser
     (Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"customer")) Parser
  (Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe Bool
      -> Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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_check")) Parser
  (Maybe Bool
   -> Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Bool)
-> Parser
     (Maybe Text
      -> Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"default_for_currency")) Parser
  (Maybe Text
   -> Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe SourceTypeEps
      -> Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
"dynamic_last4")) Parser
  (Maybe SourceTypeEps
   -> Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeEps)
-> Parser
     (Maybe Int
      -> Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeEps)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"eps")) Parser
  (Maybe Int
   -> Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Int)
-> Parser
     (Maybe Int
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"exp_month")) Parser
  (Maybe Int
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Int)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"exp_year")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
"fingerprint")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
"flow")) Parser
  (Maybe Text
   -> Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe SourceTypeGiropay
      -> Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
"funding")) Parser
  (Maybe SourceTypeGiropay
   -> Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeGiropay)
-> Parser
     (Maybe Text
      -> Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeGiropay)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"giropay")) Parser
  (Maybe Text
   -> Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe SourceTypeIdeal
      -> Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
"id")) Parser
  (Maybe SourceTypeIdeal
   -> Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeIdeal)
-> Parser
     (Maybe SourceTypeKlarna
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeIdeal)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"ideal")) Parser
  (Maybe SourceTypeKlarna
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeKlarna)
-> Parser
     (Maybe Text
      -> Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeKlarna)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"klarna")) Parser
  (Maybe Text
   -> Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe Bool
      -> Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
"last4")) Parser
  (Maybe Bool
   -> Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Bool)
-> Parser
     (Maybe Object
      -> Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"livemode")) Parser
  (Maybe Object
   -> Maybe SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Object)
-> Parser
     (Maybe SourceTypeMultibanco
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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 SourceTypeMultibanco
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeMultibanco)
-> Parser
     (Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeMultibanco)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"multibanco")) Parser
  (Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
      -> Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
  (Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
   -> Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser
     (Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner')
-> Parser
     (Maybe SourceTypeP24
      -> Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"owner")) Parser
  (Maybe SourceTypeP24
   -> Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeP24)
-> Parser
     (Maybe SourceReceiverFlow
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeP24)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"p24")) Parser
  (Maybe SourceReceiverFlow
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceReceiverFlow)
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
      -> Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceReceiverFlow)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"receiver")) Parser
  (Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
   -> Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants)
-> Parser
     (Maybe SourceRedirectFlow
      -> Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"recipient")) Parser
  (Maybe SourceRedirectFlow
   -> Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceRedirectFlow)
-> Parser
     (Maybe Text
      -> Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceRedirectFlow)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"redirect")) Parser
  (Maybe Text
   -> Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe SourceTypeSepaDebit
      -> Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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")) Parser
  (Maybe SourceTypeSepaDebit
   -> Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeSepaDebit)
-> Parser
     (Maybe SourceTypeSofort
      -> Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeSepaDebit)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"sepa_debit")) Parser
  (Maybe SourceTypeSofort
   -> Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeSofort)
-> Parser
     (Maybe SourceOrder
      -> Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeSofort)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"sofort")) Parser
  (Maybe SourceOrder
   -> Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceOrder)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceOrder)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"source_order")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"statement_descriptor")) Parser
  (Maybe Text
   -> Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe SourceTypeThreeDSecure
      -> Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
"status")) Parser
  (Maybe SourceTypeThreeDSecure
   -> Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeThreeDSecure)
-> Parser
     (Maybe Text
      -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeThreeDSecure)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"three_d_secure")) Parser
  (Maybe Text
   -> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
      -> Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
"tokenization_method")) Parser
  (Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
   -> Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser
     (Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type')
-> Parser
     (Maybe Text
      -> Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"type")) Parser
  (Maybe Text
   -> Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe Text)
-> Parser
     (Maybe SourceTypeWechat
      -> PostCustomersCustomerBankAccountsIdResponseBody200)
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
"usage")) Parser
  (Maybe SourceTypeWechat
   -> PostCustomersCustomerBankAccountsIdResponseBody200)
-> Parser (Maybe SourceTypeWechat)
-> Parser PostCustomersCustomerBankAccountsIdResponseBody200
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SourceTypeWechat)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"wechat"))

-- | Create a new 'PostCustomersCustomerBankAccountsIdResponseBody200' with all required fields.
mkPostCustomersCustomerBankAccountsIdResponseBody200 :: PostCustomersCustomerBankAccountsIdResponseBody200
mkPostCustomersCustomerBankAccountsIdResponseBody200 :: PostCustomersCustomerBankAccountsIdResponseBody200
mkPostCustomersCustomerBankAccountsIdResponseBody200 =
  PostCustomersCustomerBankAccountsIdResponseBody200 :: Maybe
  PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> Maybe Text
-> Maybe Text
-> Maybe SourceTypeAchCreditTransfer
-> Maybe SourceTypeAchDebit
-> Maybe SourceTypeAcssDebit
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe SourceTypeAlipay
-> Maybe Int
-> Maybe SourceTypeAuBecsDebit
-> Maybe
     [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
-> Maybe SourceTypeBancontact
-> Maybe Text
-> Maybe Text
-> Maybe SourceTypeCard
-> Maybe SourceTypeCardPresent
-> Maybe Text
-> Maybe SourceCodeVerificationFlow
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe SourceTypeEps
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe SourceTypeGiropay
-> Maybe Text
-> Maybe SourceTypeIdeal
-> Maybe SourceTypeKlarna
-> Maybe Text
-> Maybe Bool
-> Maybe Object
-> Maybe SourceTypeMultibanco
-> Maybe Text
-> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe SourceTypeP24
-> Maybe SourceReceiverFlow
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> Maybe SourceRedirectFlow
-> Maybe Text
-> Maybe SourceTypeSepaDebit
-> Maybe SourceTypeSofort
-> Maybe SourceOrder
-> Maybe Text
-> Maybe Text
-> Maybe SourceTypeThreeDSecure
-> Maybe Text
-> Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
-> Maybe Text
-> Maybe SourceTypeWechat
-> PostCustomersCustomerBankAccountsIdResponseBody200
PostCustomersCustomerBankAccountsIdResponseBody200
    { postCustomersCustomerBankAccountsIdResponseBody200Account :: Maybe
  PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
postCustomersCustomerBankAccountsIdResponseBody200Account = Maybe
  PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200AccountHolderName :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AccountHolderName = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200AccountHolderType :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AccountHolderType = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200AchCreditTransfer :: Maybe SourceTypeAchCreditTransfer
postCustomersCustomerBankAccountsIdResponseBody200AchCreditTransfer = Maybe SourceTypeAchCreditTransfer
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200AchDebit :: Maybe SourceTypeAchDebit
postCustomersCustomerBankAccountsIdResponseBody200AchDebit = Maybe SourceTypeAchDebit
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200AcssDebit :: Maybe SourceTypeAcssDebit
postCustomersCustomerBankAccountsIdResponseBody200AcssDebit = Maybe SourceTypeAcssDebit
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200AddressCity :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressCity = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200AddressCountry :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressCountry = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200AddressLine1 :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressLine1 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200AddressLine1Check :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressLine1Check = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200AddressLine2 :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressLine2 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200AddressState :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressState = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200AddressZip :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressZip = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200AddressZipCheck :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200AddressZipCheck = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Alipay :: Maybe SourceTypeAlipay
postCustomersCustomerBankAccountsIdResponseBody200Alipay = Maybe SourceTypeAlipay
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Amount :: Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200Amount = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200AuBecsDebit :: Maybe SourceTypeAuBecsDebit
postCustomersCustomerBankAccountsIdResponseBody200AuBecsDebit = Maybe SourceTypeAuBecsDebit
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods :: Maybe
  [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
postCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods = Maybe
  [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Bancontact :: Maybe SourceTypeBancontact
postCustomersCustomerBankAccountsIdResponseBody200Bancontact = Maybe SourceTypeBancontact
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200BankName :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200BankName = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Brand :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Brand = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Card :: Maybe SourceTypeCard
postCustomersCustomerBankAccountsIdResponseBody200Card = Maybe SourceTypeCard
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200CardPresent :: Maybe SourceTypeCardPresent
postCustomersCustomerBankAccountsIdResponseBody200CardPresent = Maybe SourceTypeCardPresent
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200ClientSecret :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200ClientSecret = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200CodeVerification :: Maybe SourceCodeVerificationFlow
postCustomersCustomerBankAccountsIdResponseBody200CodeVerification = Maybe SourceCodeVerificationFlow
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Country :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Country = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Created :: Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200Created = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Currency :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Currency = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Customer :: Maybe
  PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
postCustomersCustomerBankAccountsIdResponseBody200Customer = Maybe
  PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200CvcCheck :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200CvcCheck = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200DefaultForCurrency :: Maybe Bool
postCustomersCustomerBankAccountsIdResponseBody200DefaultForCurrency = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200DynamicLast4 :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200DynamicLast4 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Eps :: Maybe SourceTypeEps
postCustomersCustomerBankAccountsIdResponseBody200Eps = Maybe SourceTypeEps
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200ExpMonth :: Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200ExpMonth = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200ExpYear :: Maybe Int
postCustomersCustomerBankAccountsIdResponseBody200ExpYear = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Fingerprint :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Fingerprint = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Flow :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Flow = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Funding :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Funding = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Giropay :: Maybe SourceTypeGiropay
postCustomersCustomerBankAccountsIdResponseBody200Giropay = Maybe SourceTypeGiropay
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Id :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Id = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Ideal :: Maybe SourceTypeIdeal
postCustomersCustomerBankAccountsIdResponseBody200Ideal = Maybe SourceTypeIdeal
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Klarna :: Maybe SourceTypeKlarna
postCustomersCustomerBankAccountsIdResponseBody200Klarna = Maybe SourceTypeKlarna
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Last4 :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Last4 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Livemode :: Maybe Bool
postCustomersCustomerBankAccountsIdResponseBody200Livemode = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Metadata :: Maybe Object
postCustomersCustomerBankAccountsIdResponseBody200Metadata = Maybe Object
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Multibanco :: Maybe SourceTypeMultibanco
postCustomersCustomerBankAccountsIdResponseBody200Multibanco = Maybe SourceTypeMultibanco
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Name :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Name = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner :: Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
postCustomersCustomerBankAccountsIdResponseBody200Owner = Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200P24 :: Maybe SourceTypeP24
postCustomersCustomerBankAccountsIdResponseBody200P24 = Maybe SourceTypeP24
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Receiver :: Maybe SourceReceiverFlow
postCustomersCustomerBankAccountsIdResponseBody200Receiver = Maybe SourceReceiverFlow
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Recipient :: Maybe
  PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
postCustomersCustomerBankAccountsIdResponseBody200Recipient = Maybe
  PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Redirect :: Maybe SourceRedirectFlow
postCustomersCustomerBankAccountsIdResponseBody200Redirect = Maybe SourceRedirectFlow
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200RoutingNumber :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200RoutingNumber = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200SepaDebit :: Maybe SourceTypeSepaDebit
postCustomersCustomerBankAccountsIdResponseBody200SepaDebit = Maybe SourceTypeSepaDebit
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Sofort :: Maybe SourceTypeSofort
postCustomersCustomerBankAccountsIdResponseBody200Sofort = Maybe SourceTypeSofort
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200SourceOrder :: Maybe SourceOrder
postCustomersCustomerBankAccountsIdResponseBody200SourceOrder = Maybe SourceOrder
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200StatementDescriptor :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200StatementDescriptor = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Status :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Status = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200ThreeDSecure :: Maybe SourceTypeThreeDSecure
postCustomersCustomerBankAccountsIdResponseBody200ThreeDSecure = Maybe SourceTypeThreeDSecure
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200TokenizationMethod :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200TokenizationMethod = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Type :: Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
postCustomersCustomerBankAccountsIdResponseBody200Type = Maybe PostCustomersCustomerBankAccountsIdResponseBody200Type'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Usage :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Usage = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Wechat :: Maybe SourceTypeWechat
postCustomersCustomerBankAccountsIdResponseBody200Wechat = Maybe SourceTypeWechat
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the oneOf schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts\/{id}.POST.responses.200.content.application\/json.schema.anyOf.properties.account.anyOf@ in the specification.
--
-- The account this card belongs to. This attribute will not be in the card object if the card belongs to a customer or recipient instead.
data PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
  = PostCustomersCustomerBankAccountsIdResponseBody200Account'Text Data.Text.Internal.Text
  | PostCustomersCustomerBankAccountsIdResponseBody200Account'Account Account
  deriving (Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> String
-> String
[PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants]
-> String -> String
PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> String
(Int
 -> PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
    -> String)
-> ([PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants]
    -> String -> String)
-> Show
     PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants]
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants]
-> String -> String
show :: PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> String
$cshow :: PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> String
-> String
GHC.Show.Show, PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> Bool
(PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
 -> PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
 -> Bool)
-> (PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
    -> PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
    -> Bool)
-> Eq
     PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> Bool
$c/= :: PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> Bool
== :: PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> Bool
$c== :: PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> PostCustomersCustomerBankAccountsIdResponseBody200Account'Variants
-> Bool
GHC.Classes.Eq)

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

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

-- | Defines the enum schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts\/{id}.POST.responses.200.content.application\/json.schema.anyOf.properties.available_payout_methods.items@ in the specification.
data PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'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.
    PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"instant"@
    PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'EnumInstant
  | -- | Represents the JSON value @"standard"@
    PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'EnumStandard
  deriving (Int
-> PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> String
-> String
[PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
-> String -> String
PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> String
(Int
 -> PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
    -> String)
-> ([PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
    -> String -> String)
-> Show
     PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods']
-> String -> String
show :: PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> String
$cshow :: PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> String
-> String
GHC.Show.Show, PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> Bool
(PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
 -> PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
 -> Bool)
-> (PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
    -> PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
    -> Bool)
-> Eq
     PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> Bool
$c/= :: PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> Bool
== :: PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> Bool
$c== :: PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods' where
  toJSON :: PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> Value
toJSON (PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'Other Value
val) = Value
val
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'EnumInstant) = Value
"instant"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'EnumStandard) = Value
"standard"

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
parseJSON Value
val =
    PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
-> Parser
     PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
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
"instant" -> PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'EnumInstant
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"standard" -> PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'EnumStandard
            | Bool
GHC.Base.otherwise -> Value
-> PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'
PostCustomersCustomerBankAccountsIdResponseBody200AvailablePayoutMethods'Other Value
val
      )

-- | Defines the oneOf schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts\/{id}.POST.responses.200.content.application\/json.schema.anyOf.properties.customer.anyOf@ in the specification.
--
-- The customer that this card belongs to. This attribute will not be in the card object if the card belongs to an account or recipient instead.
data PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
  = PostCustomersCustomerBankAccountsIdResponseBody200Customer'Text Data.Text.Internal.Text
  | PostCustomersCustomerBankAccountsIdResponseBody200Customer'Customer Customer
  | PostCustomersCustomerBankAccountsIdResponseBody200Customer'DeletedCustomer DeletedCustomer
  deriving (Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> String
-> String
[PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants]
-> String -> String
PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> String
(Int
 -> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
    -> String)
-> ([PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants]
    -> String -> String)
-> Show
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants]
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants]
-> String -> String
show :: PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> String
$cshow :: PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> String
-> String
GHC.Show.Show, PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Bool
(PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
 -> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
 -> Bool)
-> (PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
    -> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
    -> Bool)
-> Eq
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Bool
$c/= :: PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Bool
== :: PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Bool
$c== :: PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Bool
GHC.Classes.Eq)

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

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
parseJSON Value
val = case (Text
-> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
PostCustomersCustomerBankAccountsIdResponseBody200Customer'Text (Text
 -> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants)
-> Result Text
-> Result
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'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
  PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Result
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Result
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((Customer
-> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
PostCustomersCustomerBankAccountsIdResponseBody200Customer'Customer (Customer
 -> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants)
-> Result Customer
-> Result
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Customer
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result
  PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Result
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Result
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((DeletedCustomer
-> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
PostCustomersCustomerBankAccountsIdResponseBody200Customer'DeletedCustomer (DeletedCustomer
 -> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants)
-> Result DeletedCustomer
-> Result
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result DeletedCustomer
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result
  PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Result
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Result
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched")) of
    Data.Aeson.Types.Internal.Success PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
a -> PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
-> Parser
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerBankAccountsIdResponseBody200Customer'Variants
a
    Data.Aeson.Types.Internal.Error String
a -> String
-> Parser
     PostCustomersCustomerBankAccountsIdResponseBody200Customer'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\/{id}.POST.responses.200.content.application\/json.schema.anyOf.properties.owner.anyOf@ in the specification.
--
-- Information about the owner of the payment instrument that may be used or required by particular source types.
data PostCustomersCustomerBankAccountsIdResponseBody200Owner' = PostCustomersCustomerBankAccountsIdResponseBody200Owner'
  { -- | address: Owner\'s address.
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'),
    -- | email: Owner\'s email address.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Email :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | name: Owner\'s full name.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Name :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | phone: Owner\'s phone number (including extension).
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Phone :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | verified_address: Verified owner\'s address. Verified values are verified or provided by the payment method directly (and if supported) at the time of authorization or settlement. They cannot be set or mutated.
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress :: (GHC.Maybe.Maybe PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'),
    -- | verified_email: Verified owner\'s email address. Verified values are verified or provided by the payment method directly (and if supported) at the time of authorization or settlement. They cannot be set or mutated.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedEmail :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | verified_name: Verified owner\'s full name. Verified values are verified or provided by the payment method directly (and if supported) at the time of authorization or settlement. They cannot be set or mutated.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedName :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | verified_phone: Verified owner\'s phone number (including extension). Verified values are verified or provided by the payment method directly (and if supported) at the time of authorization or settlement. They cannot be set or mutated.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedPhone :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> String
-> String
[PostCustomersCustomerBankAccountsIdResponseBody200Owner']
-> String -> String
PostCustomersCustomerBankAccountsIdResponseBody200Owner' -> String
(Int
 -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsIdResponseBody200Owner'
    -> String)
-> ([PostCustomersCustomerBankAccountsIdResponseBody200Owner']
    -> String -> String)
-> Show PostCustomersCustomerBankAccountsIdResponseBody200Owner'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsIdResponseBody200Owner']
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsIdResponseBody200Owner']
-> String -> String
show :: PostCustomersCustomerBankAccountsIdResponseBody200Owner' -> String
$cshow :: PostCustomersCustomerBankAccountsIdResponseBody200Owner' -> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner' -> Bool
(PostCustomersCustomerBankAccountsIdResponseBody200Owner'
 -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'
 -> Bool)
-> (PostCustomersCustomerBankAccountsIdResponseBody200Owner'
    -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'
    -> Bool)
-> Eq PostCustomersCustomerBankAccountsIdResponseBody200Owner'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner' -> Bool
$c/= :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner' -> Bool
== :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner' -> Bool
$c== :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner' -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsIdResponseBody200Owner' where
  toJSON :: PostCustomersCustomerBankAccountsIdResponseBody200Owner' -> Value
toJSON PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"address" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"email" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Email PostCustomersCustomerBankAccountsIdResponseBody200Owner'
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..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Name PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"phone" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Phone PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"verified_address" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"verified_email" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedEmail PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"verified_name" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedName PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"verified_phone" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedPhone PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Encoding
toEncoding PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"address" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"email" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Email PostCustomersCustomerBankAccountsIdResponseBody200Owner'
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..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Name PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"phone" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Phone PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"verified_address" Text
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"verified_email" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedEmail PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"verified_name" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedName PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"verified_phone" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedPhone PostCustomersCustomerBankAccountsIdResponseBody200Owner'
obj))))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsIdResponseBody200Owner' where
  parseJSON :: Value
-> Parser PostCustomersCustomerBankAccountsIdResponseBody200Owner'
parseJSON = String
-> (Object
    -> Parser PostCustomersCustomerBankAccountsIdResponseBody200Owner')
-> Value
-> Parser PostCustomersCustomerBankAccountsIdResponseBody200Owner'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerBankAccountsIdResponseBody200Owner'" (\Object
obj -> ((((((((Maybe
   PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe
      PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe
  PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'
PostCustomersCustomerBankAccountsIdResponseBody200Owner' Parser
  (Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"address")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
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
"email")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe
           PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
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
  (Maybe Text
   -> Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
-> Parser (Maybe Text)
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
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
"phone")) Parser
  (Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"verified_address")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
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
"verified_email")) Parser
  (Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
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
"verified_name")) Parser
  (Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner')
-> Parser (Maybe Text)
-> Parser PostCustomersCustomerBankAccountsIdResponseBody200Owner'
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
"verified_phone"))

-- | Create a new 'PostCustomersCustomerBankAccountsIdResponseBody200Owner'' with all required fields.
mkPostCustomersCustomerBankAccountsIdResponseBody200Owner' :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'
mkPostCustomersCustomerBankAccountsIdResponseBody200Owner' :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'
mkPostCustomersCustomerBankAccountsIdResponseBody200Owner' =
  PostCustomersCustomerBankAccountsIdResponseBody200Owner' :: Maybe
  PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'
PostCustomersCustomerBankAccountsIdResponseBody200Owner'
    { postCustomersCustomerBankAccountsIdResponseBody200Owner'Address :: Maybe
  PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address = Maybe
  PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'Email :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Email = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'Name :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Name = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'Phone :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Phone = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress :: Maybe
  PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress = Maybe
  PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedEmail :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedEmail = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedName :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedName = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedPhone :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedPhone = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts\/{id}.POST.responses.200.content.application\/json.schema.anyOf.properties.owner.anyOf.properties.address.anyOf@ in the specification.
--
-- Owner\\\'s address.
data PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address' = PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
  { -- | city: City, district, suburb, town, or village.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'City :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | country: Two-letter country code ([ISO 3166-1 alpha-2](https:\/\/en.wikipedia.org\/wiki\/ISO_3166-1_alpha-2)).
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'Country :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | line1: Address line 1 (e.g., street, PO Box, or company name).
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'Line1 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | line2: Address line 2 (e.g., apartment, suite, unit, or building).
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'Line2 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | postal_code: ZIP or postal code.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'PostalCode :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | state: State, county, province, or region.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'State :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> String
-> String
[PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address']
-> String -> String
PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> String
(Int
 -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
    -> String)
-> ([PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address']
    -> String -> String)
-> Show
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address']
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address']
-> String -> String
show :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> String
$cshow :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Bool
(PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
 -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
 -> Bool)
-> (PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
    -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
    -> Bool)
-> Eq
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Bool
$c/= :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Bool
== :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Bool
$c== :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address' where
  toJSON :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Value
toJSON PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"city" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'City PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"country" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'Country PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"line1" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'Line1 PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"line2" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'Line2 PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"postal_code" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'PostalCode PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"state" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'State PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Encoding
toEncoding PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"city" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'City PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"country" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'Country PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"line1" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'Line1 PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"line2" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'Line2 PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"postal_code" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'PostalCode PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"state" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'State PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
obj))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
parseJSON = String
-> (Object
    -> Parser
         PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
-> Value
-> Parser
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'" (\Object
obj -> ((((((Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address' Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
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
"city")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
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
"country")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
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
"line1")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
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
"line2")) Parser
  (Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
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
"postal_code")) Parser
  (Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address')
-> Parser (Maybe Text)
-> Parser
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
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
"state"))

-- | Create a new 'PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'' with all required fields.
mkPostCustomersCustomerBankAccountsIdResponseBody200Owner'Address' :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
mkPostCustomersCustomerBankAccountsIdResponseBody200Owner'Address' :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
mkPostCustomersCustomerBankAccountsIdResponseBody200Owner'Address' =
  PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address' :: Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
PostCustomersCustomerBankAccountsIdResponseBody200Owner'Address'
    { postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'City :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'City = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'Country :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'Country = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'Line1 :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'Line1 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'Line2 :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'Line2 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'PostalCode :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'PostalCode = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'State :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'Address'State = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the object schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts\/{id}.POST.responses.200.content.application\/json.schema.anyOf.properties.owner.anyOf.properties.verified_address.anyOf@ in the specification.
--
-- Verified owner\\\'s address. Verified values are verified or provided by the payment method directly (and if supported) at the time of authorization or settlement. They cannot be set or mutated.
data PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress' = PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
  { -- | city: City, district, suburb, town, or village.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'City :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | country: Two-letter country code ([ISO 3166-1 alpha-2](https:\/\/en.wikipedia.org\/wiki\/ISO_3166-1_alpha-2)).
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'Country :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | line1: Address line 1 (e.g., street, PO Box, or company name).
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'Line1 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | line2: Address line 2 (e.g., apartment, suite, unit, or building).
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'Line2 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | postal_code: ZIP or postal code.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'PostalCode :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | state: State, county, province, or region.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'State :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> String
-> String
[PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress']
-> String -> String
PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> String
(Int
 -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
    -> String)
-> ([PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress']
    -> String -> String)
-> Show
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress']
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress']
-> String -> String
show :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> String
$cshow :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Bool
(PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
 -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
 -> Bool)
-> (PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
    -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
    -> Bool)
-> Eq
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Bool
$c/= :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Bool
== :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Bool
$c== :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress' where
  toJSON :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Value
toJSON PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"city" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'City PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"country" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'Country PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"line1" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'Line1 PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"line2" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'Line2 PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"postal_code" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'PostalCode PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"state" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'State PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Encoding
toEncoding PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"city" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'City PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"country" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'Country PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"line1" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'Line1 PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"line2" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'Line2 PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"postal_code" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'PostalCode PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"state" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
-> Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'State PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
obj))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
parseJSON = String
-> (Object
    -> Parser
         PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
-> Value
-> Parser
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'" (\Object
obj -> ((((((Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress' Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
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
"city")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
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
"country")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
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
"line1")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
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
"line2")) Parser
  (Maybe Text
   -> Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
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
"postal_code")) Parser
  (Maybe Text
   -> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress')
-> Parser (Maybe Text)
-> Parser
     PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
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
"state"))

-- | Create a new 'PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'' with all required fields.
mkPostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress' :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
mkPostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress' :: PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
mkPostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress' =
  PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress' :: Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
PostCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'
    { postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'City :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'City = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'Country :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'Country = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'Line1 :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'Line1 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'Line2 :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'Line2 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'PostalCode :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'PostalCode = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'State :: Maybe Text
postCustomersCustomerBankAccountsIdResponseBody200Owner'VerifiedAddress'State = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the oneOf schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts\/{id}.POST.responses.200.content.application\/json.schema.anyOf.properties.recipient.anyOf@ in the specification.
--
-- The recipient that this card belongs to. This attribute will not be in the card object if the card belongs to a customer or account instead.
data PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
  = PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Text Data.Text.Internal.Text
  | PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Recipient Recipient
  deriving (Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> String
-> String
[PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants]
-> String -> String
PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> String
(Int
 -> PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
    -> String)
-> ([PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants]
    -> String -> String)
-> Show
     PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants]
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants]
-> String -> String
show :: PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> String
$cshow :: PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> String
-> String
GHC.Show.Show, PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> Bool
(PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
 -> PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
 -> Bool)
-> (PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
    -> PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
    -> Bool)
-> Eq
     PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> Bool
$c/= :: PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> Bool
== :: PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> Bool
$c== :: PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> PostCustomersCustomerBankAccountsIdResponseBody200Recipient'Variants
-> Bool
GHC.Classes.Eq)

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

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

-- | Defines the enum schema located at @paths.\/v1\/customers\/{customer}\/bank_accounts\/{id}.POST.responses.200.content.application\/json.schema.anyOf.properties.type@ in the specification.
--
-- The \`type\` of the source. The \`type\` is a payment method, one of \`ach_credit_transfer\`, \`ach_debit\`, \`alipay\`, \`bancontact\`, \`card\`, \`card_present\`, \`eps\`, \`giropay\`, \`ideal\`, \`multibanco\`, \`klarna\`, \`p24\`, \`sepa_debit\`, \`sofort\`, \`three_d_secure\`, or \`wechat\`. An additional hash is included on the source with a name matching this value. It contains additional information specific to the [payment method](https:\/\/stripe.com\/docs\/sources) used.
data PostCustomersCustomerBankAccountsIdResponseBody200Type'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCustomersCustomerBankAccountsIdResponseBody200Type'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.
    PostCustomersCustomerBankAccountsIdResponseBody200Type'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"ach_credit_transfer"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumAchCreditTransfer
  | -- | Represents the JSON value @"ach_debit"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumAchDebit
  | -- | Represents the JSON value @"acss_debit"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumAcssDebit
  | -- | Represents the JSON value @"alipay"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumAlipay
  | -- | Represents the JSON value @"au_becs_debit"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumAuBecsDebit
  | -- | Represents the JSON value @"bancontact"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumBancontact
  | -- | Represents the JSON value @"card"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumCard
  | -- | Represents the JSON value @"card_present"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumCardPresent
  | -- | Represents the JSON value @"eps"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumEps
  | -- | Represents the JSON value @"giropay"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumGiropay
  | -- | Represents the JSON value @"ideal"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumIdeal
  | -- | Represents the JSON value @"klarna"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumKlarna
  | -- | Represents the JSON value @"multibanco"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumMultibanco
  | -- | Represents the JSON value @"p24"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumP24
  | -- | Represents the JSON value @"sepa_debit"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumSepaDebit
  | -- | Represents the JSON value @"sofort"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumSofort
  | -- | Represents the JSON value @"three_d_secure"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumThreeDSecure
  | -- | Represents the JSON value @"wechat"@
    PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumWechat
  deriving (Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Type'
-> String
-> String
[PostCustomersCustomerBankAccountsIdResponseBody200Type']
-> String -> String
PostCustomersCustomerBankAccountsIdResponseBody200Type' -> String
(Int
 -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
 -> String
 -> String)
-> (PostCustomersCustomerBankAccountsIdResponseBody200Type'
    -> String)
-> ([PostCustomersCustomerBankAccountsIdResponseBody200Type']
    -> String -> String)
-> Show PostCustomersCustomerBankAccountsIdResponseBody200Type'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerBankAccountsIdResponseBody200Type']
-> String -> String
$cshowList :: [PostCustomersCustomerBankAccountsIdResponseBody200Type']
-> String -> String
show :: PostCustomersCustomerBankAccountsIdResponseBody200Type' -> String
$cshow :: PostCustomersCustomerBankAccountsIdResponseBody200Type' -> String
showsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Type'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerBankAccountsIdResponseBody200Type'
-> String
-> String
GHC.Show.Show, PostCustomersCustomerBankAccountsIdResponseBody200Type'
-> PostCustomersCustomerBankAccountsIdResponseBody200Type' -> Bool
(PostCustomersCustomerBankAccountsIdResponseBody200Type'
 -> PostCustomersCustomerBankAccountsIdResponseBody200Type' -> Bool)
-> (PostCustomersCustomerBankAccountsIdResponseBody200Type'
    -> PostCustomersCustomerBankAccountsIdResponseBody200Type' -> Bool)
-> Eq PostCustomersCustomerBankAccountsIdResponseBody200Type'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerBankAccountsIdResponseBody200Type'
-> PostCustomersCustomerBankAccountsIdResponseBody200Type' -> Bool
$c/= :: PostCustomersCustomerBankAccountsIdResponseBody200Type'
-> PostCustomersCustomerBankAccountsIdResponseBody200Type' -> Bool
== :: PostCustomersCustomerBankAccountsIdResponseBody200Type'
-> PostCustomersCustomerBankAccountsIdResponseBody200Type' -> Bool
$c== :: PostCustomersCustomerBankAccountsIdResponseBody200Type'
-> PostCustomersCustomerBankAccountsIdResponseBody200Type' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerBankAccountsIdResponseBody200Type' where
  toJSON :: PostCustomersCustomerBankAccountsIdResponseBody200Type' -> Value
toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'Other Value
val) = Value
val
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumAchCreditTransfer) = Value
"ach_credit_transfer"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumAchDebit) = Value
"ach_debit"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumAcssDebit) = Value
"acss_debit"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumAlipay) = Value
"alipay"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumAuBecsDebit) = Value
"au_becs_debit"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumBancontact) = Value
"bancontact"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumCard) = Value
"card"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumCardPresent) = Value
"card_present"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumEps) = Value
"eps"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumGiropay) = Value
"giropay"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumIdeal) = Value
"ideal"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumKlarna) = Value
"klarna"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumMultibanco) = Value
"multibanco"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumP24) = Value
"p24"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumSepaDebit) = Value
"sepa_debit"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumSofort) = Value
"sofort"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumThreeDSecure) = Value
"three_d_secure"
  toJSON (PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumWechat) = Value
"wechat"

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerBankAccountsIdResponseBody200Type' where
  parseJSON :: Value
-> Parser PostCustomersCustomerBankAccountsIdResponseBody200Type'
parseJSON Value
val =
    PostCustomersCustomerBankAccountsIdResponseBody200Type'
-> Parser PostCustomersCustomerBankAccountsIdResponseBody200Type'
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
"ach_credit_transfer" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumAchCreditTransfer
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ach_debit" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumAchDebit
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"acss_debit" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumAcssDebit
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"alipay" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumAlipay
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"au_becs_debit" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumAuBecsDebit
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"bancontact" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumBancontact
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"card" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumCard
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"card_present" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumCardPresent
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"eps" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumEps
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"giropay" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumGiropay
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"ideal" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumIdeal
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"klarna" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumKlarna
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"multibanco" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumMultibanco
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"p24" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumP24
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"sepa_debit" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumSepaDebit
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"sofort" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumSofort
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"three_d_secure" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumThreeDSecure
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"wechat" -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'EnumWechat
            | Bool
GHC.Base.otherwise -> Value -> PostCustomersCustomerBankAccountsIdResponseBody200Type'
PostCustomersCustomerBankAccountsIdResponseBody200Type'Other Value
val
      )