{-# LANGUAGE TemplateHaskell #-} module PayPal.Adaptive.Core.PayResponse.PaymentInfo.TransactionStatus where import Data.Aeson.TH import Data.Aeson.Types (camelTo) import Data.Char (toUpper) import Import -- | PaymentInfos have both a transactionStatus and senderTransactionStatus field. -- As far as I can tell the same data type can represent both of them. -- The comments for the data constructors come from senderTransactionStatus. -- -- https://developer.paypal.com/docs/classic/api/adaptive-payments/Pay_API_Operation/ data TransactionStatus = TsCreated -- ^ CREATED – The payment request was received; funds will be transferred once approval is received | TsPending -- ^ PENDING – The transaction is awaiting further processing | TsProcessing -- ^ PROCESSING – The transaction is in progress | TsCompleted -- ^ COMPLETED – The sender's transaction has completed | TsDenied -- ^ DENIED – The transaction was rejected by the receiver | TsFailed -- ^ FAILED – The payment failed | TsRefunded -- ^ REFUNDED – The payment was refunded | TsPartiallyRefunded -- ^ PARTIALLY_REFUNDED – Transaction was partially refunded | TsReversed -- ^ REVERSED – The payment was returned to the sender deriving (Eq, Show, Read) $(deriveFromJSON defaultOptions { constructorTagModifier = map toUpper . camelTo '_' . drop 2 } ''TransactionStatus) $(makePrisms ''TransactionStatus)