{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module StripeAPI.Types.SetupIntentNextAction 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.SetupIntentNextActionRedirectToUrl
import {-# SOURCE #-} StripeAPI.Types.SetupIntentNextActionVerifyWithMicrodeposits
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe
data SetupIntentNextAction = SetupIntentNextAction
  { 
    SetupIntentNextAction -> Maybe SetupIntentNextActionRedirectToUrl
setupIntentNextActionRedirectToUrl :: (GHC.Maybe.Maybe SetupIntentNextActionRedirectToUrl),
    
    
    
    
    
    SetupIntentNextAction -> Text
setupIntentNextActionType :: Data.Text.Internal.Text,
    
    SetupIntentNextAction -> Maybe Object
setupIntentNextActionUseStripeSdk :: (GHC.Maybe.Maybe Data.Aeson.Types.Internal.Object),
    
    SetupIntentNextAction
-> Maybe SetupIntentNextActionVerifyWithMicrodeposits
setupIntentNextActionVerifyWithMicrodeposits :: (GHC.Maybe.Maybe SetupIntentNextActionVerifyWithMicrodeposits)
  }
  deriving
    ( Int -> SetupIntentNextAction -> ShowS
[SetupIntentNextAction] -> ShowS
SetupIntentNextAction -> String
(Int -> SetupIntentNextAction -> ShowS)
-> (SetupIntentNextAction -> String)
-> ([SetupIntentNextAction] -> ShowS)
-> Show SetupIntentNextAction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetupIntentNextAction] -> ShowS
$cshowList :: [SetupIntentNextAction] -> ShowS
show :: SetupIntentNextAction -> String
$cshow :: SetupIntentNextAction -> String
showsPrec :: Int -> SetupIntentNextAction -> ShowS
$cshowsPrec :: Int -> SetupIntentNextAction -> ShowS
GHC.Show.Show,
      SetupIntentNextAction -> SetupIntentNextAction -> Bool
(SetupIntentNextAction -> SetupIntentNextAction -> Bool)
-> (SetupIntentNextAction -> SetupIntentNextAction -> Bool)
-> Eq SetupIntentNextAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetupIntentNextAction -> SetupIntentNextAction -> Bool
$c/= :: SetupIntentNextAction -> SetupIntentNextAction -> Bool
== :: SetupIntentNextAction -> SetupIntentNextAction -> Bool
$c== :: SetupIntentNextAction -> SetupIntentNextAction -> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON SetupIntentNextAction where
  toJSON :: SetupIntentNextAction -> Value
toJSON SetupIntentNextAction
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"redirect_to_url" Text -> Maybe SetupIntentNextActionRedirectToUrl -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupIntentNextAction -> Maybe SetupIntentNextActionRedirectToUrl
setupIntentNextActionRedirectToUrl SetupIntentNextAction
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"type" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupIntentNextAction -> Text
setupIntentNextActionType SetupIntentNextAction
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"use_stripe_sdk" Text -> Maybe Object -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupIntentNextAction -> Maybe Object
setupIntentNextActionUseStripeSdk SetupIntentNextAction
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"verify_with_microdeposits" Text -> Maybe SetupIntentNextActionVerifyWithMicrodeposits -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupIntentNextAction
-> Maybe SetupIntentNextActionVerifyWithMicrodeposits
setupIntentNextActionVerifyWithMicrodeposits SetupIntentNextAction
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: SetupIntentNextAction -> Encoding
toEncoding SetupIntentNextAction
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"redirect_to_url" Text -> Maybe SetupIntentNextActionRedirectToUrl -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupIntentNextAction -> Maybe SetupIntentNextActionRedirectToUrl
setupIntentNextActionRedirectToUrl SetupIntentNextAction
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"type" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupIntentNextAction -> Text
setupIntentNextActionType SetupIntentNextAction
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"use_stripe_sdk" Text -> Maybe Object -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupIntentNextAction -> Maybe Object
setupIntentNextActionUseStripeSdk SetupIntentNextAction
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"verify_with_microdeposits" Text
-> Maybe SetupIntentNextActionVerifyWithMicrodeposits -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SetupIntentNextAction
-> Maybe SetupIntentNextActionVerifyWithMicrodeposits
setupIntentNextActionVerifyWithMicrodeposits SetupIntentNextAction
obj))))
instance Data.Aeson.Types.FromJSON.FromJSON SetupIntentNextAction where
  parseJSON :: Value -> Parser SetupIntentNextAction
parseJSON = String
-> (Object -> Parser SetupIntentNextAction)
-> Value
-> Parser SetupIntentNextAction
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"SetupIntentNextAction" (\Object
obj -> ((((Maybe SetupIntentNextActionRedirectToUrl
 -> Text
 -> Maybe Object
 -> Maybe SetupIntentNextActionVerifyWithMicrodeposits
 -> SetupIntentNextAction)
-> Parser
     (Maybe SetupIntentNextActionRedirectToUrl
      -> Text
      -> Maybe Object
      -> Maybe SetupIntentNextActionVerifyWithMicrodeposits
      -> SetupIntentNextAction)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe SetupIntentNextActionRedirectToUrl
-> Text
-> Maybe Object
-> Maybe SetupIntentNextActionVerifyWithMicrodeposits
-> SetupIntentNextAction
SetupIntentNextAction Parser
  (Maybe SetupIntentNextActionRedirectToUrl
   -> Text
   -> Maybe Object
   -> Maybe SetupIntentNextActionVerifyWithMicrodeposits
   -> SetupIntentNextAction)
-> Parser (Maybe SetupIntentNextActionRedirectToUrl)
-> Parser
     (Text
      -> Maybe Object
      -> Maybe SetupIntentNextActionVerifyWithMicrodeposits
      -> SetupIntentNextAction)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe SetupIntentNextActionRedirectToUrl)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"redirect_to_url")) Parser
  (Text
   -> Maybe Object
   -> Maybe SetupIntentNextActionVerifyWithMicrodeposits
   -> SetupIntentNextAction)
-> Parser Text
-> Parser
     (Maybe Object
      -> Maybe SetupIntentNextActionVerifyWithMicrodeposits
      -> SetupIntentNextAction)
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
"type")) Parser
  (Maybe Object
   -> Maybe SetupIntentNextActionVerifyWithMicrodeposits
   -> SetupIntentNextAction)
-> Parser (Maybe Object)
-> Parser
     (Maybe SetupIntentNextActionVerifyWithMicrodeposits
      -> SetupIntentNextAction)
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
"use_stripe_sdk")) Parser
  (Maybe SetupIntentNextActionVerifyWithMicrodeposits
   -> SetupIntentNextAction)
-> Parser (Maybe SetupIntentNextActionVerifyWithMicrodeposits)
-> Parser SetupIntentNextAction
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text
-> Parser (Maybe SetupIntentNextActionVerifyWithMicrodeposits)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"verify_with_microdeposits"))
mkSetupIntentNextAction ::
  
  Data.Text.Internal.Text ->
  SetupIntentNextAction
mkSetupIntentNextAction :: Text -> SetupIntentNextAction
mkSetupIntentNextAction Text
setupIntentNextActionType =
  SetupIntentNextAction :: Maybe SetupIntentNextActionRedirectToUrl
-> Text
-> Maybe Object
-> Maybe SetupIntentNextActionVerifyWithMicrodeposits
-> SetupIntentNextAction
SetupIntentNextAction
    { setupIntentNextActionRedirectToUrl :: Maybe SetupIntentNextActionRedirectToUrl
setupIntentNextActionRedirectToUrl = Maybe SetupIntentNextActionRedirectToUrl
forall a. Maybe a
GHC.Maybe.Nothing,
      setupIntentNextActionType :: Text
setupIntentNextActionType = Text
setupIntentNextActionType,
      setupIntentNextActionUseStripeSdk :: Maybe Object
setupIntentNextActionUseStripeSdk = Maybe Object
forall a. Maybe a
GHC.Maybe.Nothing,
      setupIntentNextActionVerifyWithMicrodeposits :: Maybe SetupIntentNextActionVerifyWithMicrodeposits
setupIntentNextActionVerifyWithMicrodeposits = Maybe SetupIntentNextActionVerifyWithMicrodeposits
forall a. Maybe a
GHC.Maybe.Nothing
    }