{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module StripeAPI.Types.Card 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.Account
import {-# SOURCE #-} StripeAPI.Types.Customer
import {-# SOURCE #-} StripeAPI.Types.DeletedCustomer
import {-# SOURCE #-} StripeAPI.Types.Recipient
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe
data Card = Card
  { 
    Card -> Maybe CardAccount'Variants
cardAccount :: (GHC.Maybe.Maybe CardAccount'Variants),
    
    
    
    
    
    Card -> Maybe Text
cardAddressCity :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    
    
    Card -> Maybe Text
cardAddressCountry :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    
    
    Card -> Maybe Text
cardAddressLine1 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    
    
    Card -> Maybe Text
cardAddressLine1Check :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    
    
    Card -> Maybe Text
cardAddressLine2 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    
    
    Card -> Maybe Text
cardAddressState :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    
    
    Card -> Maybe Text
cardAddressZip :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    
    
    Card -> Maybe Text
cardAddressZipCheck :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    Card -> Maybe [CardAvailablePayoutMethods']
cardAvailablePayoutMethods :: (GHC.Maybe.Maybe ([CardAvailablePayoutMethods'])),
    
    
    
    
    
    Card -> Text
cardBrand :: Data.Text.Internal.Text,
    
    
    
    
    
    Card -> Maybe Text
cardCountry :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    Card -> Maybe Text
cardCurrency :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    Card -> Maybe CardCustomer'Variants
cardCustomer :: (GHC.Maybe.Maybe CardCustomer'Variants),
    
    
    
    
    
    Card -> Maybe Text
cardCvcCheck :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    Card -> Maybe Bool
cardDefaultForCurrency :: (GHC.Maybe.Maybe GHC.Types.Bool),
    
    
    
    
    
    Card -> Maybe Text
cardDynamicLast4 :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    Card -> Int
cardExpMonth :: GHC.Types.Int,
    
    Card -> Int
cardExpYear :: GHC.Types.Int,
    
    
    
    
    
    
    
    Card -> Maybe Text
cardFingerprint :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    
    
    
    
    Card -> Text
cardFunding :: Data.Text.Internal.Text,
    
    
    
    
    
    Card -> Text
cardId :: Data.Text.Internal.Text,
    
    
    
    
    
    Card -> Text
cardLast4 :: Data.Text.Internal.Text,
    
    Card -> Maybe Object
cardMetadata :: (GHC.Maybe.Maybe Data.Aeson.Types.Internal.Object),
    
    
    
    
    
    Card -> Maybe Text
cardName :: (GHC.Maybe.Maybe Data.Text.Internal.Text),
    
    Card -> Maybe CardRecipient'Variants
cardRecipient :: (GHC.Maybe.Maybe CardRecipient'Variants),
    
    
    
    
    
    Card -> Maybe Text
cardTokenizationMethod :: (GHC.Maybe.Maybe Data.Text.Internal.Text)
  }
  deriving
    ( Int -> Card -> ShowS
[Card] -> ShowS
Card -> String
(Int -> Card -> ShowS)
-> (Card -> String) -> ([Card] -> ShowS) -> Show Card
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Card] -> ShowS
$cshowList :: [Card] -> ShowS
show :: Card -> String
$cshow :: Card -> String
showsPrec :: Int -> Card -> ShowS
$cshowsPrec :: Int -> Card -> ShowS
GHC.Show.Show,
      Card -> Card -> Bool
(Card -> Card -> Bool) -> (Card -> Card -> Bool) -> Eq Card
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Card -> Card -> Bool
$c/= :: Card -> Card -> Bool
== :: Card -> Card -> Bool
$c== :: Card -> Card -> Bool
GHC.Classes.Eq
    )
instance Data.Aeson.Types.ToJSON.ToJSON Card where
  toJSON :: Card -> Value
toJSON Card
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"account" Text -> Maybe CardAccount'Variants -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe CardAccount'Variants
cardAccount Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_city" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressCity Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_country" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressCountry Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_line1" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressLine1 Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_line1_check" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressLine1Check Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_line2" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressLine2 Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_state" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressState Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_zip" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressZip Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"address_zip_check" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressZipCheck Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"available_payout_methods" Text -> Maybe [CardAvailablePayoutMethods'] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe [CardAvailablePayoutMethods']
cardAvailablePayoutMethods Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"brand" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Text
cardBrand Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"country" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardCountry Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"currency" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardCurrency Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"customer" Text -> Maybe CardCustomer'Variants -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe CardCustomer'Variants
cardCustomer Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"cvc_check" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardCvcCheck Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"default_for_currency" Text -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Bool
cardDefaultForCurrency Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"dynamic_last4" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardDynamicLast4 Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"exp_month" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Int
cardExpMonth Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"exp_year" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Int
cardExpYear Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"fingerprint" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardFingerprint Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"funding" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Text
cardFunding Card
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..= Card -> Text
cardId Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"last4" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Text
cardLast4 Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text -> Maybe Object -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Object
cardMetadata Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"name" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardName Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"recipient" Text -> Maybe CardRecipient'Variants -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe CardRecipient'Variants
cardRecipient Card
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"tokenization_method" Text -> Maybe Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardTokenizationMethod Card
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
"card" Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
  toEncoding :: Card -> Encoding
toEncoding Card
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"account" Text -> Maybe CardAccount'Variants -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe CardAccount'Variants
cardAccount Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_city" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressCity Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_country" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressCountry Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_line1" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressLine1 Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_line1_check" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressLine1Check Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_line2" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressLine2 Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_state" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressState Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_zip" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressZip Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"address_zip_check" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardAddressZipCheck Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"available_payout_methods" Text -> Maybe [CardAvailablePayoutMethods'] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe [CardAvailablePayoutMethods']
cardAvailablePayoutMethods Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"brand" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Text
cardBrand Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"country" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardCountry Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"currency" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardCurrency Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"customer" Text -> Maybe CardCustomer'Variants -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe CardCustomer'Variants
cardCustomer Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"cvc_check" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardCvcCheck Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"default_for_currency" Text -> Maybe Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Bool
cardDefaultForCurrency Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"dynamic_last4" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardDynamicLast4 Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"exp_month" Text -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Int
cardExpMonth Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"exp_year" Text -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Int
cardExpYear Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"fingerprint" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardFingerprint Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"funding" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Text
cardFunding Card
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..= Card -> Text
cardId Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"last4" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Text
cardLast4 Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"metadata" Text -> Maybe Object -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Object
cardMetadata Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"name" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardName Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"recipient" Text -> Maybe CardRecipient'Variants -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe CardRecipient'Variants
cardRecipient Card
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"tokenization_method" Text -> Maybe Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Card -> Maybe Text
cardTokenizationMethod Card
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
"card"))))))))))))))))))))))))))))
instance Data.Aeson.Types.FromJSON.FromJSON Card where
  parseJSON :: Value -> Parser Card
parseJSON = String -> (Object -> Parser Card) -> Value -> Parser Card
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"Card" (\Object
obj -> (((((((((((((((((((((((((((Maybe CardAccount'Variants
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe [CardAvailablePayoutMethods']
 -> Text
 -> Maybe Text
 -> Maybe Text
 -> Maybe CardCustomer'Variants
 -> Maybe Text
 -> Maybe Bool
 -> Maybe Text
 -> Int
 -> Int
 -> Maybe Text
 -> Text
 -> Text
 -> Text
 -> Maybe Object
 -> Maybe Text
 -> Maybe CardRecipient'Variants
 -> Maybe Text
 -> Card)
-> Parser
     (Maybe CardAccount'Variants
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe [CardAvailablePayoutMethods']
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe CardCustomer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Maybe CardAccount'Variants
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [CardAvailablePayoutMethods']
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe CardCustomer'Variants
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Int
-> Int
-> Maybe Text
-> Text
-> Text
-> Text
-> Maybe Object
-> Maybe Text
-> Maybe CardRecipient'Variants
-> Maybe Text
-> Card
Card Parser
  (Maybe CardAccount'Variants
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe [CardAvailablePayoutMethods']
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe CardCustomer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe CardAccount'Variants)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe [CardAvailablePayoutMethods']
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe CardCustomer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe CardAccount'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"account")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe [CardAvailablePayoutMethods']
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe CardCustomer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe [CardAvailablePayoutMethods']
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe CardCustomer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"address_city")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe [CardAvailablePayoutMethods']
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe CardCustomer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe [CardAvailablePayoutMethods']
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe CardCustomer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"address_country")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe [CardAvailablePayoutMethods']
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe CardCustomer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe [CardAvailablePayoutMethods']
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe CardCustomer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"address_line1")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe [CardAvailablePayoutMethods']
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe CardCustomer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe [CardAvailablePayoutMethods']
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe CardCustomer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"address_line1_check")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe [CardAvailablePayoutMethods']
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe CardCustomer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe [CardAvailablePayoutMethods']
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe CardCustomer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"address_line2")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe [CardAvailablePayoutMethods']
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe CardCustomer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe [CardAvailablePayoutMethods']
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe CardCustomer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"address_state")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe [CardAvailablePayoutMethods']
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe CardCustomer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe [CardAvailablePayoutMethods']
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe CardCustomer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"address_zip")) Parser
  (Maybe Text
   -> Maybe [CardAvailablePayoutMethods']
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe CardCustomer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe Text)
-> Parser
     (Maybe [CardAvailablePayoutMethods']
      -> Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe CardCustomer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"address_zip_check")) Parser
  (Maybe [CardAvailablePayoutMethods']
   -> Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe CardCustomer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe [CardAvailablePayoutMethods'])
-> Parser
     (Text
      -> Maybe Text
      -> Maybe Text
      -> Maybe CardCustomer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe [CardAvailablePayoutMethods'])
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"available_payout_methods")) Parser
  (Text
   -> Maybe Text
   -> Maybe Text
   -> Maybe CardCustomer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser Text
-> Parser
     (Maybe Text
      -> Maybe Text
      -> Maybe CardCustomer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
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
"brand")) Parser
  (Maybe Text
   -> Maybe Text
   -> Maybe CardCustomer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe Text)
-> Parser
     (Maybe Text
      -> Maybe CardCustomer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"country")) Parser
  (Maybe Text
   -> Maybe CardCustomer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe Text)
-> Parser
     (Maybe CardCustomer'Variants
      -> Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"currency")) Parser
  (Maybe CardCustomer'Variants
   -> Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe CardCustomer'Variants)
-> Parser
     (Maybe Text
      -> Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe CardCustomer'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"customer")) Parser
  (Maybe Text
   -> Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe Text)
-> Parser
     (Maybe Bool
      -> Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"cvc_check")) Parser
  (Maybe Bool
   -> Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe Bool)
-> Parser
     (Maybe Text
      -> Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"default_for_currency")) Parser
  (Maybe Text
   -> Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe Text)
-> Parser
     (Int
      -> Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"dynamic_last4")) Parser
  (Int
   -> Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser Int
-> Parser
     (Int
      -> Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"exp_month")) Parser
  (Int
   -> Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser Int
-> Parser
     (Maybe Text
      -> Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Int
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"exp_year")) Parser
  (Maybe Text
   -> Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe Text)
-> Parser
     (Text
      -> Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"fingerprint")) Parser
  (Text
   -> Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser Text
-> Parser
     (Text
      -> Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
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
"funding")) Parser
  (Text
   -> Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser Text
-> Parser
     (Text
      -> Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
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
  (Text
   -> Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser Text
-> Parser
     (Maybe Object
      -> Maybe Text
      -> Maybe CardRecipient'Variants
      -> Maybe Text
      -> Card)
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
"last4")) Parser
  (Maybe Object
   -> Maybe Text
   -> Maybe CardRecipient'Variants
   -> Maybe Text
   -> Card)
-> Parser (Maybe Object)
-> Parser
     (Maybe Text -> Maybe CardRecipient'Variants -> Maybe Text -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"metadata")) Parser
  (Maybe Text -> Maybe CardRecipient'Variants -> Maybe Text -> Card)
-> Parser (Maybe Text)
-> Parser (Maybe CardRecipient'Variants -> Maybe Text -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"name")) Parser (Maybe CardRecipient'Variants -> Maybe Text -> Card)
-> Parser (Maybe CardRecipient'Variants)
-> Parser (Maybe Text -> Card)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe CardRecipient'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"recipient")) Parser (Maybe Text -> Card) -> Parser (Maybe Text) -> Parser Card
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe Text)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"tokenization_method"))
mkCard ::
  
  Data.Text.Internal.Text ->
  
  GHC.Types.Int ->
  
  GHC.Types.Int ->
  
  Data.Text.Internal.Text ->
  
  Data.Text.Internal.Text ->
  
  Data.Text.Internal.Text ->
  Card
mkCard :: Text -> Int -> Int -> Text -> Text -> Text -> Card
mkCard Text
cardBrand Int
cardExpMonth Int
cardExpYear Text
cardFunding Text
cardId Text
cardLast4 =
  Card :: Maybe CardAccount'Variants
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [CardAvailablePayoutMethods']
-> Text
-> Maybe Text
-> Maybe Text
-> Maybe CardCustomer'Variants
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Int
-> Int
-> Maybe Text
-> Text
-> Text
-> Text
-> Maybe Object
-> Maybe Text
-> Maybe CardRecipient'Variants
-> Maybe Text
-> Card
Card
    { cardAccount :: Maybe CardAccount'Variants
cardAccount = Maybe CardAccount'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      cardAddressCity :: Maybe Text
cardAddressCity = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      cardAddressCountry :: Maybe Text
cardAddressCountry = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      cardAddressLine1 :: Maybe Text
cardAddressLine1 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      cardAddressLine1Check :: Maybe Text
cardAddressLine1Check = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      cardAddressLine2 :: Maybe Text
cardAddressLine2 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      cardAddressState :: Maybe Text
cardAddressState = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      cardAddressZip :: Maybe Text
cardAddressZip = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      cardAddressZipCheck :: Maybe Text
cardAddressZipCheck = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      cardAvailablePayoutMethods :: Maybe [CardAvailablePayoutMethods']
cardAvailablePayoutMethods = Maybe [CardAvailablePayoutMethods']
forall a. Maybe a
GHC.Maybe.Nothing,
      cardBrand :: Text
cardBrand = Text
cardBrand,
      cardCountry :: Maybe Text
cardCountry = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      cardCurrency :: Maybe Text
cardCurrency = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      cardCustomer :: Maybe CardCustomer'Variants
cardCustomer = Maybe CardCustomer'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      cardCvcCheck :: Maybe Text
cardCvcCheck = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      cardDefaultForCurrency :: Maybe Bool
cardDefaultForCurrency = Maybe Bool
forall a. Maybe a
GHC.Maybe.Nothing,
      cardDynamicLast4 :: Maybe Text
cardDynamicLast4 = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      cardExpMonth :: Int
cardExpMonth = Int
cardExpMonth,
      cardExpYear :: Int
cardExpYear = Int
cardExpYear,
      cardFingerprint :: Maybe Text
cardFingerprint = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      cardFunding :: Text
cardFunding = Text
cardFunding,
      cardId :: Text
cardId = Text
cardId,
      cardLast4 :: Text
cardLast4 = Text
cardLast4,
      cardMetadata :: Maybe Object
cardMetadata = Maybe Object
forall a. Maybe a
GHC.Maybe.Nothing,
      cardName :: Maybe Text
cardName = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing,
      cardRecipient :: Maybe CardRecipient'Variants
cardRecipient = Maybe CardRecipient'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
      cardTokenizationMethod :: Maybe Text
cardTokenizationMethod = Maybe Text
forall a. Maybe a
GHC.Maybe.Nothing
    }
data CardAccount'Variants
  = CardAccount'Text Data.Text.Internal.Text
  | CardAccount'Account Account
  deriving (Int -> CardAccount'Variants -> ShowS
[CardAccount'Variants] -> ShowS
CardAccount'Variants -> String
(Int -> CardAccount'Variants -> ShowS)
-> (CardAccount'Variants -> String)
-> ([CardAccount'Variants] -> ShowS)
-> Show CardAccount'Variants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CardAccount'Variants] -> ShowS
$cshowList :: [CardAccount'Variants] -> ShowS
show :: CardAccount'Variants -> String
$cshow :: CardAccount'Variants -> String
showsPrec :: Int -> CardAccount'Variants -> ShowS
$cshowsPrec :: Int -> CardAccount'Variants -> ShowS
GHC.Show.Show, CardAccount'Variants -> CardAccount'Variants -> Bool
(CardAccount'Variants -> CardAccount'Variants -> Bool)
-> (CardAccount'Variants -> CardAccount'Variants -> Bool)
-> Eq CardAccount'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CardAccount'Variants -> CardAccount'Variants -> Bool
$c/= :: CardAccount'Variants -> CardAccount'Variants -> Bool
== :: CardAccount'Variants -> CardAccount'Variants -> Bool
$c== :: CardAccount'Variants -> CardAccount'Variants -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON CardAccount'Variants where
  toJSON :: CardAccount'Variants -> Value
toJSON (CardAccount'Text Text
a) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
a
  toJSON (CardAccount'Account Account
a) = Account -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Account
a
instance Data.Aeson.Types.FromJSON.FromJSON CardAccount'Variants where
  parseJSON :: Value -> Parser CardAccount'Variants
parseJSON Value
val = case (Text -> CardAccount'Variants
CardAccount'Text (Text -> CardAccount'Variants)
-> Result Text -> Result CardAccount'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Text
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result CardAccount'Variants
-> Result CardAccount'Variants -> Result CardAccount'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((Account -> CardAccount'Variants
CardAccount'Account (Account -> CardAccount'Variants)
-> Result Account -> Result CardAccount'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Account
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result CardAccount'Variants
-> Result CardAccount'Variants -> Result CardAccount'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String -> Result CardAccount'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched") of
    Data.Aeson.Types.Internal.Success CardAccount'Variants
a -> CardAccount'Variants -> Parser CardAccount'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure CardAccount'Variants
a
    Data.Aeson.Types.Internal.Error String
a -> String -> Parser CardAccount'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a
data CardAvailablePayoutMethods'
  = 
    CardAvailablePayoutMethods'Other Data.Aeson.Types.Internal.Value
  | 
    CardAvailablePayoutMethods'Typed Data.Text.Internal.Text
  | 
    CardAvailablePayoutMethods'EnumInstant
  | 
    CardAvailablePayoutMethods'EnumStandard
  deriving (Int -> CardAvailablePayoutMethods' -> ShowS
[CardAvailablePayoutMethods'] -> ShowS
CardAvailablePayoutMethods' -> String
(Int -> CardAvailablePayoutMethods' -> ShowS)
-> (CardAvailablePayoutMethods' -> String)
-> ([CardAvailablePayoutMethods'] -> ShowS)
-> Show CardAvailablePayoutMethods'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CardAvailablePayoutMethods'] -> ShowS
$cshowList :: [CardAvailablePayoutMethods'] -> ShowS
show :: CardAvailablePayoutMethods' -> String
$cshow :: CardAvailablePayoutMethods' -> String
showsPrec :: Int -> CardAvailablePayoutMethods' -> ShowS
$cshowsPrec :: Int -> CardAvailablePayoutMethods' -> ShowS
GHC.Show.Show, CardAvailablePayoutMethods' -> CardAvailablePayoutMethods' -> Bool
(CardAvailablePayoutMethods'
 -> CardAvailablePayoutMethods' -> Bool)
-> (CardAvailablePayoutMethods'
    -> CardAvailablePayoutMethods' -> Bool)
-> Eq CardAvailablePayoutMethods'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CardAvailablePayoutMethods' -> CardAvailablePayoutMethods' -> Bool
$c/= :: CardAvailablePayoutMethods' -> CardAvailablePayoutMethods' -> Bool
== :: CardAvailablePayoutMethods' -> CardAvailablePayoutMethods' -> Bool
$c== :: CardAvailablePayoutMethods' -> CardAvailablePayoutMethods' -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON CardAvailablePayoutMethods' where
  toJSON :: CardAvailablePayoutMethods' -> Value
toJSON (CardAvailablePayoutMethods'Other Value
val) = Value
val
  toJSON (CardAvailablePayoutMethods'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
  toJSON (CardAvailablePayoutMethods'
CardAvailablePayoutMethods'EnumInstant) = Value
"instant"
  toJSON (CardAvailablePayoutMethods'
CardAvailablePayoutMethods'EnumStandard) = Value
"standard"
instance Data.Aeson.Types.FromJSON.FromJSON CardAvailablePayoutMethods' where
  parseJSON :: Value -> Parser CardAvailablePayoutMethods'
parseJSON Value
val =
    CardAvailablePayoutMethods' -> Parser CardAvailablePayoutMethods'
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
"instant" -> CardAvailablePayoutMethods'
CardAvailablePayoutMethods'EnumInstant
            | Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"standard" -> CardAvailablePayoutMethods'
CardAvailablePayoutMethods'EnumStandard
            | Bool
GHC.Base.otherwise -> Value -> CardAvailablePayoutMethods'
CardAvailablePayoutMethods'Other Value
val
      )
data CardCustomer'Variants
  = CardCustomer'Text Data.Text.Internal.Text
  | CardCustomer'Customer Customer
  | CardCustomer'DeletedCustomer DeletedCustomer
  deriving (Int -> CardCustomer'Variants -> ShowS
[CardCustomer'Variants] -> ShowS
CardCustomer'Variants -> String
(Int -> CardCustomer'Variants -> ShowS)
-> (CardCustomer'Variants -> String)
-> ([CardCustomer'Variants] -> ShowS)
-> Show CardCustomer'Variants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CardCustomer'Variants] -> ShowS
$cshowList :: [CardCustomer'Variants] -> ShowS
show :: CardCustomer'Variants -> String
$cshow :: CardCustomer'Variants -> String
showsPrec :: Int -> CardCustomer'Variants -> ShowS
$cshowsPrec :: Int -> CardCustomer'Variants -> ShowS
GHC.Show.Show, CardCustomer'Variants -> CardCustomer'Variants -> Bool
(CardCustomer'Variants -> CardCustomer'Variants -> Bool)
-> (CardCustomer'Variants -> CardCustomer'Variants -> Bool)
-> Eq CardCustomer'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CardCustomer'Variants -> CardCustomer'Variants -> Bool
$c/= :: CardCustomer'Variants -> CardCustomer'Variants -> Bool
== :: CardCustomer'Variants -> CardCustomer'Variants -> Bool
$c== :: CardCustomer'Variants -> CardCustomer'Variants -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON CardCustomer'Variants where
  toJSON :: CardCustomer'Variants -> Value
toJSON (CardCustomer'Text Text
a) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
a
  toJSON (CardCustomer'Customer Customer
a) = Customer -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Customer
a
  toJSON (CardCustomer'DeletedCustomer DeletedCustomer
a) = DeletedCustomer -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON DeletedCustomer
a
instance Data.Aeson.Types.FromJSON.FromJSON CardCustomer'Variants where
  parseJSON :: Value -> Parser CardCustomer'Variants
parseJSON Value
val = case (Text -> CardCustomer'Variants
CardCustomer'Text (Text -> CardCustomer'Variants)
-> Result Text -> Result CardCustomer'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Text
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result CardCustomer'Variants
-> Result CardCustomer'Variants -> Result CardCustomer'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((Customer -> CardCustomer'Variants
CardCustomer'Customer (Customer -> CardCustomer'Variants)
-> Result Customer -> Result CardCustomer'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Customer
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result CardCustomer'Variants
-> Result CardCustomer'Variants -> Result CardCustomer'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((DeletedCustomer -> CardCustomer'Variants
CardCustomer'DeletedCustomer (DeletedCustomer -> CardCustomer'Variants)
-> Result DeletedCustomer -> Result CardCustomer'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result DeletedCustomer
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result CardCustomer'Variants
-> Result CardCustomer'Variants -> Result CardCustomer'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String -> Result CardCustomer'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched")) of
    Data.Aeson.Types.Internal.Success CardCustomer'Variants
a -> CardCustomer'Variants -> Parser CardCustomer'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure CardCustomer'Variants
a
    Data.Aeson.Types.Internal.Error String
a -> String -> Parser CardCustomer'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a
data CardRecipient'Variants
  = CardRecipient'Text Data.Text.Internal.Text
  | CardRecipient'Recipient Recipient
  deriving (Int -> CardRecipient'Variants -> ShowS
[CardRecipient'Variants] -> ShowS
CardRecipient'Variants -> String
(Int -> CardRecipient'Variants -> ShowS)
-> (CardRecipient'Variants -> String)
-> ([CardRecipient'Variants] -> ShowS)
-> Show CardRecipient'Variants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CardRecipient'Variants] -> ShowS
$cshowList :: [CardRecipient'Variants] -> ShowS
show :: CardRecipient'Variants -> String
$cshow :: CardRecipient'Variants -> String
showsPrec :: Int -> CardRecipient'Variants -> ShowS
$cshowsPrec :: Int -> CardRecipient'Variants -> ShowS
GHC.Show.Show, CardRecipient'Variants -> CardRecipient'Variants -> Bool
(CardRecipient'Variants -> CardRecipient'Variants -> Bool)
-> (CardRecipient'Variants -> CardRecipient'Variants -> Bool)
-> Eq CardRecipient'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CardRecipient'Variants -> CardRecipient'Variants -> Bool
$c/= :: CardRecipient'Variants -> CardRecipient'Variants -> Bool
== :: CardRecipient'Variants -> CardRecipient'Variants -> Bool
$c== :: CardRecipient'Variants -> CardRecipient'Variants -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON CardRecipient'Variants where
  toJSON :: CardRecipient'Variants -> Value
toJSON (CardRecipient'Text Text
a) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
a
  toJSON (CardRecipient'Recipient Recipient
a) = Recipient -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Recipient
a
instance Data.Aeson.Types.FromJSON.FromJSON CardRecipient'Variants where
  parseJSON :: Value -> Parser CardRecipient'Variants
parseJSON Value
val = case (Text -> CardRecipient'Variants
CardRecipient'Text (Text -> CardRecipient'Variants)
-> Result Text -> Result CardRecipient'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Text
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result CardRecipient'Variants
-> Result CardRecipient'Variants -> Result CardRecipient'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((Recipient -> CardRecipient'Variants
CardRecipient'Recipient (Recipient -> CardRecipient'Variants)
-> Result Recipient -> Result CardRecipient'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Recipient
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result CardRecipient'Variants
-> Result CardRecipient'Variants -> Result CardRecipient'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String -> Result CardRecipient'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched") of
    Data.Aeson.Types.Internal.Success CardRecipient'Variants
a -> CardRecipient'Variants -> Parser CardRecipient'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure CardRecipient'Variants
a
    Data.Aeson.Types.Internal.Error String
a -> String -> Parser CardRecipient'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a