{-# 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 SetupAttemptPaymentMethodDetailsCard
module StripeAPI.Types.SetupAttemptPaymentMethodDetailsCard 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.ThreeDSecureDetails
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe

-- | Defines the object schema located at @components.schemas.setup_attempt_payment_method_details_card@ in the specification.
data SetupAttemptPaymentMethodDetailsCard = SetupAttemptPaymentMethodDetailsCard
  { -- | three_d_secure: Populated if this authorization used 3D Secure authentication.
    SetupAttemptPaymentMethodDetailsCard
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'
setupAttemptPaymentMethodDetailsCardThreeDSecure :: (GHC.Maybe.Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure')
  }
  deriving
    ( Int -> SetupAttemptPaymentMethodDetailsCard -> ShowS
[SetupAttemptPaymentMethodDetailsCard] -> ShowS
SetupAttemptPaymentMethodDetailsCard -> String
(Int -> SetupAttemptPaymentMethodDetailsCard -> ShowS)
-> (SetupAttemptPaymentMethodDetailsCard -> String)
-> ([SetupAttemptPaymentMethodDetailsCard] -> ShowS)
-> Show SetupAttemptPaymentMethodDetailsCard
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetupAttemptPaymentMethodDetailsCard] -> ShowS
$cshowList :: [SetupAttemptPaymentMethodDetailsCard] -> ShowS
show :: SetupAttemptPaymentMethodDetailsCard -> String
$cshow :: SetupAttemptPaymentMethodDetailsCard -> String
showsPrec :: Int -> SetupAttemptPaymentMethodDetailsCard -> ShowS
$cshowsPrec :: Int -> SetupAttemptPaymentMethodDetailsCard -> ShowS
GHC.Show.Show,
      SetupAttemptPaymentMethodDetailsCard
-> SetupAttemptPaymentMethodDetailsCard -> Bool
(SetupAttemptPaymentMethodDetailsCard
 -> SetupAttemptPaymentMethodDetailsCard -> Bool)
-> (SetupAttemptPaymentMethodDetailsCard
    -> SetupAttemptPaymentMethodDetailsCard -> Bool)
-> Eq SetupAttemptPaymentMethodDetailsCard
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetupAttemptPaymentMethodDetailsCard
-> SetupAttemptPaymentMethodDetailsCard -> Bool
$c/= :: SetupAttemptPaymentMethodDetailsCard
-> SetupAttemptPaymentMethodDetailsCard -> Bool
== :: SetupAttemptPaymentMethodDetailsCard
-> SetupAttemptPaymentMethodDetailsCard -> Bool
$c== :: SetupAttemptPaymentMethodDetailsCard
-> SetupAttemptPaymentMethodDetailsCard -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON SetupAttemptPaymentMethodDetailsCard where
  toJSON :: SetupAttemptPaymentMethodDetailsCard -> Value
toJSON SetupAttemptPaymentMethodDetailsCard
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"three_d_secure" Text
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupAttemptPaymentMethodDetailsCard
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'
setupAttemptPaymentMethodDetailsCardThreeDSecure SetupAttemptPaymentMethodDetailsCard
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: SetupAttemptPaymentMethodDetailsCard -> Encoding
toEncoding SetupAttemptPaymentMethodDetailsCard
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs (Text
"three_d_secure" Text
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupAttemptPaymentMethodDetailsCard
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'
setupAttemptPaymentMethodDetailsCardThreeDSecure SetupAttemptPaymentMethodDetailsCard
obj)

instance Data.Aeson.Types.FromJSON.FromJSON SetupAttemptPaymentMethodDetailsCard where
  parseJSON :: Value -> Parser SetupAttemptPaymentMethodDetailsCard
parseJSON = String
-> (Object -> Parser SetupAttemptPaymentMethodDetailsCard)
-> Value
-> Parser SetupAttemptPaymentMethodDetailsCard
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"SetupAttemptPaymentMethodDetailsCard" (\Object
obj -> (Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'
 -> SetupAttemptPaymentMethodDetailsCard)
-> Parser
     (Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'
      -> SetupAttemptPaymentMethodDetailsCard)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> SetupAttemptPaymentMethodDetailsCard
SetupAttemptPaymentMethodDetailsCard Parser
  (Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'
   -> SetupAttemptPaymentMethodDetailsCard)
-> Parser (Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure')
-> Parser SetupAttemptPaymentMethodDetailsCard
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"three_d_secure"))

-- | Create a new 'SetupAttemptPaymentMethodDetailsCard' with all required fields.
mkSetupAttemptPaymentMethodDetailsCard :: SetupAttemptPaymentMethodDetailsCard
mkSetupAttemptPaymentMethodDetailsCard :: SetupAttemptPaymentMethodDetailsCard
mkSetupAttemptPaymentMethodDetailsCard = SetupAttemptPaymentMethodDetailsCard :: Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> SetupAttemptPaymentMethodDetailsCard
SetupAttemptPaymentMethodDetailsCard {setupAttemptPaymentMethodDetailsCardThreeDSecure :: Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'
setupAttemptPaymentMethodDetailsCardThreeDSecure = Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'
forall a. Maybe a
GHC.Maybe.Nothing}

-- | Defines the object schema located at @components.schemas.setup_attempt_payment_method_details_card.properties.three_d_secure.anyOf@ in the specification.
--
-- Populated if this authorization used 3D Secure authentication.
data SetupAttemptPaymentMethodDetailsCardThreeDSecure' = SetupAttemptPaymentMethodDetailsCardThreeDSecure'
  { -- | authentication_flow: For authenticated transactions: how the customer was authenticated by
    -- the issuing bank.
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> Maybe
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
setupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow :: (GHC.Maybe.Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'),
    -- | result: Indicates the outcome of 3D Secure authentication.
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
setupAttemptPaymentMethodDetailsCardThreeDSecure'Result :: (GHC.Maybe.Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'),
    -- | result_reason: Additional information about why 3D Secure succeeded or failed based
    -- on the \`result\`.
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> Maybe
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
setupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason :: (GHC.Maybe.Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'),
    -- | version: The version of 3D Secure that was used.
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
setupAttemptPaymentMethodDetailsCardThreeDSecure'Version :: (GHC.Maybe.Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version')
  }
  deriving
    ( Int -> SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> ShowS
[SetupAttemptPaymentMethodDetailsCardThreeDSecure'] -> ShowS
SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> String
(Int -> SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> ShowS)
-> (SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> String)
-> ([SetupAttemptPaymentMethodDetailsCardThreeDSecure'] -> ShowS)
-> Show SetupAttemptPaymentMethodDetailsCardThreeDSecure'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetupAttemptPaymentMethodDetailsCardThreeDSecure'] -> ShowS
$cshowList :: [SetupAttemptPaymentMethodDetailsCardThreeDSecure'] -> ShowS
show :: SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> String
$cshow :: SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> String
showsPrec :: Int -> SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> ShowS
$cshowsPrec :: Int -> SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> ShowS
GHC.Show.Show,
      SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> Bool
(SetupAttemptPaymentMethodDetailsCardThreeDSecure'
 -> SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> Bool)
-> (SetupAttemptPaymentMethodDetailsCardThreeDSecure'
    -> SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> Bool)
-> Eq SetupAttemptPaymentMethodDetailsCardThreeDSecure'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> Bool
$c/= :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> Bool
== :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> Bool
$c== :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON SetupAttemptPaymentMethodDetailsCardThreeDSecure' where
  toJSON :: SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> Value
toJSON SetupAttemptPaymentMethodDetailsCardThreeDSecure'
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"authentication_flow" Text
-> Maybe
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> Maybe
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
setupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow SetupAttemptPaymentMethodDetailsCardThreeDSecure'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"result" Text
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
setupAttemptPaymentMethodDetailsCardThreeDSecure'Result SetupAttemptPaymentMethodDetailsCardThreeDSecure'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"result_reason" Text
-> Maybe
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> Maybe
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
setupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason SetupAttemptPaymentMethodDetailsCardThreeDSecure'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"version" Text
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
setupAttemptPaymentMethodDetailsCardThreeDSecure'Version SetupAttemptPaymentMethodDetailsCardThreeDSecure'
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: SetupAttemptPaymentMethodDetailsCardThreeDSecure' -> Encoding
toEncoding SetupAttemptPaymentMethodDetailsCardThreeDSecure'
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"authentication_flow" Text
-> Maybe
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> Maybe
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
setupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow SetupAttemptPaymentMethodDetailsCardThreeDSecure'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"result" Text
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
setupAttemptPaymentMethodDetailsCardThreeDSecure'Result SetupAttemptPaymentMethodDetailsCardThreeDSecure'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"result_reason" Text
-> Maybe
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> Maybe
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
setupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason SetupAttemptPaymentMethodDetailsCardThreeDSecure'
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"version" Text
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupAttemptPaymentMethodDetailsCardThreeDSecure'
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
setupAttemptPaymentMethodDetailsCardThreeDSecure'Version SetupAttemptPaymentMethodDetailsCardThreeDSecure'
obj))))

instance Data.Aeson.Types.FromJSON.FromJSON SetupAttemptPaymentMethodDetailsCardThreeDSecure' where
  parseJSON :: Value -> Parser SetupAttemptPaymentMethodDetailsCardThreeDSecure'
parseJSON = String
-> (Object
    -> Parser SetupAttemptPaymentMethodDetailsCardThreeDSecure')
-> Value
-> Parser SetupAttemptPaymentMethodDetailsCardThreeDSecure'
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"SetupAttemptPaymentMethodDetailsCardThreeDSecure'" (\Object
obj -> ((((Maybe
   SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
 -> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
 -> Maybe
      SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
 -> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
 -> SetupAttemptPaymentMethodDetailsCardThreeDSecure')
-> Parser
     (Maybe
        SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
      -> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
      -> Maybe
           SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
      -> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
      -> SetupAttemptPaymentMethodDetailsCardThreeDSecure')
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe
  SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
-> Maybe
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'
SetupAttemptPaymentMethodDetailsCardThreeDSecure' Parser
  (Maybe
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
   -> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
   -> Maybe
        SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
   -> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
   -> SetupAttemptPaymentMethodDetailsCardThreeDSecure')
-> Parser
     (Maybe
        SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow')
-> Parser
     (Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
      -> Maybe
           SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
      -> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
      -> SetupAttemptPaymentMethodDetailsCardThreeDSecure')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"authentication_flow")) Parser
  (Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
   -> Maybe
        SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
   -> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
   -> SetupAttemptPaymentMethodDetailsCardThreeDSecure')
-> Parser
     (Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result')
-> Parser
     (Maybe
        SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
      -> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
      -> SetupAttemptPaymentMethodDetailsCardThreeDSecure')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"result")) Parser
  (Maybe
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
   -> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
   -> SetupAttemptPaymentMethodDetailsCardThreeDSecure')
-> Parser
     (Maybe
        SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason')
-> Parser
     (Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
      -> SetupAttemptPaymentMethodDetailsCardThreeDSecure')
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe
        SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"result_reason")) Parser
  (Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
   -> SetupAttemptPaymentMethodDetailsCardThreeDSecure')
-> Parser
     (Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version')
-> Parser SetupAttemptPaymentMethodDetailsCardThreeDSecure'
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser
     (Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version')
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"version"))

-- | Create a new 'SetupAttemptPaymentMethodDetailsCardThreeDSecure'' with all required fields.
mkSetupAttemptPaymentMethodDetailsCardThreeDSecure' :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'
mkSetupAttemptPaymentMethodDetailsCardThreeDSecure' :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'
mkSetupAttemptPaymentMethodDetailsCardThreeDSecure' =
  SetupAttemptPaymentMethodDetailsCardThreeDSecure' :: Maybe
  SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
-> Maybe
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'
    { setupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow :: Maybe
  SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
setupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow = Maybe
  SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
forall a. Maybe a
GHC.Maybe.Nothing,
      setupAttemptPaymentMethodDetailsCardThreeDSecure'Result :: Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
setupAttemptPaymentMethodDetailsCardThreeDSecure'Result = Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
forall a. Maybe a
GHC.Maybe.Nothing,
      setupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason :: Maybe
  SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
setupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason = Maybe
  SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
forall a. Maybe a
GHC.Maybe.Nothing,
      setupAttemptPaymentMethodDetailsCardThreeDSecure'Version :: Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
setupAttemptPaymentMethodDetailsCardThreeDSecure'Version = Maybe SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
forall a. Maybe a
GHC.Maybe.Nothing
    }

-- | Defines the enum schema located at @components.schemas.setup_attempt_payment_method_details_card.properties.three_d_secure.anyOf.properties.authentication_flow@ in the specification.
--
-- For authenticated transactions: how the customer was authenticated by
-- the issuing bank.
data SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'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.
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"challenge"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'EnumChallenge
  | -- | Represents the JSON value @"frictionless"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'EnumFrictionless
  deriving (Int
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> ShowS
[SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow']
-> ShowS
SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> String
(Int
 -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
 -> ShowS)
-> (SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
    -> String)
-> ([SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow']
    -> ShowS)
-> Show
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow']
-> ShowS
$cshowList :: [SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow']
-> ShowS
show :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> String
$cshow :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> String
showsPrec :: Int
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> ShowS
$cshowsPrec :: Int
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> ShowS
GHC.Show.Show, SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> Bool
(SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
 -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
 -> Bool)
-> (SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
    -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
    -> Bool)
-> Eq
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> Bool
$c/= :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> Bool
== :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> Bool
$c== :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow' where
  toJSON :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> Value
toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'Other Value
val) = Value
val
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'EnumChallenge) = Value
"challenge"
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'EnumFrictionless) = Value
"frictionless"

instance Data.Aeson.Types.FromJSON.FromJSON SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow' where
  parseJSON :: Value
-> Parser
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
parseJSON Value
val =
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
-> Parser
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
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
"challenge" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'EnumChallenge
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"frictionless" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'EnumFrictionless
            | Bool
GHC.Base.otherwise -> Value
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'AuthenticationFlow'Other Value
val
      )

-- | Defines the enum schema located at @components.schemas.setup_attempt_payment_method_details_card.properties.three_d_secure.anyOf.properties.result@ in the specification.
--
-- Indicates the outcome of 3D Secure authentication.
data SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'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.
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"attempt_acknowledged"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'EnumAttemptAcknowledged
  | -- | Represents the JSON value @"authenticated"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'EnumAuthenticated
  | -- | Represents the JSON value @"failed"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'EnumFailed
  | -- | Represents the JSON value @"not_supported"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'EnumNotSupported
  | -- | Represents the JSON value @"processing_error"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'EnumProcessingError
  deriving (Int
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
-> ShowS
[SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'] -> ShowS
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result' -> String
(Int
 -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
 -> ShowS)
-> (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
    -> String)
-> ([SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result']
    -> ShowS)
-> Show SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'] -> ShowS
$cshowList :: [SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'] -> ShowS
show :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result' -> String
$cshow :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result' -> String
showsPrec :: Int
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
-> ShowS
$cshowsPrec :: Int
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
-> ShowS
GHC.Show.Show, SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result' -> Bool
(SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
 -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
 -> Bool)
-> (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
    -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
    -> Bool)
-> Eq SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result' -> Bool
$c/= :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result' -> Bool
== :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result' -> Bool
$c== :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result' -> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result' where
  toJSON :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result' -> Value
toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'Other Value
val) = Value
val
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'EnumAttemptAcknowledged) = Value
"attempt_acknowledged"
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'EnumAuthenticated) = Value
"authenticated"
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'EnumFailed) = Value
"failed"
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'EnumNotSupported) = Value
"not_supported"
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'EnumProcessingError) = Value
"processing_error"

instance Data.Aeson.Types.FromJSON.FromJSON SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result' where
  parseJSON :: Value
-> Parser SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
parseJSON Value
val =
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
-> Parser SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
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
"attempt_acknowledged" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'EnumAttemptAcknowledged
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"authenticated" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'EnumAuthenticated
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"failed" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'EnumFailed
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"not_supported" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'EnumNotSupported
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"processing_error" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'EnumProcessingError
            | Bool
GHC.Base.otherwise -> Value -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Result'Other Value
val
      )

-- | Defines the enum schema located at @components.schemas.setup_attempt_payment_method_details_card.properties.three_d_secure.anyOf.properties.result_reason@ in the specification.
--
-- Additional information about why 3D Secure succeeded or failed based
-- on the \`result\`.
data SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'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.
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"abandoned"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumAbandoned
  | -- | Represents the JSON value @"bypassed"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumBypassed
  | -- | Represents the JSON value @"canceled"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumCanceled
  | -- | Represents the JSON value @"card_not_enrolled"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumCardNotEnrolled
  | -- | Represents the JSON value @"network_not_supported"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumNetworkNotSupported
  | -- | Represents the JSON value @"protocol_error"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumProtocolError
  | -- | Represents the JSON value @"rejected"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumRejected
  deriving (Int
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> ShowS
[SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason']
-> ShowS
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> String
(Int
 -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
 -> ShowS)
-> (SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
    -> String)
-> ([SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason']
    -> ShowS)
-> Show
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason']
-> ShowS
$cshowList :: [SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason']
-> ShowS
show :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> String
$cshow :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> String
showsPrec :: Int
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> ShowS
$cshowsPrec :: Int
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> ShowS
GHC.Show.Show, SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> Bool
(SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
 -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
 -> Bool)
-> (SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
    -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
    -> Bool)
-> Eq
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> Bool
$c/= :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> Bool
== :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> Bool
$c== :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason' where
  toJSON :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> Value
toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'Other Value
val) = Value
val
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumAbandoned) = Value
"abandoned"
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumBypassed) = Value
"bypassed"
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumCanceled) = Value
"canceled"
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumCardNotEnrolled) = Value
"card_not_enrolled"
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumNetworkNotSupported) = Value
"network_not_supported"
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumProtocolError) = Value
"protocol_error"
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumRejected) = Value
"rejected"

instance Data.Aeson.Types.FromJSON.FromJSON SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason' where
  parseJSON :: Value
-> Parser
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
parseJSON Value
val =
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
-> Parser
     SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
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
"abandoned" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumAbandoned
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"bypassed" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumBypassed
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"canceled" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumCanceled
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"card_not_enrolled" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumCardNotEnrolled
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"network_not_supported" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumNetworkNotSupported
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"protocol_error" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumProtocolError
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"rejected" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'EnumRejected
            | Bool
GHC.Base.otherwise -> Value
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'ResultReason'Other Value
val
      )

-- | Defines the enum schema located at @components.schemas.setup_attempt_payment_method_details_card.properties.three_d_secure.anyOf.properties.version@ in the specification.
--
-- The version of 3D Secure that was used.
data SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
  = -- | This case is used if the value encountered during decoding does not match any of the provided cases in the specification.
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'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.
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'Typed Data.Text.Internal.Text
  | -- | Represents the JSON value @"1.0.2"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'Enum1'0'2
  | -- | Represents the JSON value @"2.1.0"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'Enum2'1'0
  | -- | Represents the JSON value @"2.2.0"@
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'Enum2'2'0
  deriving (Int
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> ShowS
[SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version']
-> ShowS
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version' -> String
(Int
 -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
 -> ShowS)
-> (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
    -> String)
-> ([SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version']
    -> ShowS)
-> Show SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version']
-> ShowS
$cshowList :: [SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version']
-> ShowS
show :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version' -> String
$cshow :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version' -> String
showsPrec :: Int
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> ShowS
$cshowsPrec :: Int
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> ShowS
GHC.Show.Show, SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> Bool
(SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
 -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
 -> Bool)
-> (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
    -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
    -> Bool)
-> Eq SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> Bool
$c/= :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> Bool
== :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> Bool
$c== :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> Bool
GHC.Classes.Eq)

instance Data.Aeson.Types.ToJSON.ToJSON SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version' where
  toJSON :: SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version' -> Value
toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'Other Value
val) = Value
val
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'Enum1'0'2) = Value
"1.0.2"
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'Enum2'1'0) = Value
"2.1.0"
  toJSON (SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'Enum2'2'0) = Value
"2.2.0"

instance Data.Aeson.Types.FromJSON.FromJSON SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version' where
  parseJSON :: Value
-> Parser SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
parseJSON Value
val =
    SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
-> Parser SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
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
"1.0.2" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'Enum1'0'2
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"2.1.0" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'Enum2'1'0
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"2.2.0" -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'Enum2'2'0
            | Bool
GHC.Base.otherwise -> Value -> SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'
SetupAttemptPaymentMethodDetailsCardThreeDSecure'Version'Other Value
val
      )