{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE OverloadedStrings #-}
module StripeAPI.Types.Dispute 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.BalanceTransaction
import {-# SOURCE #-} StripeAPI.Types.Charge
import {-# SOURCE #-} StripeAPI.Types.DisputeEvidence
import {-# SOURCE #-} StripeAPI.Types.DisputeEvidenceDetails
import {-# SOURCE #-} StripeAPI.Types.PaymentIntent
import qualified Prelude as GHC.Integer.Type
import qualified Prelude as GHC.Maybe
data Dispute = Dispute
{
Dispute -> Int
disputeAmount :: GHC.Types.Int,
Dispute -> [BalanceTransaction]
disputeBalanceTransactions :: ([BalanceTransaction]),
Dispute -> DisputeCharge'Variants
disputeCharge :: DisputeCharge'Variants,
Dispute -> Int
disputeCreated :: GHC.Types.Int,
Dispute -> Text
disputeCurrency :: Data.Text.Internal.Text,
Dispute -> DisputeEvidence
disputeEvidence :: DisputeEvidence,
Dispute -> DisputeEvidenceDetails
disputeEvidenceDetails :: DisputeEvidenceDetails,
Dispute -> Text
disputeId :: Data.Text.Internal.Text,
Dispute -> Bool
disputeIsChargeRefundable :: GHC.Types.Bool,
Dispute -> Bool
disputeLivemode :: GHC.Types.Bool,
Dispute -> Object
disputeMetadata :: Data.Aeson.Types.Internal.Object,
Dispute -> Maybe DisputePaymentIntent'Variants
disputePaymentIntent :: (GHC.Maybe.Maybe DisputePaymentIntent'Variants),
Dispute -> Text
disputeReason :: Data.Text.Internal.Text,
Dispute -> DisputeStatus'
disputeStatus :: DisputeStatus'
}
deriving
( Int -> Dispute -> ShowS
[Dispute] -> ShowS
Dispute -> String
(Int -> Dispute -> ShowS)
-> (Dispute -> String) -> ([Dispute] -> ShowS) -> Show Dispute
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Dispute] -> ShowS
$cshowList :: [Dispute] -> ShowS
show :: Dispute -> String
$cshow :: Dispute -> String
showsPrec :: Int -> Dispute -> ShowS
$cshowsPrec :: Int -> Dispute -> ShowS
GHC.Show.Show,
Dispute -> Dispute -> Bool
(Dispute -> Dispute -> Bool)
-> (Dispute -> Dispute -> Bool) -> Eq Dispute
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Dispute -> Dispute -> Bool
$c/= :: Dispute -> Dispute -> Bool
== :: Dispute -> Dispute -> Bool
$c== :: Dispute -> Dispute -> Bool
GHC.Classes.Eq
)
instance Data.Aeson.Types.ToJSON.ToJSON Dispute where
toJSON :: Dispute -> Value
toJSON Dispute
obj = [Pair] -> Value
Data.Aeson.Types.Internal.object (Text
"amount" Text -> Int -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> Int
disputeAmount Dispute
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"balance_transactions" Text -> [BalanceTransaction] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> [BalanceTransaction]
disputeBalanceTransactions Dispute
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"charge" Text -> DisputeCharge'Variants -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> DisputeCharge'Variants
disputeCharge Dispute
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..= Dispute -> Int
disputeCreated Dispute
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"currency" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> Text
disputeCurrency Dispute
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"evidence" Text -> DisputeEvidence -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> DisputeEvidence
disputeEvidence Dispute
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"evidence_details" Text -> DisputeEvidenceDetails -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> DisputeEvidenceDetails
disputeEvidenceDetails Dispute
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..= Dispute -> Text
disputeId Dispute
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"is_charge_refundable" Text -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> Bool
disputeIsChargeRefundable Dispute
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..= Dispute -> Bool
disputeLivemode Dispute
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"metadata" Text -> Object -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> Object
disputeMetadata Dispute
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"payment_intent" Text -> Maybe DisputePaymentIntent'Variants -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> Maybe DisputePaymentIntent'Variants
disputePaymentIntent Dispute
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..= Dispute -> Text
disputeReason Dispute
obj Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: Text
"status" Text -> DisputeStatus' -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> DisputeStatus'
disputeStatus Dispute
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
"dispute" Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
forall a. Monoid a => a
GHC.Base.mempty)
toEncoding :: Dispute -> Encoding
toEncoding Dispute
obj = Series -> Encoding
Data.Aeson.Encoding.Internal.pairs ((Text
"amount" Text -> Int -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> Int
disputeAmount Dispute
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"balance_transactions" Text -> [BalanceTransaction] -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> [BalanceTransaction]
disputeBalanceTransactions Dispute
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"charge" Text -> DisputeCharge'Variants -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> DisputeCharge'Variants
disputeCharge Dispute
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..= Dispute -> Int
disputeCreated Dispute
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"currency" Text -> Text -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> Text
disputeCurrency Dispute
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"evidence" Text -> DisputeEvidence -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> DisputeEvidence
disputeEvidence Dispute
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"evidence_details" Text -> DisputeEvidenceDetails -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> DisputeEvidenceDetails
disputeEvidenceDetails Dispute
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..= Dispute -> Text
disputeId Dispute
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"is_charge_refundable" Text -> Bool -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> Bool
disputeIsChargeRefundable Dispute
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..= Dispute -> Bool
disputeLivemode Dispute
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"metadata" Text -> Object -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> Object
disputeMetadata Dispute
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"payment_intent" Text -> Maybe DisputePaymentIntent'Variants -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> Maybe DisputePaymentIntent'Variants
disputePaymentIntent Dispute
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..= Dispute -> Text
disputeReason Dispute
obj) Series -> Series -> Series
forall a. Semigroup a => a -> a -> a
GHC.Base.<> ((Text
"status" Text -> DisputeStatus' -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
Data.Aeson.Types.ToJSON..= Dispute -> DisputeStatus'
disputeStatus Dispute
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
"dispute")))))))))))))))
instance Data.Aeson.Types.FromJSON.FromJSON Dispute where
parseJSON :: Value -> Parser Dispute
parseJSON = String -> (Object -> Parser Dispute) -> Value -> Parser Dispute
forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.Aeson.Types.FromJSON.withObject String
"Dispute" (\Object
obj -> ((((((((((((((Int
-> [BalanceTransaction]
-> DisputeCharge'Variants
-> Int
-> Text
-> DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
-> Parser
(Int
-> [BalanceTransaction]
-> DisputeCharge'Variants
-> Int
-> Text
-> DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure Int
-> [BalanceTransaction]
-> DisputeCharge'Variants
-> Int
-> Text
-> DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute
Dispute Parser
(Int
-> [BalanceTransaction]
-> DisputeCharge'Variants
-> Int
-> Text
-> DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
-> Parser Int
-> Parser
([BalanceTransaction]
-> DisputeCharge'Variants
-> Int
-> Text
-> DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
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
"amount")) Parser
([BalanceTransaction]
-> DisputeCharge'Variants
-> Int
-> Text
-> DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
-> Parser [BalanceTransaction]
-> Parser
(DisputeCharge'Variants
-> Int
-> Text
-> DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser [BalanceTransaction]
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"balance_transactions")) Parser
(DisputeCharge'Variants
-> Int
-> Text
-> DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
-> Parser DisputeCharge'Variants
-> Parser
(Int
-> Text
-> DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser DisputeCharge'Variants
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"charge")) Parser
(Int
-> Text
-> DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
-> Parser Int
-> Parser
(Text
-> DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
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
-> DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
-> Parser Text
-> Parser
(DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
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
"currency")) Parser
(DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
-> Parser DisputeEvidence
-> Parser
(DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser DisputeEvidence
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"evidence")) Parser
(DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
-> Parser DisputeEvidenceDetails
-> Parser
(Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser DisputeEvidenceDetails
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"evidence_details")) Parser
(Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
-> Parser Text
-> Parser
(Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
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
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
-> Parser Bool
-> Parser
(Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
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
"is_charge_refundable")) Parser
(Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
-> Parser Bool
-> Parser
(Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
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
(Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute)
-> Parser Object
-> Parser
(Maybe DisputePaymentIntent'Variants
-> Text -> DisputeStatus' -> Dispute)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser Object
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"metadata")) Parser
(Maybe DisputePaymentIntent'Variants
-> Text -> DisputeStatus' -> Dispute)
-> Parser (Maybe DisputePaymentIntent'Variants)
-> Parser (Text -> DisputeStatus' -> Dispute)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser (Maybe DisputePaymentIntent'Variants)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
Data.Aeson.Types.FromJSON..:? Text
"payment_intent")) Parser (Text -> DisputeStatus' -> Dispute)
-> Parser Text -> Parser (DisputeStatus' -> Dispute)
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 (DisputeStatus' -> Dispute)
-> Parser DisputeStatus' -> Parser Dispute
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
GHC.Base.<*> (Object
obj Object -> Text -> Parser DisputeStatus'
forall a. FromJSON a => Object -> Text -> Parser a
Data.Aeson.Types.FromJSON..: Text
"status"))
mkDispute ::
GHC.Types.Int ->
[BalanceTransaction] ->
DisputeCharge'Variants ->
GHC.Types.Int ->
Data.Text.Internal.Text ->
DisputeEvidence ->
DisputeEvidenceDetails ->
Data.Text.Internal.Text ->
GHC.Types.Bool ->
GHC.Types.Bool ->
Data.Aeson.Types.Internal.Object ->
Data.Text.Internal.Text ->
DisputeStatus' ->
Dispute
mkDispute :: Int
-> [BalanceTransaction]
-> DisputeCharge'Variants
-> Int
-> Text
-> DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Text
-> DisputeStatus'
-> Dispute
mkDispute Int
disputeAmount [BalanceTransaction]
disputeBalanceTransactions DisputeCharge'Variants
disputeCharge Int
disputeCreated Text
disputeCurrency DisputeEvidence
disputeEvidence DisputeEvidenceDetails
disputeEvidenceDetails Text
disputeId Bool
disputeIsChargeRefundable Bool
disputeLivemode Object
disputeMetadata Text
disputeReason DisputeStatus'
disputeStatus =
Dispute :: Int
-> [BalanceTransaction]
-> DisputeCharge'Variants
-> Int
-> Text
-> DisputeEvidence
-> DisputeEvidenceDetails
-> Text
-> Bool
-> Bool
-> Object
-> Maybe DisputePaymentIntent'Variants
-> Text
-> DisputeStatus'
-> Dispute
Dispute
{ disputeAmount :: Int
disputeAmount = Int
disputeAmount,
disputeBalanceTransactions :: [BalanceTransaction]
disputeBalanceTransactions = [BalanceTransaction]
disputeBalanceTransactions,
disputeCharge :: DisputeCharge'Variants
disputeCharge = DisputeCharge'Variants
disputeCharge,
disputeCreated :: Int
disputeCreated = Int
disputeCreated,
disputeCurrency :: Text
disputeCurrency = Text
disputeCurrency,
disputeEvidence :: DisputeEvidence
disputeEvidence = DisputeEvidence
disputeEvidence,
disputeEvidenceDetails :: DisputeEvidenceDetails
disputeEvidenceDetails = DisputeEvidenceDetails
disputeEvidenceDetails,
disputeId :: Text
disputeId = Text
disputeId,
disputeIsChargeRefundable :: Bool
disputeIsChargeRefundable = Bool
disputeIsChargeRefundable,
disputeLivemode :: Bool
disputeLivemode = Bool
disputeLivemode,
disputeMetadata :: Object
disputeMetadata = Object
disputeMetadata,
disputePaymentIntent :: Maybe DisputePaymentIntent'Variants
disputePaymentIntent = Maybe DisputePaymentIntent'Variants
forall a. Maybe a
GHC.Maybe.Nothing,
disputeReason :: Text
disputeReason = Text
disputeReason,
disputeStatus :: DisputeStatus'
disputeStatus = DisputeStatus'
disputeStatus
}
data DisputeCharge'Variants
= DisputeCharge'Text Data.Text.Internal.Text
| DisputeCharge'Charge Charge
deriving (Int -> DisputeCharge'Variants -> ShowS
[DisputeCharge'Variants] -> ShowS
DisputeCharge'Variants -> String
(Int -> DisputeCharge'Variants -> ShowS)
-> (DisputeCharge'Variants -> String)
-> ([DisputeCharge'Variants] -> ShowS)
-> Show DisputeCharge'Variants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisputeCharge'Variants] -> ShowS
$cshowList :: [DisputeCharge'Variants] -> ShowS
show :: DisputeCharge'Variants -> String
$cshow :: DisputeCharge'Variants -> String
showsPrec :: Int -> DisputeCharge'Variants -> ShowS
$cshowsPrec :: Int -> DisputeCharge'Variants -> ShowS
GHC.Show.Show, DisputeCharge'Variants -> DisputeCharge'Variants -> Bool
(DisputeCharge'Variants -> DisputeCharge'Variants -> Bool)
-> (DisputeCharge'Variants -> DisputeCharge'Variants -> Bool)
-> Eq DisputeCharge'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisputeCharge'Variants -> DisputeCharge'Variants -> Bool
$c/= :: DisputeCharge'Variants -> DisputeCharge'Variants -> Bool
== :: DisputeCharge'Variants -> DisputeCharge'Variants -> Bool
$c== :: DisputeCharge'Variants -> DisputeCharge'Variants -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON DisputeCharge'Variants where
toJSON :: DisputeCharge'Variants -> Value
toJSON (DisputeCharge'Text Text
a) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
a
toJSON (DisputeCharge'Charge Charge
a) = Charge -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Charge
a
instance Data.Aeson.Types.FromJSON.FromJSON DisputeCharge'Variants where
parseJSON :: Value -> Parser DisputeCharge'Variants
parseJSON Value
val = case (Text -> DisputeCharge'Variants
DisputeCharge'Text (Text -> DisputeCharge'Variants)
-> Result Text -> Result DisputeCharge'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 DisputeCharge'Variants
-> Result DisputeCharge'Variants -> Result DisputeCharge'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((Charge -> DisputeCharge'Variants
DisputeCharge'Charge (Charge -> DisputeCharge'Variants)
-> Result Charge -> Result DisputeCharge'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result Charge
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result DisputeCharge'Variants
-> Result DisputeCharge'Variants -> Result DisputeCharge'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String -> Result DisputeCharge'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched") of
Data.Aeson.Types.Internal.Success DisputeCharge'Variants
a -> DisputeCharge'Variants -> Parser DisputeCharge'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure DisputeCharge'Variants
a
Data.Aeson.Types.Internal.Error String
a -> String -> Parser DisputeCharge'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a
data DisputePaymentIntent'Variants
= DisputePaymentIntent'Text Data.Text.Internal.Text
| DisputePaymentIntent'PaymentIntent PaymentIntent
deriving (Int -> DisputePaymentIntent'Variants -> ShowS
[DisputePaymentIntent'Variants] -> ShowS
DisputePaymentIntent'Variants -> String
(Int -> DisputePaymentIntent'Variants -> ShowS)
-> (DisputePaymentIntent'Variants -> String)
-> ([DisputePaymentIntent'Variants] -> ShowS)
-> Show DisputePaymentIntent'Variants
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisputePaymentIntent'Variants] -> ShowS
$cshowList :: [DisputePaymentIntent'Variants] -> ShowS
show :: DisputePaymentIntent'Variants -> String
$cshow :: DisputePaymentIntent'Variants -> String
showsPrec :: Int -> DisputePaymentIntent'Variants -> ShowS
$cshowsPrec :: Int -> DisputePaymentIntent'Variants -> ShowS
GHC.Show.Show, DisputePaymentIntent'Variants
-> DisputePaymentIntent'Variants -> Bool
(DisputePaymentIntent'Variants
-> DisputePaymentIntent'Variants -> Bool)
-> (DisputePaymentIntent'Variants
-> DisputePaymentIntent'Variants -> Bool)
-> Eq DisputePaymentIntent'Variants
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisputePaymentIntent'Variants
-> DisputePaymentIntent'Variants -> Bool
$c/= :: DisputePaymentIntent'Variants
-> DisputePaymentIntent'Variants -> Bool
== :: DisputePaymentIntent'Variants
-> DisputePaymentIntent'Variants -> Bool
$c== :: DisputePaymentIntent'Variants
-> DisputePaymentIntent'Variants -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON DisputePaymentIntent'Variants where
toJSON :: DisputePaymentIntent'Variants -> Value
toJSON (DisputePaymentIntent'Text Text
a) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
a
toJSON (DisputePaymentIntent'PaymentIntent PaymentIntent
a) = PaymentIntent -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON PaymentIntent
a
instance Data.Aeson.Types.FromJSON.FromJSON DisputePaymentIntent'Variants where
parseJSON :: Value -> Parser DisputePaymentIntent'Variants
parseJSON Value
val = case (Text -> DisputePaymentIntent'Variants
DisputePaymentIntent'Text (Text -> DisputePaymentIntent'Variants)
-> Result Text -> Result DisputePaymentIntent'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 DisputePaymentIntent'Variants
-> Result DisputePaymentIntent'Variants
-> Result DisputePaymentIntent'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> ((PaymentIntent -> DisputePaymentIntent'Variants
DisputePaymentIntent'PaymentIntent (PaymentIntent -> DisputePaymentIntent'Variants)
-> Result PaymentIntent -> Result DisputePaymentIntent'Variants
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Data.Functor.<$> Value -> Result PaymentIntent
forall a. FromJSON a => Value -> Result a
Data.Aeson.Types.FromJSON.fromJSON Value
val) Result DisputePaymentIntent'Variants
-> Result DisputePaymentIntent'Variants
-> Result DisputePaymentIntent'Variants
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
GHC.Base.<|> String -> Result DisputePaymentIntent'Variants
forall a. String -> Result a
Data.Aeson.Types.Internal.Error String
"No variant matched") of
Data.Aeson.Types.Internal.Success DisputePaymentIntent'Variants
a -> DisputePaymentIntent'Variants
-> Parser DisputePaymentIntent'Variants
forall (f :: * -> *) a. Applicative f => a -> f a
GHC.Base.pure DisputePaymentIntent'Variants
a
Data.Aeson.Types.Internal.Error String
a -> String -> Parser DisputePaymentIntent'Variants
forall (m :: * -> *) a. MonadFail m => String -> m a
Control.Monad.Fail.fail String
a
data DisputeStatus'
=
DisputeStatus'Other Data.Aeson.Types.Internal.Value
|
DisputeStatus'Typed Data.Text.Internal.Text
|
DisputeStatus'EnumChargeRefunded
|
DisputeStatus'EnumLost
|
DisputeStatus'EnumNeedsResponse
|
DisputeStatus'EnumUnderReview
|
DisputeStatus'EnumWarningClosed
|
DisputeStatus'EnumWarningNeedsResponse
|
DisputeStatus'EnumWarningUnderReview
|
DisputeStatus'EnumWon
deriving (Int -> DisputeStatus' -> ShowS
[DisputeStatus'] -> ShowS
DisputeStatus' -> String
(Int -> DisputeStatus' -> ShowS)
-> (DisputeStatus' -> String)
-> ([DisputeStatus'] -> ShowS)
-> Show DisputeStatus'
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisputeStatus'] -> ShowS
$cshowList :: [DisputeStatus'] -> ShowS
show :: DisputeStatus' -> String
$cshow :: DisputeStatus' -> String
showsPrec :: Int -> DisputeStatus' -> ShowS
$cshowsPrec :: Int -> DisputeStatus' -> ShowS
GHC.Show.Show, DisputeStatus' -> DisputeStatus' -> Bool
(DisputeStatus' -> DisputeStatus' -> Bool)
-> (DisputeStatus' -> DisputeStatus' -> Bool) -> Eq DisputeStatus'
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisputeStatus' -> DisputeStatus' -> Bool
$c/= :: DisputeStatus' -> DisputeStatus' -> Bool
== :: DisputeStatus' -> DisputeStatus' -> Bool
$c== :: DisputeStatus' -> DisputeStatus' -> Bool
GHC.Classes.Eq)
instance Data.Aeson.Types.ToJSON.ToJSON DisputeStatus' where
toJSON :: DisputeStatus' -> Value
toJSON (DisputeStatus'Other Value
val) = Value
val
toJSON (DisputeStatus'Typed Text
val) = Text -> Value
forall a. ToJSON a => a -> Value
Data.Aeson.Types.ToJSON.toJSON Text
val
toJSON (DisputeStatus'
DisputeStatus'EnumChargeRefunded) = Value
"charge_refunded"
toJSON (DisputeStatus'
DisputeStatus'EnumLost) = Value
"lost"
toJSON (DisputeStatus'
DisputeStatus'EnumNeedsResponse) = Value
"needs_response"
toJSON (DisputeStatus'
DisputeStatus'EnumUnderReview) = Value
"under_review"
toJSON (DisputeStatus'
DisputeStatus'EnumWarningClosed) = Value
"warning_closed"
toJSON (DisputeStatus'
DisputeStatus'EnumWarningNeedsResponse) = Value
"warning_needs_response"
toJSON (DisputeStatus'
DisputeStatus'EnumWarningUnderReview) = Value
"warning_under_review"
toJSON (DisputeStatus'
DisputeStatus'EnumWon) = Value
"won"
instance Data.Aeson.Types.FromJSON.FromJSON DisputeStatus' where
parseJSON :: Value -> Parser DisputeStatus'
parseJSON Value
val =
DisputeStatus' -> Parser DisputeStatus'
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
"charge_refunded" -> DisputeStatus'
DisputeStatus'EnumChargeRefunded
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"lost" -> DisputeStatus'
DisputeStatus'EnumLost
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"needs_response" -> DisputeStatus'
DisputeStatus'EnumNeedsResponse
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"under_review" -> DisputeStatus'
DisputeStatus'EnumUnderReview
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"warning_closed" -> DisputeStatus'
DisputeStatus'EnumWarningClosed
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"warning_needs_response" -> DisputeStatus'
DisputeStatus'EnumWarningNeedsResponse
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"warning_under_review" -> DisputeStatus'
DisputeStatus'EnumWarningUnderReview
| Value
val Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
GHC.Classes.== Value
"won" -> DisputeStatus'
DisputeStatus'EnumWon
| Bool
GHC.Base.otherwise -> Value -> DisputeStatus'
DisputeStatus'Other Value
val
)