{-# 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 SourceMandateNotification
module StripeAPI.Types.SourceMandateNotification 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.Source
import {-# SOURCE #-} StripeAPI.Types.SourceMandateNotificationAcssDebitData
import {-# SOURCE #-} StripeAPI.Types.SourceMandateNotificationBacsDebitData
import {-# SOURCE #-} StripeAPI.Types.SourceMandateNotificationSepaDebitData
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe

-- | Defines the object schema located at @components.schemas.source_mandate_notification@ in the specification.
--
-- Source mandate notifications should be created when a notification related to
-- a source mandate must be sent to the payer. They will trigger a webhook or
-- deliver an email to the customer.
data SourceMandateNotification = SourceMandateNotification
  { -- | acss_debit:
    SourceMandateNotification
-> Maybe SourceMandateNotificationAcssDebitData
sourceMandateNotificationAcssDebit :: (GHC.Maybe.Maybe SourceMandateNotificationAcssDebitData),
    -- | amount: A positive integer in the smallest currency unit (that is, 100 cents for \$1.00, or 1 for ¥1, Japanese Yen being a zero-decimal currency) representing the amount associated with the mandate notification. The amount is expressed in the currency of the underlying source. Required if the notification type is \`debit_initiated\`.
    SourceMandateNotification -> Maybe Int
sourceMandateNotificationAmount :: (GHC.Maybe.Maybe GHC.Types.Int),
    -- | bacs_debit:
    SourceMandateNotification
-> Maybe SourceMandateNotificationBacsDebitData
sourceMandateNotificationBacsDebit :: (GHC.Maybe.Maybe SourceMandateNotificationBacsDebitData),
    -- | created: Time at which the object was created. Measured in seconds since the Unix epoch.
    SourceMandateNotification -> Int
sourceMandateNotificationCreated :: GHC.Types.Int,
    -- | id: Unique identifier for the object.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    SourceMandateNotification -> Text
sourceMandateNotificationId :: Data.Text.Internal.Text,
    -- | livemode: Has the value \`true\` if the object exists in live mode or the value \`false\` if the object exists in test mode.
    SourceMandateNotification -> Bool
sourceMandateNotificationLivemode :: GHC.Types.Bool,
    -- | reason: The reason of the mandate notification. Valid reasons are \`mandate_confirmed\` or \`debit_initiated\`.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    SourceMandateNotification -> Text
sourceMandateNotificationReason :: Data.Text.Internal.Text,
    -- | sepa_debit:
    SourceMandateNotification
-> Maybe SourceMandateNotificationSepaDebitData
sourceMandateNotificationSepaDebit :: (GHC.Maybe.Maybe SourceMandateNotificationSepaDebitData),
    -- | source: \`Source\` objects allow you to accept a variety of payment methods. They
    -- represent a customer\'s payment instrument, and can be used with the Stripe API
    -- just like a \`Card\` object: once chargeable, they can be charged, or can be
    -- attached to customers.
    --
    -- Related guides: [Sources API](https:\/\/stripe.com\/docs\/sources) and [Sources & Customers](https:\/\/stripe.com\/docs\/sources\/customers).
    SourceMandateNotification -> Source
sourceMandateNotificationSource :: Source,
    -- | status: The status of the mandate notification. Valid statuses are \`pending\` or \`submitted\`.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    SourceMandateNotification -> Text
sourceMandateNotificationStatus :: Data.Text.Internal.Text,
    -- | type: The type of source this mandate notification is attached to. Should be the source type identifier code for the payment method, such as \`three_d_secure\`.
    --
    -- Constraints:
    --
    -- * Maximum length of 5000
    SourceMandateNotification -> Text
sourceMandateNotificationType :: Data.Text.Internal.Text
  }
  deriving
    ( Int -> SourceMandateNotification -> ShowS
[SourceMandateNotification] -> ShowS
SourceMandateNotification -> String
(Int -> SourceMandateNotification -> ShowS)
-> (SourceMandateNotification -> String)
-> ([SourceMandateNotification] -> ShowS)
-> Show SourceMandateNotification
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceMandateNotification] -> ShowS
$cshowList :: [SourceMandateNotification] -> ShowS
show :: SourceMandateNotification -> String
$cshow :: SourceMandateNotification -> String
showsPrec :: Int -> SourceMandateNotification -> ShowS
$cshowsPrec :: Int -> SourceMandateNotification -> ShowS
GHC.Show.Show,
      SourceMandateNotification -> SourceMandateNotification -> Bool
(SourceMandateNotification -> SourceMandateNotification -> Bool)
-> (SourceMandateNotification -> SourceMandateNotification -> Bool)
-> Eq SourceMandateNotification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceMandateNotification -> SourceMandateNotification -> Bool
$c/= :: SourceMandateNotification -> SourceMandateNotification -> Bool
== :: SourceMandateNotification -> SourceMandateNotification -> Bool
$c== :: SourceMandateNotification -> SourceMandateNotification -> Bool
GHC.Classes.Eq
    )

instance Data.Aeson.Types.ToJSON.ToJSON SourceMandateNotification where
  toJSON :: SourceMandateNotification -> Value
toJSON SourceMandateNotification
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"acss_debit" Text -> Maybe SourceMandateNotificationAcssDebitData -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification
-> Maybe SourceMandateNotificationAcssDebitData
sourceMandateNotificationAcssDebit SourceMandateNotification
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"amount" Text -> Maybe Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification -> Maybe Int
sourceMandateNotificationAmount SourceMandateNotification
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"bacs_debit" Text -> Maybe SourceMandateNotificationBacsDebitData -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification
-> Maybe SourceMandateNotificationBacsDebitData
sourceMandateNotificationBacsDebit SourceMandateNotification
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"created" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification -> Int
sourceMandateNotificationCreated SourceMandateNotification
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"id" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification -> Text
sourceMandateNotificationId SourceMandateNotification
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"livemode" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification -> Bool
sourceMandateNotificationLivemode SourceMandateNotification
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"reason" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification -> Text
sourceMandateNotificationReason SourceMandateNotification
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"sepa_debit" Text -> Maybe SourceMandateNotificationSepaDebitData -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification
-> Maybe SourceMandateNotificationSepaDebitData
sourceMandateNotificationSepaDebit SourceMandateNotification
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"source" Text -> Source -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification -> Source
sourceMandateNotificationSource SourceMandateNotification
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"status" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification -> Text
sourceMandateNotificationStatus SourceMandateNotification
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..= SourceMandateNotification -> Text
sourceMandateNotificationType SourceMandateNotification
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"object" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Text -> Value
Data.Aeson.Types.Internal.String Text
"source_mandate_notification" Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: SourceMandateNotification -> Encoding
toEncoding SourceMandateNotification
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"acss_debit" Text -> Maybe SourceMandateNotificationAcssDebitData -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification
-> Maybe SourceMandateNotificationAcssDebitData
sourceMandateNotificationAcssDebit SourceMandateNotification
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"amount" Text -> Maybe Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification -> Maybe Int
sourceMandateNotificationAmount SourceMandateNotification
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"bacs_debit" Text -> Maybe SourceMandateNotificationBacsDebitData -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification
-> Maybe SourceMandateNotificationBacsDebitData
sourceMandateNotificationBacsDebit SourceMandateNotification
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"created" Text -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification -> Int
sourceMandateNotificationCreated SourceMandateNotification
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"id" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification -> Text
sourceMandateNotificationId SourceMandateNotification
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"livemode" Text -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification -> Bool
sourceMandateNotificationLivemode SourceMandateNotification
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"reason" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification -> Text
sourceMandateNotificationReason SourceMandateNotification
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"sepa_debit" Text -> Maybe SourceMandateNotificationSepaDebitData -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification
-> Maybe SourceMandateNotificationSepaDebitData
sourceMandateNotificationSepaDebit SourceMandateNotification
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"source" Text -> Source -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification -> Source
sourceMandateNotificationSource SourceMandateNotification
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"status" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= SourceMandateNotification -> Text
sourceMandateNotificationStatus SourceMandateNotification
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..= SourceMandateNotification -> Text
sourceMandateNotificationType SourceMandateNotification
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> (Text
"object" Text -> Value -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Text -> Value
Data.Aeson.Types.Internal.String Text
"source_mandate_notification"))))))))))))

instance Data.Aeson.Types.FromJSON.FromJSON SourceMandateNotification where
  parseJSON :: Value -> Parser SourceMandateNotification
parseJSON = String
-> (Object -> Parser SourceMandateNotification)
-> Value
-> Parser SourceMandateNotification
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"SourceMandateNotification" (\Object
obj -> (((((((((((Maybe SourceMandateNotificationAcssDebitData
 -> Maybe Int
 -> Maybe SourceMandateNotificationBacsDebitData
 -> Int
 -> Text
 -> Bool
 -> Text
 -> Maybe SourceMandateNotificationSepaDebitData
 -> Source
 -> Text
 -> Text
 -> SourceMandateNotification)
-> Parser
     (Maybe SourceMandateNotificationAcssDebitData
      -> Maybe Int
      -> Maybe SourceMandateNotificationBacsDebitData
      -> Int
      -> Text
      -> Bool
      -> Text
      -> Maybe SourceMandateNotificationSepaDebitData
      -> Source
      -> Text
      -> Text
      -> SourceMandateNotification)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe SourceMandateNotificationAcssDebitData
-> Maybe Int
-> Maybe SourceMandateNotificationBacsDebitData
-> Int
-> Text
-> Bool
-> Text
-> Maybe SourceMandateNotificationSepaDebitData
-> Source
-> Text
-> Text
-> SourceMandateNotification
SourceMandateNotification Parser
  (Maybe SourceMandateNotificationAcssDebitData
   -> Maybe Int
   -> Maybe SourceMandateNotificationBacsDebitData
   -> Int
   -> Text
   -> Bool
   -> Text
   -> Maybe SourceMandateNotificationSepaDebitData
   -> Source
   -> Text
   -> Text
   -> SourceMandateNotification)
-> Parser (Maybe SourceMandateNotificationAcssDebitData)
-> Parser
     (Maybe Int
      -> Maybe SourceMandateNotificationBacsDebitData
      -> Int
      -> Text
      -> Bool
      -> Text
      -> Maybe SourceMandateNotificationSepaDebitData
      -> Source
      -> Text
      -> Text
      -> SourceMandateNotification)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text -> Parser (Maybe SourceMandateNotificationAcssDebitData)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"acss_debit")) Parser
  (Maybe Int
   -> Maybe SourceMandateNotificationBacsDebitData
   -> Int
   -> Text
   -> Bool
   -> Text
   -> Maybe SourceMandateNotificationSepaDebitData
   -> Source
   -> Text
   -> Text
   -> SourceMandateNotification)
-> Parser (Maybe Int)
-> Parser
     (Maybe SourceMandateNotificationBacsDebitData
      -> Int
      -> Text
      -> Bool
      -> Text
      -> Maybe SourceMandateNotificationSepaDebitData
      -> Source
      -> Text
      -> Text
      -> SourceMandateNotification)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"amount")) Parser
  (Maybe SourceMandateNotificationBacsDebitData
   -> Int
   -> Text
   -> Bool
   -> Text
   -> Maybe SourceMandateNotificationSepaDebitData
   -> Source
   -> Text
   -> Text
   -> SourceMandateNotification)
-> Parser (Maybe SourceMandateNotificationBacsDebitData)
-> Parser
     (Int
      -> Text
      -> Bool
      -> Text
      -> Maybe SourceMandateNotificationSepaDebitData
      -> Source
      -> Text
      -> Text
      -> SourceMandateNotification)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text -> Parser (Maybe SourceMandateNotificationBacsDebitData)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"bacs_debit")) Parser
  (Int
   -> Text
   -> Bool
   -> Text
   -> Maybe SourceMandateNotificationSepaDebitData
   -> Source
   -> Text
   -> Text
   -> SourceMandateNotification)
-> Parser Int
-> Parser
     (Text
      -> Bool
      -> Text
      -> Maybe SourceMandateNotificationSepaDebitData
      -> Source
      -> Text
      -> Text
      -> SourceMandateNotification)
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
"created")) Parser
  (Text
   -> Bool
   -> Text
   -> Maybe SourceMandateNotificationSepaDebitData
   -> Source
   -> Text
   -> Text
   -> SourceMandateNotification)
-> Parser Text
-> Parser
     (Bool
      -> Text
      -> Maybe SourceMandateNotificationSepaDebitData
      -> Source
      -> Text
      -> Text
      -> SourceMandateNotification)
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
"id")) Parser
  (Bool
   -> Text
   -> Maybe SourceMandateNotificationSepaDebitData
   -> Source
   -> Text
   -> Text
   -> SourceMandateNotification)
-> Parser Bool
-> Parser
     (Text
      -> Maybe SourceMandateNotificationSepaDebitData
      -> Source
      -> Text
      -> Text
      -> SourceMandateNotification)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Bool
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"livemode")) Parser
  (Text
   -> Maybe SourceMandateNotificationSepaDebitData
   -> Source
   -> Text
   -> Text
   -> SourceMandateNotification)
-> Parser Text
-> Parser
     (Maybe SourceMandateNotificationSepaDebitData
      -> Source -> Text -> Text -> SourceMandateNotification)
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
"reason")) Parser
  (Maybe SourceMandateNotificationSepaDebitData
   -> Source -> Text -> Text -> SourceMandateNotification)
-> Parser (Maybe SourceMandateNotificationSepaDebitData)
-> Parser (Source -> Text -> Text -> SourceMandateNotification)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object
-> Text -> Parser (Maybe SourceMandateNotificationSepaDebitData)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"sepa_debit")) Parser (Source -> Text -> Text -> SourceMandateNotification)
-> Parser Source
-> Parser (Text -> Text -> SourceMandateNotification)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Source
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"source")) Parser (Text -> Text -> SourceMandateNotification)
-> Parser Text -> Parser (Text -> SourceMandateNotification)
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
"status")) Parser (Text -> SourceMandateNotification)
-> Parser Text -> Parser SourceMandateNotification
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"))

-- | Create a new 'SourceMandateNotification' with all required fields.
mkSourceMandateNotification ::
  -- | 'sourceMandateNotificationCreated'
  GHC.Types.Int ->
  -- | 'sourceMandateNotificationId'
  Data.Text.Internal.Text ->
  -- | 'sourceMandateNotificationLivemode'
  GHC.Types.Bool ->
  -- | 'sourceMandateNotificationReason'
  Data.Text.Internal.Text ->
  -- | 'sourceMandateNotificationSource'
  Source ->
  -- | 'sourceMandateNotificationStatus'
  Data.Text.Internal.Text ->
  -- | 'sourceMandateNotificationType'
  Data.Text.Internal.Text ->
  SourceMandateNotification
mkSourceMandateNotification :: Int
-> Text
-> Bool
-> Text
-> Source
-> Text
-> Text
-> SourceMandateNotification
mkSourceMandateNotification Int
sourceMandateNotificationCreated Text
sourceMandateNotificationId Bool
sourceMandateNotificationLivemode Text
sourceMandateNotificationReason Source
sourceMandateNotificationSource Text
sourceMandateNotificationStatus Text
sourceMandateNotificationType =
  SourceMandateNotification :: Maybe SourceMandateNotificationAcssDebitData
-> Maybe Int
-> Maybe SourceMandateNotificationBacsDebitData
-> Int
-> Text
-> Bool
-> Text
-> Maybe SourceMandateNotificationSepaDebitData
-> Source
-> Text
-> Text
-> SourceMandateNotification
SourceMandateNotification
    { sourceMandateNotificationAcssDebit :: Maybe SourceMandateNotificationAcssDebitData
sourceMandateNotificationAcssDebit = Maybe SourceMandateNotificationAcssDebitData
forall a. Maybe a
GHC.Maybe.Nothing,
      sourceMandateNotificationAmount :: Maybe Int
sourceMandateNotificationAmount = Maybe Int
forall a. Maybe a
GHC.Maybe.Nothing,
      sourceMandateNotificationBacsDebit :: Maybe SourceMandateNotificationBacsDebitData
sourceMandateNotificationBacsDebit = Maybe SourceMandateNotificationBacsDebitData
forall a. Maybe a
GHC.Maybe.Nothing,
      sourceMandateNotificationCreated :: Int
sourceMandateNotificationCreated = Int
sourceMandateNotificationCreated,
      sourceMandateNotificationId :: Text
sourceMandateNotificationId = Text
sourceMandateNotificationId,
      sourceMandateNotificationLivemode :: Bool
sourceMandateNotificationLivemode = Bool
sourceMandateNotificationLivemode,
      sourceMandateNotificationReason :: Text
sourceMandateNotificationReason = Text
sourceMandateNotificationReason,
      sourceMandateNotificationSepaDebit :: Maybe SourceMandateNotificationSepaDebitData
sourceMandateNotificationSepaDebit = Maybe SourceMandateNotificationSepaDebitData
forall a. Maybe a
GHC.Maybe.Nothing,
      sourceMandateNotificationSource :: Source
sourceMandateNotificationSource = Source
sourceMandateNotificationSource,
      sourceMandateNotificationStatus :: Text
sourceMandateNotificationStatus = Text
sourceMandateNotificationStatus,
      sourceMandateNotificationType :: Text
sourceMandateNotificationType = Text
sourceMandateNotificationType
    }