{-# 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 types generated from the schema SetupIntentPaymentMethodOptions
module StripeAPI.Types.SetupIntentPaymentMethodOptions where

import qualified Control.Monad.Fail
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.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 GHC.Base
import qualified GHC.Classes
import qualified GHC.Int
import qualified GHC.Show
import qualified GHC.Types
import qualified StripeAPI.Common
import StripeAPI.TypeAlias
import {-# SOURCE #-} StripeAPI.Types.SetupIntentPaymentMethodOptionsAcssDebit
import {-# SOURCE #-} StripeAPI.Types.SetupIntentPaymentMethodOptionsCard
import {-# SOURCE #-} StripeAPI.Types.SetupIntentPaymentMethodOptionsSepaDebit
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe

-- | Defines the object schema located at @components.schemas.setup_intent_payment_method_options@ in the specification.
data SetupIntentPaymentMethodOptions = SetupIntentPaymentMethodOptions
  { -- | acss_debit:
    SetupIntentPaymentMethodOptions
-> Maybe SetupIntentPaymentMethodOptionsAcssDebit
setupIntentPaymentMethodOptionsAcssDebit :: (GHC.Maybe.Maybe SetupIntentPaymentMethodOptionsAcssDebit),
    -- | card:
    SetupIntentPaymentMethodOptions
-> Maybe SetupIntentPaymentMethodOptionsCard
setupIntentPaymentMethodOptionsCard :: (GHC.Maybe.Maybe SetupIntentPaymentMethodOptionsCard),
    -- | sepa_debit:
    SetupIntentPaymentMethodOptions
-> Maybe SetupIntentPaymentMethodOptionsSepaDebit
setupIntentPaymentMethodOptionsSepaDebit :: (GHC.Maybe.Maybe SetupIntentPaymentMethodOptionsSepaDebit)
  }
  deriving
    ( Int -> SetupIntentPaymentMethodOptions -> ShowS
[SetupIntentPaymentMethodOptions] -> ShowS
SetupIntentPaymentMethodOptions -> String
(Int -> SetupIntentPaymentMethodOptions -> ShowS)
-> (SetupIntentPaymentMethodOptions -> String)
-> ([SetupIntentPaymentMethodOptions] -> ShowS)
-> Show SetupIntentPaymentMethodOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetupIntentPaymentMethodOptions] -> ShowS
$cshowList :: [SetupIntentPaymentMethodOptions] -> ShowS
show :: SetupIntentPaymentMethodOptions -> String
$cshow :: SetupIntentPaymentMethodOptions -> String
showsPrec :: Int -> SetupIntentPaymentMethodOptions -> ShowS
$cshowsPrec :: Int -> SetupIntentPaymentMethodOptions -> ShowS
GHC.Show.Show,
      SetupIntentPaymentMethodOptions
-> SetupIntentPaymentMethodOptions -> Bool
(SetupIntentPaymentMethodOptions
 -> SetupIntentPaymentMethodOptions -> Bool)
-> (SetupIntentPaymentMethodOptions
    -> SetupIntentPaymentMethodOptions -> Bool)
-> Eq SetupIntentPaymentMethodOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetupIntentPaymentMethodOptions
-> SetupIntentPaymentMethodOptions -> Bool
$c/= :: SetupIntentPaymentMethodOptions
-> SetupIntentPaymentMethodOptions -> Bool
== :: SetupIntentPaymentMethodOptions
-> SetupIntentPaymentMethodOptions -> Bool
$c== :: SetupIntentPaymentMethodOptions
-> SetupIntentPaymentMethodOptions -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON SetupIntentPaymentMethodOptions where
  toJSON :: SetupIntentPaymentMethodOptions -> Value
toJSON SetupIntentPaymentMethodOptions
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"acss_debit" Text -> Maybe SetupIntentPaymentMethodOptionsAcssDebit -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupIntentPaymentMethodOptions
-> Maybe SetupIntentPaymentMethodOptionsAcssDebit
setupIntentPaymentMethodOptionsAcssDebit SetupIntentPaymentMethodOptions
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"card" Text -> Maybe SetupIntentPaymentMethodOptionsCard -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupIntentPaymentMethodOptions
-> Maybe SetupIntentPaymentMethodOptionsCard
setupIntentPaymentMethodOptionsCard SetupIntentPaymentMethodOptions
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"sepa_debit" Text -> Maybe SetupIntentPaymentMethodOptionsSepaDebit -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupIntentPaymentMethodOptions
-> Maybe SetupIntentPaymentMethodOptionsSepaDebit
setupIntentPaymentMethodOptionsSepaDebit SetupIntentPaymentMethodOptions
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: SetupIntentPaymentMethodOptions -> Encoding
toEncoding SetupIntentPaymentMethodOptions
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"acss_debit" Text -> Maybe SetupIntentPaymentMethodOptionsAcssDebit -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupIntentPaymentMethodOptions
-> Maybe SetupIntentPaymentMethodOptionsAcssDebit
setupIntentPaymentMethodOptionsAcssDebit SetupIntentPaymentMethodOptions
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"card" Text -> Maybe SetupIntentPaymentMethodOptionsCard -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupIntentPaymentMethodOptions
-> Maybe SetupIntentPaymentMethodOptionsCard
setupIntentPaymentMethodOptionsCard SetupIntentPaymentMethodOptions
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"sepa_debit" Text -> Maybe SetupIntentPaymentMethodOptionsSepaDebit -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupIntentPaymentMethodOptions
-> Maybe SetupIntentPaymentMethodOptionsSepaDebit
setupIntentPaymentMethodOptionsSepaDebit SetupIntentPaymentMethodOptions
obj)))

instance Data.Aeson.Types.FromJSON.FromJSON SetupIntentPaymentMethodOptions where
  parseJSON :: Value -> Parser SetupIntentPaymentMethodOptions
parseJSON = String
-> (Object -> Parser SetupIntentPaymentMethodOptions)
-> Value
-> Parser SetupIntentPaymentMethodOptions
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"SetupIntentPaymentMethodOptions" (\Object
obj -> (((Maybe SetupIntentPaymentMethodOptionsAcssDebit
 -> Maybe SetupIntentPaymentMethodOptionsCard
 -> Maybe SetupIntentPaymentMethodOptionsSepaDebit
 -> SetupIntentPaymentMethodOptions)
-> Parser
     (Maybe SetupIntentPaymentMethodOptionsAcssDebit
      -> Maybe SetupIntentPaymentMethodOptionsCard
      -> Maybe SetupIntentPaymentMethodOptionsSepaDebit
      -> SetupIntentPaymentMethodOptions)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe SetupIntentPaymentMethodOptionsAcssDebit
-> Maybe SetupIntentPaymentMethodOptionsCard
-> Maybe SetupIntentPaymentMethodOptionsSepaDebit
-> SetupIntentPaymentMethodOptions
SetupIntentPaymentMethodOptions Parser
  (Maybe SetupIntentPaymentMethodOptionsAcssDebit
   -> Maybe SetupIntentPaymentMethodOptionsCard
   -> Maybe SetupIntentPaymentMethodOptionsSepaDebit
   -> SetupIntentPaymentMethodOptions)
-> Parser (Maybe SetupIntentPaymentMethodOptionsAcssDebit)
-> Parser
     (Maybe SetupIntentPaymentMethodOptionsCard
      -> Maybe SetupIntentPaymentMethodOptionsSepaDebit
      -> SetupIntentPaymentMethodOptions)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text -> Parser (Maybe SetupIntentPaymentMethodOptionsAcssDebit)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"acss_debit")) Parser
  (Maybe SetupIntentPaymentMethodOptionsCard
   -> Maybe SetupIntentPaymentMethodOptionsSepaDebit
   -> SetupIntentPaymentMethodOptions)
-> Parser (Maybe SetupIntentPaymentMethodOptionsCard)
-> Parser
     (Maybe SetupIntentPaymentMethodOptionsSepaDebit
      -> SetupIntentPaymentMethodOptions)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text -> Parser (Maybe SetupIntentPaymentMethodOptionsCard)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"card")) Parser
  (Maybe SetupIntentPaymentMethodOptionsSepaDebit
   -> SetupIntentPaymentMethodOptions)
-> Parser (Maybe SetupIntentPaymentMethodOptionsSepaDebit)
-> Parser SetupIntentPaymentMethodOptions
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text -> Parser (Maybe SetupIntentPaymentMethodOptionsSepaDebit)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"sepa_debit"))

-- | Create a new 'SetupIntentPaymentMethodOptions' with all required fields.
mkSetupIntentPaymentMethodOptions :: SetupIntentPaymentMethodOptions
mkSetupIntentPaymentMethodOptions :: SetupIntentPaymentMethodOptions
mkSetupIntentPaymentMethodOptions =
  SetupIntentPaymentMethodOptions :: Maybe SetupIntentPaymentMethodOptionsAcssDebit
-> Maybe SetupIntentPaymentMethodOptionsCard
-> Maybe SetupIntentPaymentMethodOptionsSepaDebit
-> SetupIntentPaymentMethodOptions
SetupIntentPaymentMethodOptions
    { setupIntentPaymentMethodOptionsAcssDebit :: Maybe SetupIntentPaymentMethodOptionsAcssDebit
setupIntentPaymentMethodOptionsAcssDebit = Maybe SetupIntentPaymentMethodOptionsAcssDebit
forall a. Maybe a
GHC.Maybe.Nothing,
      setupIntentPaymentMethodOptionsCard :: Maybe SetupIntentPaymentMethodOptionsCard
setupIntentPaymentMethodOptionsCard = Maybe SetupIntentPaymentMethodOptionsCard
forall a. Maybe a
GHC.Maybe.Nothing,
      setupIntentPaymentMethodOptionsSepaDebit :: Maybe SetupIntentPaymentMethodOptionsSepaDebit
setupIntentPaymentMethodOptionsSepaDebit = Maybe SetupIntentPaymentMethodOptionsSepaDebit
forall a. Maybe a
GHC.Maybe.Nothing
    }