{-# 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 postCustomersCustomerSources
module StripeAPI.Operations.PostCustomersCustomerSources 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}/sources
--
-- \<p>When you create a new credit card, you must specify a customer or recipient on which to create it.\<\/p>
--
-- \<p>If the card’s owner has no default card, then the new card will become the default.
-- However, if the owner already has a default, then it will not change.
-- To change the default, you should \<a href=\"\/docs\/api\#update_customer\">update the customer\<\/a> to have a new \<code>default_source\<\/code>.\<\/p>
postCustomersCustomerSources ::
  forall m.
  StripeAPI.Common.MonadHTTP m =>
  -- | customer | Constraints: Maximum length of 5000
  Data.Text.Internal.Text ->
  -- | The request body to send
  GHC.Maybe.Maybe PostCustomersCustomerSourcesRequestBody ->
  -- | Monadic computation which returns the result of the operation
  StripeAPI.Common.ClientT m (Network.HTTP.Client.Types.Response PostCustomersCustomerSourcesResponse)
postCustomersCustomerSources :: Text
-> Maybe PostCustomersCustomerSourcesRequestBody
-> ClientT m (Response PostCustomersCustomerSourcesResponse)
postCustomersCustomerSources
  Text
customer
  Maybe PostCustomersCustomerSourcesRequestBody
body =
    (Response ByteString
 -> Response PostCustomersCustomerSourcesResponse)
-> ClientT m (Response ByteString)
-> ClientT m (Response PostCustomersCustomerSourcesResponse)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
      ( \Response ByteString
response_0 ->
          (ByteString -> PostCustomersCustomerSourcesResponse)
-> Response ByteString
-> Response PostCustomersCustomerSourcesResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
GHC.Base.fmap
            ( (String -> PostCustomersCustomerSourcesResponse)
-> (PostCustomersCustomerSourcesResponse
    -> PostCustomersCustomerSourcesResponse)
-> Either String PostCustomersCustomerSourcesResponse
-> PostCustomersCustomerSourcesResponse
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
Data.Either.either String -> PostCustomersCustomerSourcesResponse
PostCustomersCustomerSourcesResponseError PostCustomersCustomerSourcesResponse
-> PostCustomersCustomerSourcesResponse
forall a. a -> a
GHC.Base.id
                (Either String PostCustomersCustomerSourcesResponse
 -> PostCustomersCustomerSourcesResponse)
-> (ByteString
    -> Either String PostCustomersCustomerSourcesResponse)
-> ByteString
-> PostCustomersCustomerSourcesResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
GHC.Base.. ( \Response ByteString
response ByteString
body ->
                               if
                                   | (\Status
status_1 -> Status -> Int
Network.HTTP.Types.Status.statusCode Status
status_1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Int
200) (Response ByteString -> Status
forall body. Response body -> Status
Network.HTTP.Client.Types.responseStatus Response ByteString
response) ->
                                     PaymentSource -> PostCustomersCustomerSourcesResponse
PostCustomersCustomerSourcesResponse200
                                       (PaymentSource -> PostCustomersCustomerSourcesResponse)
-> Either String PaymentSource
-> Either String PostCustomersCustomerSourcesResponse
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> ( ByteString -> Either String PaymentSource
forall a. FromJSON a => ByteString -> Either String a
Data.Aeson.eitherDecodeStrict ByteString
body ::
                                                            Data.Either.Either
                                                              GHC.Base.String
                                                              PaymentSource
                                                        )
                                   | Bool -> Status -> Bool
forall a b. a -> b -> a
GHC.Base.const Bool
GHC.Types.True (Response ByteString -> Status
forall body. Response body -> Status
Network.HTTP.Client.Types.responseStatus Response ByteString
response) ->
                                     Error -> PostCustomersCustomerSourcesResponse
PostCustomersCustomerSourcesResponseDefault
                                       (Error -> PostCustomersCustomerSourcesResponse)
-> Either String Error
-> Either String PostCustomersCustomerSourcesResponse
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 PostCustomersCustomerSourcesResponse
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 PostCustomersCustomerSourcesRequestBody
-> RequestBodyEncoding
-> ClientT m (Response ByteString)
forall (m :: * -> *) body.
(MonadHTTP m, ToJSON body) =>
Text
-> Text
-> [QueryParameter]
-> Maybe body
-> RequestBodyEncoding
-> ClientT m (Response ByteString)
StripeAPI.Common.doBodyCallWithConfigurationM (Text -> Text
Data.Text.toUpper (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
GHC.Base.$ String -> Text
Data.Text.pack String
"POST") (String -> Text
Data.Text.pack (String
"/v1/customers/" String -> String -> String
forall a. [a] -> [a] -> [a]
GHC.Base.++ (ByteString -> String
Data.ByteString.Char8.unpack (Bool -> ByteString -> ByteString
Network.HTTP.Types.URI.urlEncode Bool
GHC.Types.True (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
GHC.Base.$ (String -> ByteString
Data.ByteString.Char8.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
GHC.Base.$ Text -> String
forall a. StringifyModel a => a -> String
StripeAPI.Common.stringifyModel Text
customer)) String -> String -> String
forall a. [a] -> [a] -> [a]
GHC.Base.++ String
"/sources"))) [QueryParameter]
forall a. Monoid a => a
GHC.Base.mempty Maybe PostCustomersCustomerSourcesRequestBody
body RequestBodyEncoding
StripeAPI.Common.RequestBodyEncodingFormData)

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

instance Data.Aeson.Types.ToJSON.ToJSON PostCustomersCustomerSourcesRequestBody where
  toJSON :: PostCustomersCustomerSourcesRequestBody -> Value
toJSON PostCustomersCustomerSourcesRequestBody
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"alipay_account" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSourcesRequestBody -> Maybe Text
postCustomersCustomerSourcesRequestBodyAlipayAccount PostCustomersCustomerSourcesRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"bank_account" Text
-> Maybe
     PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSourcesRequestBody
-> Maybe
     PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
postCustomersCustomerSourcesRequestBodyBankAccount PostCustomersCustomerSourcesRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"card" Text
-> Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSourcesRequestBody
-> Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants
postCustomersCustomerSourcesRequestBodyCard PostCustomersCustomerSourcesRequestBody
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..= PostCustomersCustomerSourcesRequestBody -> Maybe [Text]
postCustomersCustomerSourcesRequestBodyExpand PostCustomersCustomerSourcesRequestBody
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..= PostCustomersCustomerSourcesRequestBody -> Maybe Object
postCustomersCustomerSourcesRequestBodyMetadata PostCustomersCustomerSourcesRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"source" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSourcesRequestBody -> Maybe Text
postCustomersCustomerSourcesRequestBodySource PostCustomersCustomerSourcesRequestBody
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: PostCustomersCustomerSourcesRequestBody -> Encoding
toEncoding PostCustomersCustomerSourcesRequestBody
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"alipay_account" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSourcesRequestBody -> Maybe Text
postCustomersCustomerSourcesRequestBodyAlipayAccount PostCustomersCustomerSourcesRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"bank_account" Text
-> Maybe
     PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSourcesRequestBody
-> Maybe
     PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
postCustomersCustomerSourcesRequestBodyBankAccount PostCustomersCustomerSourcesRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"card" Text
-> Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSourcesRequestBody
-> Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants
postCustomersCustomerSourcesRequestBodyCard PostCustomersCustomerSourcesRequestBody
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..= PostCustomersCustomerSourcesRequestBody -> Maybe [Text]
postCustomersCustomerSourcesRequestBodyExpand PostCustomersCustomerSourcesRequestBody
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..= PostCustomersCustomerSourcesRequestBody -> Maybe Object
postCustomersCustomerSourcesRequestBodyMetadata PostCustomersCustomerSourcesRequestBody
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"source" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= PostCustomersCustomerSourcesRequestBody -> Maybe Text
postCustomersCustomerSourcesRequestBodySource PostCustomersCustomerSourcesRequestBody
obj))))))

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSourcesRequestBody where
  parseJSON :: Value -> Parser PostCustomersCustomerSourcesRequestBody
parseJSON = String
-> (Object -> Parser PostCustomersCustomerSourcesRequestBody)
-> Value
-> Parser PostCustomersCustomerSourcesRequestBody
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"PostCustomersCustomerSourcesRequestBody" (\Object
obj -> ((((((Maybe Text
 -> Maybe
      PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
 -> Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants
 -> Maybe [Text]
 -> Maybe Object
 -> Maybe Text
 -> PostCustomersCustomerSourcesRequestBody)
-> Parser
     (Maybe Text
      -> Maybe
           PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
      -> Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants
      -> Maybe [Text]
      -> Maybe Object
      -> Maybe Text
      -> PostCustomersCustomerSourcesRequestBody)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe Text
-> Maybe
     PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
-> Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants
-> Maybe [Text]
-> Maybe Object
-> Maybe Text
-> PostCustomersCustomerSourcesRequestBody
PostCustomersCustomerSourcesRequestBody Parser
  (Maybe Text
   -> Maybe
        PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
   -> Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants
   -> Maybe [Text]
   -> Maybe Object
   -> Maybe Text
   -> PostCustomersCustomerSourcesRequestBody)
-> Parser (Maybe Text)
-> Parser
     (Maybe PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
      -> Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants
      -> Maybe [Text]
      -> Maybe Object
      -> Maybe Text
      -> PostCustomersCustomerSourcesRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"alipay_account")) Parser
  (Maybe PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
   -> Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants
   -> Maybe [Text]
   -> Maybe Object
   -> Maybe Text
   -> PostCustomersCustomerSourcesRequestBody)
-> Parser
     (Maybe PostCustomersCustomerSourcesRequestBodyBankAccount'Variants)
-> Parser
     (Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants
      -> Maybe [Text]
      -> Maybe Object
      -> Maybe Text
      -> PostCustomersCustomerSourcesRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe PostCustomersCustomerSourcesRequestBodyBankAccount'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"bank_account")) Parser
  (Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants
   -> Maybe [Text]
   -> Maybe Object
   -> Maybe Text
   -> PostCustomersCustomerSourcesRequestBody)
-> Parser
     (Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants)
-> Parser
     (Maybe [Text]
      -> Maybe Object
      -> Maybe Text
      -> PostCustomersCustomerSourcesRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"card")) Parser
  (Maybe [Text]
   -> Maybe Object
   -> Maybe Text
   -> PostCustomersCustomerSourcesRequestBody)
-> Parser (Maybe [Text])
-> Parser
     (Maybe Object
      -> Maybe Text -> PostCustomersCustomerSourcesRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [Text])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"expand")) Parser
  (Maybe Object
   -> Maybe Text -> PostCustomersCustomerSourcesRequestBody)
-> Parser (Maybe Object)
-> Parser (Maybe Text -> PostCustomersCustomerSourcesRequestBody)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"metadata")) Parser (Maybe Text -> PostCustomersCustomerSourcesRequestBody)
-> Parser (Maybe Text)
-> Parser PostCustomersCustomerSourcesRequestBody
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"source"))

-- | Create a new 'PostCustomersCustomerSourcesRequestBody' with all required fields.
mkPostCustomersCustomerSourcesRequestBody :: PostCustomersCustomerSourcesRequestBody
mkPostCustomersCustomerSourcesRequestBody :: PostCustomersCustomerSourcesRequestBody
mkPostCustomersCustomerSourcesRequestBody =
  PostCustomersCustomerSourcesRequestBody :: Maybe Text
-> Maybe
     PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
-> Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants
-> Maybe [Text]
-> Maybe Object
-> Maybe Text
-> PostCustomersCustomerSourcesRequestBody
PostCustomersCustomerSourcesRequestBody
    { postCustomersCustomerSourcesRequestBodyAlipayAccount :: Maybe Text
postCustomersCustomerSourcesRequestBodyAlipayAccount = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSourcesRequestBodyBankAccount :: Maybe PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
postCustomersCustomerSourcesRequestBodyBankAccount = Maybe PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSourcesRequestBodyCard :: Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants
postCustomersCustomerSourcesRequestBodyCard = Maybe PostCustomersCustomerSourcesRequestBodyCard'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSourcesRequestBodyExpand :: Maybe [Text]
postCustomersCustomerSourcesRequestBodyExpand = Maybe [Text]
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSourcesRequestBodyMetadata :: Maybe Object
postCustomersCustomerSourcesRequestBodyMetadata = Maybe Object
forall a. Maybe a
GHC.Maybe.Nothing,
      postCustomersCustomerSourcesRequestBodySource :: Maybe Text
postCustomersCustomerSourcesRequestBodySource = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }

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

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

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

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

-- | Defines the enum schema located at @paths.\/v1\/customers\/{customer}\/sources.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.bank_account.anyOf.properties.account_holder_type@ in the specification.
data PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"company"@
    PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'EnumCompany
  | -- | Represents the JSON value @"individual"@
    PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'EnumIndividual
  deriving (Int
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> String
-> String
[PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType']
-> String -> String
PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> String
(Int
 -> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
 -> String
 -> String)
-> (PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
    -> String)
-> ([PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType']
    -> String -> String)
-> Show
     PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType']
-> String -> String
$cshowList :: [PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType']
-> String -> String
show :: PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> String
$cshow :: PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> String
showsPrec :: Int
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> Bool
(PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
 -> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
 -> Bool)
-> (PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
    -> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
    -> Bool)
-> Eq
     PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> Bool
$c/= :: PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> Bool
== :: PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> Bool
$c== :: PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> Bool
GHC.Classes.Eq)

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

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
parseJSON Value
val =
    PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
-> Parser
     PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"company" -> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'EnumCompany
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"individual" -> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'EnumIndividual
            | Bool
GHC.Base.otherwise -> Value
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'
PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1AccountHolderType'Other Value
val
      )

-- | Defines the enum schema located at @paths.\/v1\/customers\/{customer}\/sources.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.bank_account.anyOf.properties.object@ in the specification.
data PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"bank_account"@
    PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'EnumBankAccount
  deriving (Int
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> String
-> String
[PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object']
-> String -> String
PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> String
(Int
 -> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
 -> String
 -> String)
-> (PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
    -> String)
-> ([PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object']
    -> String -> String)
-> Show
     PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object']
-> String -> String
$cshowList :: [PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object']
-> String -> String
show :: PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> String
$cshow :: PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> String
showsPrec :: Int
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> Bool
(PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
 -> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
 -> Bool)
-> (PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
    -> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
    -> Bool)
-> Eq
     PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> Bool
$c/= :: PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> Bool
== :: PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> Bool
$c== :: PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> Bool
GHC.Classes.Eq)

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

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object' where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
parseJSON Value
val =
    PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
-> Parser
     PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"bank_account" -> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'EnumBankAccount
            | Bool
GHC.Base.otherwise -> Value
-> PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'
PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1Object'Other Value
val
      )

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

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

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSourcesRequestBodyBankAccount'Variants where
  parseJSON :: Value
-> Parser
     PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
parseJSON Value
val = case (PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1
-> PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
PostCustomersCustomerSourcesRequestBodyBankAccount'PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1 (PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1
 -> PostCustomersCustomerSourcesRequestBodyBankAccount'Variants)
-> Result PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1
-> Result
     PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value
-> Result PostCustomersCustomerSourcesRequestBodyBankAccount'OneOf1
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
-> Result
     PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
-> Result
     PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((Text -> PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
PostCustomersCustomerSourcesRequestBodyBankAccount'Text (Text
 -> PostCustomersCustomerSourcesRequestBodyBankAccount'Variants)
-> Result Text
-> Result
     PostCustomersCustomerSourcesRequestBodyBankAccount'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 PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
-> Result
     PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
-> Result
     PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String
-> Result
     PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched") of
    Data.Aeson.Types.Internal.Success PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
a -> PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
-> Parser
     PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure PostCustomersCustomerSourcesRequestBodyBankAccount'Variants
a
    Data.Aeson.Types.Internal.Error String
a -> String
-> Parser
     PostCustomersCustomerSourcesRequestBodyBankAccount'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}\/sources.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.card.anyOf@ in the specification.
data PostCustomersCustomerSourcesRequestBodyCard'OneOf1 = PostCustomersCustomerSourcesRequestBodyCard'OneOf1
  { -- | address_city
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Maybe Text
postCustomersCustomerSourcesRequestBodyCard'OneOf1AddressCity :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_country
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Maybe Text
postCustomersCustomerSourcesRequestBodyCard'OneOf1AddressCountry :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_line1
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Maybe Text
postCustomersCustomerSourcesRequestBodyCard'OneOf1AddressLine1 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_line2
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Maybe Text
postCustomersCustomerSourcesRequestBodyCard'OneOf1AddressLine2 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_state
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Maybe Text
postCustomersCustomerSourcesRequestBodyCard'OneOf1AddressState :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | address_zip
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Maybe Text
postCustomersCustomerSourcesRequestBodyCard'OneOf1AddressZip :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | cvc
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Maybe Text
postCustomersCustomerSourcesRequestBodyCard'OneOf1Cvc :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | exp_month
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Int
postCustomersCustomerSourcesRequestBodyCard'OneOf1ExpMonth :: GHC.Types.Int,
    -- | exp_year
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Int
postCustomersCustomerSourcesRequestBodyCard'OneOf1ExpYear :: GHC.Types.Int,
    -- | metadata
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Maybe Object
postCustomersCustomerSourcesRequestBodyCard'OneOf1Metadata :: (GHC.Maybe.Maybe Data.Aeson.Types.Internal.Object),
    -- | name
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Maybe Text
postCustomersCustomerSourcesRequestBodyCard'OneOf1Name :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    -- | number
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Text
postCustomersCustomerSourcesRequestBodyCard'OneOf1Number :: Data.Text.Internal.Text,
    -- | object
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1
-> Maybe PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
postCustomersCustomerSourcesRequestBodyCard'OneOf1Object :: (GHC.Maybe.Maybe PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object')
  }
  deriving
    ( Int
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1
-> String
-> String
[PostCustomersCustomerSourcesRequestBodyCard'OneOf1]
-> String -> String
PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> String
(Int
 -> PostCustomersCustomerSourcesRequestBodyCard'OneOf1
 -> String
 -> String)
-> (PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> String)
-> ([PostCustomersCustomerSourcesRequestBodyCard'OneOf1]
    -> String -> String)
-> Show PostCustomersCustomerSourcesRequestBodyCard'OneOf1
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSourcesRequestBodyCard'OneOf1]
-> String -> String
$cshowList :: [PostCustomersCustomerSourcesRequestBodyCard'OneOf1]
-> String -> String
show :: PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> String
$cshow :: PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> String
showsPrec :: Int
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1
-> String
-> String
GHC.Show.Show,
      PostCustomersCustomerSourcesRequestBodyCard'OneOf1
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Bool
(PostCustomersCustomerSourcesRequestBodyCard'OneOf1
 -> PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Bool)
-> (PostCustomersCustomerSourcesRequestBodyCard'OneOf1
    -> PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Bool)
-> Eq PostCustomersCustomerSourcesRequestBodyCard'OneOf1
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSourcesRequestBodyCard'OneOf1
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Bool
$c/= :: PostCustomersCustomerSourcesRequestBodyCard'OneOf1
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Bool
== :: PostCustomersCustomerSourcesRequestBodyCard'OneOf1
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Bool
$c== :: PostCustomersCustomerSourcesRequestBodyCard'OneOf1
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1 -> Bool
GHC.Classes.Eq
    )

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

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

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

-- | Defines the enum schema located at @paths.\/v1\/customers\/{customer}\/sources.POST.requestBody.content.application\/x-www-form-urlencoded.schema.properties.card.anyOf.properties.object@ in the specification.
data PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'Other Data.Aeson.Types.Internal.Value
  | -- | This constructor can be used to send values to the server which are not present in the specification yet.
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"card"@
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'EnumCard
  deriving (Int
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
-> String
-> String
[PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object']
-> String -> String
PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object' -> String
(Int
 -> PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
 -> String
 -> String)
-> (PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
    -> String)
-> ([PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object']
    -> String -> String)
-> Show PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object']
-> String -> String
$cshowList :: [PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object']
-> String -> String
show :: PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object' -> String
$cshow :: PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object' -> String
showsPrec :: Int
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
-> String
-> String
$cshowsPrec :: Int
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
-> String
-> String
GHC.Show.Show, PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
-> Bool
(PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
 -> PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
 -> Bool)
-> (PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
    -> PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
    -> Bool)
-> Eq PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
-> Bool
$c/= :: PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
-> Bool
== :: PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
-> Bool
$c== :: PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
-> PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
-> Bool
GHC.Classes.Eq)

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

instance Data.Aeson.Types.FromJSON.FromJSON PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object' where
  parseJSON :: Value
-> Parser PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
parseJSON Value
val =
    PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
-> Parser PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure
      ( if
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"card" -> PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'EnumCard
            | Bool
GHC.Base.otherwise -> Value -> PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'
PostCustomersCustomerSourcesRequestBodyCard'OneOf1Object'Other Value
val
      )

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

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

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

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