Copyright | (c) David Johnson 2014 |
---|---|
Maintainer | djohnson.m@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- type family ExpandsTo id :: *
- data Expandable id
- data TimeRange a = TimeRange {}
- emptyTimeRange :: TimeRange a
- newtype AvailableOn = AvailableOn UTCTime
- newtype Created = Created UTCTime
- newtype Date = Date UTCTime
- newtype ChargeId = ChargeId Text
- newtype StatementDescription = StatementDescription Text
- data Charge = Charge {
- chargeId :: ChargeId
- chargeObject :: Text
- chargeCreated :: UTCTime
- chargeLiveMode :: Bool
- chargePaid :: Bool
- chargeAmount :: Amount
- chargeCurrency :: Currency
- chargeRefunded :: Bool
- chargeCreditCard :: Maybe Card
- chargeCaptured :: Bool
- chargeRefunds :: StripeList Refund
- chargeBalanceTransaction :: Maybe (Expandable TransactionId)
- chargeFailureMessage :: Maybe Text
- chargeFailureCode :: Maybe Text
- chargeAmountRefunded :: Int
- chargeCustomerId :: Maybe (Expandable CustomerId)
- chargeInvoice :: Maybe (Expandable InvoiceId)
- chargeDescription :: Maybe Description
- chargeDispute :: Maybe Dispute
- chargeMetaData :: MetaData
- chargeStatementDescription :: Maybe StatementDescription
- chargeReceiptEmail :: Maybe Text
- chargeReceiptNumber :: Maybe Text
- newtype Capture = Capture {
- getCapture :: Bool
- newtype RefundId = RefundId Text
- data Refund = Refund {}
- newtype RefundApplicationFee = RefundApplicationFee {}
- data RefundReason
- newtype CustomerId = CustomerId Text
- data Customer
- = Customer {
- customerObject :: Text
- customerCreated :: UTCTime
- customerId :: CustomerId
- customerLiveMode :: Bool
- customerDescription :: Maybe Description
- customerEmail :: Maybe Email
- customerDelinquent :: Bool
- customerSubscriptions :: StripeList Subscription
- customerDiscount :: Maybe Discount
- customerAccountBalance :: Int
- customerCards :: StripeList Card
- customerCurrency :: Maybe Currency
- customerDefaultCard :: Maybe (Expandable CardId)
- customerMetaData :: MetaData
- | DeletedCustomer { }
- = Customer {
- newtype AccountBalance = AccountBalance Int
- newtype CardId = CardId Text
- newtype RecipientCardId = RecipientCardId Text
- newtype CardNumber = CardNumber Text
- newtype ExpMonth = ExpMonth Int
- newtype ExpYear = ExpYear Int
- newtype CVC = CVC Text
- newtype AddressCity = AddressCity Text
- newtype AddressCountry = AddressCountry Text
- newtype AddressLine1 = AddressLine1 Text
- newtype AddressLine2 = AddressLine2 Text
- newtype AddressState = AddressState Text
- newtype AddressZip = AddressZip Text
- newtype IsVerified = IsVerified {
- getVerified :: Bool
- data Brand
- = Visa
- | AMEX
- | MasterCard
- | Discover
- | JCB
- | DinersClub
- | Unknown
- data Card = Card {
- cardId :: CardId
- cardObject :: Text
- cardLastFour :: Text
- cardBrand :: Brand
- cardFunding :: Text
- cardExpMonth :: ExpMonth
- cardExpYear :: ExpYear
- cardFingerprint :: Text
- cardCountry :: Maybe Text
- cardName :: Maybe Name
- cardAddressLine1 :: Maybe AddressLine1
- cardAddressLine2 :: Maybe AddressLine2
- cardAddressCity :: Maybe AddressCity
- cardAddressState :: Maybe AddressState
- cardAddressZip :: Maybe AddressZip
- cardAddressCountry :: Maybe AddressCountry
- cardCVCCheck :: Maybe Text
- cardAddressLine1Check :: Maybe Text
- cardAddressZipCheck :: Maybe Text
- cardCustomerId :: Maybe (Expandable CustomerId)
- cardMetaData :: MetaData
- data RecipientCard = RecipientCard {
- recipientCardId :: RecipientCardId
- recipientCardLastFour :: Text
- recipientCardBrand :: Brand
- recipientCardFunding :: Text
- recipientCardExpMonth :: ExpMonth
- recipientCardExpYear :: ExpYear
- recipientCardFingerprint :: Text
- recipientCardCountry :: Country
- recipientCardName :: Maybe Name
- recipientCardAddressLine1 :: Maybe AddressLine1
- recipientCardAddressLine2 :: Maybe AddressLine2
- recipientCardAddressCity :: Maybe AddressCity
- recipientCardAddressState :: Maybe AddressState
- recipientCardAddressZip :: Maybe AddressZip
- recipientCardAddressCountry :: Maybe AddressCountry
- recipientCardCVCCheck :: Maybe Text
- recipientCardAddressLine1Check :: Maybe Text
- recipientCardAddressZipCheck :: Maybe Text
- recipientCardRecipientId :: Maybe (Expandable RecipientId)
- data NewCard = NewCard {
- newCardCardNumber :: CardNumber
- newCardExpMonth :: ExpMonth
- newCardExpYear :: ExpYear
- newCardCVC :: Maybe CVC
- newCardName :: Maybe Name
- newCardAddressLine1 :: Maybe AddressLine1
- newCardAddressLine2 :: Maybe AddressLine2
- newCardAddressCity :: Maybe AddressCity
- newCardAddressZip :: Maybe AddressZip
- newCardAddressState :: Maybe AddressState
- newCardAddressCountry :: Maybe AddressCountry
- mkNewCard :: CardNumber -> ExpMonth -> ExpYear -> NewCard
- data DefaultCard = DefaultCard {}
- newtype SubscriptionId = SubscriptionId {}
- data Subscription = Subscription {
- subscriptionId :: SubscriptionId
- subscriptionPlan :: Plan
- subscriptionObject :: Text
- subscriptionStart :: UTCTime
- subscriptionStatus :: SubscriptionStatus
- subscriptionCustomerId :: Expandable CustomerId
- subscriptionCancelAtPeriodEnd :: Bool
- subscriptionCurrentPeriodStart :: UTCTime
- subscriptionCurrentPeriodEnd :: UTCTime
- subscriptionEndedAt :: Maybe UTCTime
- subscriptionTrialStart :: Maybe UTCTime
- subscriptionTrialEnd :: Maybe UTCTime
- subscriptionCanceledAt :: Maybe UTCTime
- subscriptionQuantity :: Quantity
- subscriptionApplicationFeePercent :: Maybe Double
- subscriptionDiscount :: Maybe Discount
- subscriptionMetaData :: MetaData
- subscriptionTaxPercent :: Maybe Double
- data SubscriptionStatus
- newtype TaxPercent = TaxPercent Double
- newtype PlanId = PlanId Text
- data Plan = Plan {}
- newtype TrialPeriod = TrialPeriod UTCTime
- newtype TrialEnd = TrialEnd UTCTime
- data Interval
- data Duration
- data Coupon = Coupon {
- couponId :: CouponId
- couponCreated :: UTCTime
- couponPercentOff :: Maybe Int
- couponAmountOff :: Maybe Int
- couponCurrency :: Maybe Currency
- couponLiveMode :: Bool
- couponDuration :: Duration
- couponRedeemBy :: Maybe UTCTime
- couponMaxRedemptions :: Maybe Int
- couponTimesRedeemed :: Maybe Int
- couponDurationInMonths :: Maybe Int
- couponValid :: Bool
- couponMetaData :: MetaData
- newtype CouponId = CouponId Text
- newtype AmountOff = AmountOff Int
- newtype MaxRedemptions = MaxRedemptions Int
- newtype PercentOff = PercentOff Int
- newtype RedeemBy = RedeemBy UTCTime
- newtype DurationInMonths = DurationInMonths Int
- newtype IntervalCount = IntervalCount Int
- newtype TrialPeriodDays = TrialPeriodDays Int
- newtype Amount = Amount {}
- data Discount = Discount {}
- newtype InvoiceId = InvoiceId Text
- data Invoice = Invoice {
- invoiceDate :: UTCTime
- invoiceId :: Maybe InvoiceId
- invoicePeriodStart :: UTCTime
- invoicePeriodEnd :: UTCTime
- invoiceLineItems :: StripeList InvoiceLineItem
- invoiceSubTotal :: Int
- invoiceTotal :: Int
- invoiceCustomer :: Expandable CustomerId
- invoiceObject :: Text
- invoiceAttempted :: Bool
- invoiceClosed :: Bool
- invoiceForgiven :: Bool
- invoicePaid :: Bool
- invoiceLiveMode :: Bool
- invoiceAttemptCount :: Int
- invoiceAmountDue :: Int
- invoiceCurrency :: Currency
- invoiceStartingBalance :: Int
- invoiceEndingBalance :: Maybe Int
- invoiceNextPaymentAttempt :: Maybe UTCTime
- invoiceWebHooksDeliveredAt :: Maybe UTCTime
- invoiceCharge :: Maybe (Expandable ChargeId)
- invoiceDiscount :: Maybe Discount
- invoiceApplicateFee :: Maybe FeeId
- invoiceSubscription :: Maybe SubscriptionId
- invoiceStatementDescription :: Maybe StatementDescription
- invoiceDescription :: Maybe Description
- invoiceMetaData :: MetaData
- newtype InvoiceItemId = InvoiceItemId Text
- data InvoiceItem = InvoiceItem {
- invoiceItemObject :: Text
- invoiceItemId :: InvoiceItemId
- invoiceItemDate :: UTCTime
- invoiceItemAmount :: Int
- invoiceItemLiveMode :: Bool
- invoiceItemProration :: Bool
- invoiceItemCurrency :: Currency
- invoiceItemCustomer :: Expandable CustomerId
- invoiceItemDescription :: Maybe Description
- invoiceItemInvoice :: Maybe (Expandable InvoiceId)
- invoiceItemQuantity :: Maybe Quantity
- invoiceItemSubscription :: Maybe SubscriptionId
- invoiceItemMetaData :: MetaData
- newtype InvoiceLineItemId = InvoiceLineItemId Text
- data InvoiceLineItemType
- data InvoiceLineItem = InvoiceLineItem {
- invoiceLineItemId :: InvoiceLineItemId
- invoiceLineItemObject :: Text
- invoiceLineItemType :: InvoiceLineItemType
- invoiceLineItemLiveMode :: Bool
- invoiceLineItemAmount :: Int
- invoiceLineItemCurrency :: Currency
- invoiceLineItemProration :: Bool
- invoiceLineItemPeriod :: Period
- invoiceLineItemQuantity :: Maybe Quantity
- invoiceLineItemPlan :: Maybe Plan
- invoiceLineItemDescription :: Maybe Description
- invoiceLineItemMetaData :: MetaData
- data Period = Period {}
- newtype Closed = Closed {}
- newtype Forgiven = Forgiven {
- getForgiven :: Bool
- data DisputeStatus
- data DisputeReason
- data Dispute = Dispute {
- disputeChargeId :: Expandable ChargeId
- disputeAmount :: Int
- disputeCreated :: UTCTime
- disputeStatus :: DisputeStatus
- disputeLiveMode :: Bool
- disputeCurrency :: Currency
- disputeObject :: Text
- disputeReason :: DisputeReason
- disputeIsChargeRefundable :: Bool
- disputeBalanceTransactions :: [BalanceTransaction]
- disputeEvidenceDueBy :: UTCTime
- disputeEvidence :: Maybe Evidence
- disputeMetaData :: MetaData
- newtype Evidence = Evidence Text
- newtype TransferId = TransferId Text
- data TransferStatus
- data TransferType
- data Transfer = Transfer {
- transferId :: TransferId
- transferObject :: Text
- transferCreated :: UTCTime
- transferDate :: UTCTime
- transferLiveMode :: Bool
- transferAmount :: Int
- transferCurrency :: Currency
- transferStatus :: TransferStatus
- transferType :: TransferType
- transferBalanceTransaction :: Expandable TransactionId
- transferDescription :: Maybe Description
- transferBankAccount :: Maybe BankAccount
- transferFailureMessage :: Maybe Text
- transferFailureCode :: Maybe Text
- transferStatementDescription :: Maybe StatementDescription
- transferRecipient :: Maybe (Expandable RecipientId)
- transferMetaData :: MetaData
- data BankAccount = BankAccount {}
- newtype BankAccountId = BankAccountId Text
- data BankAccountStatus
- newtype RoutingNumber = RoutingNumber Text
- newtype Country = Country Text
- newtype AccountNumber = AccountNumber Text
- data NewBankAccount = NewBankAccount {}
- newtype FirstName = FirstName Text
- newtype LastName = LastName Text
- type MiddleInitial = Char
- newtype RecipientId = RecipientId Text
- newtype TaxID = TaxID {}
- data RecipientType
- data Recipient
- = Recipient {
- recipientId :: RecipientId
- recipientObject :: Text
- recipientCreated :: UTCTime
- recipientLiveMode :: Bool
- recipientType :: RecipientType
- recipientDescription :: Maybe Description
- recipientEmail :: Maybe Email
- recipientName :: Name
- recipientVerified :: Bool
- recipientActiveAccount :: Maybe BankAccount
- recipientCards :: StripeList RecipientCard
- recipientDefaultCard :: Maybe (Expandable RecipientCardId)
- | DeletedRecipient { }
- = Recipient {
- newtype ApplicationFeeId = ApplicationFeeId Text
- data ApplicationFee = ApplicationFee {
- applicationFeeId :: ApplicationFeeId
- applicationFeeObjecet :: Text
- applicationFeeCreated :: UTCTime
- applicationFeeLiveMode :: Bool
- applicationFeeAmount :: Int
- applicationFeeCurrency :: Currency
- applicationFeeRefunded :: Bool
- applicationFeeAmountRefunded :: Int
- applicationFeeRefunds :: StripeList Refund
- applicationFeeBalanceTransaction :: Expandable TransactionId
- applicationFeeAccountId :: Expandable AccountId
- applicationFeeApplicationId :: ApplicationId
- applicationFeeChargeId :: Expandable ChargeId
- applicationFeeMetaData :: MetaData
- newtype ApplicationFeePercent = ApplicationFeePercent Double
- newtype ApplicationFeeAmount = ApplicationFeeAmount Integer
- newtype ApplicationId = ApplicationId Text
- newtype FeeId = FeeId Text
- data ApplicationFeeRefund = ApplicationFeeRefund {
- applicationFeeRefundId :: RefundId
- applicationFeeRefundAmount :: Int
- applicationFeeRefundCurrency :: Currency
- applicationFeeRefundCreated :: UTCTime
- applicationFeeRefundObject :: Text
- applicationFeeRefundBalanceTransaction :: Maybe (Expandable TransactionId)
- applicationFeeRefundFee :: FeeId
- applicationFeeRefundMetaData :: MetaData
- newtype AccountId = AccountId Text
- data Account = Account {
- accountId :: AccountId
- accountEmail :: Email
- accountStatementDescriptor :: Maybe Description
- accountDisplayName :: Maybe Text
- accountTimeZone :: Text
- accountDetailsSubmitted :: Bool
- accountChargeEnabled :: Bool
- accountTransferEnabled :: Bool
- accountCurrenciesSupported :: [Currency]
- accountDefaultCurrency :: Currency
- accountCountry :: Text
- accountObject :: Text
- accountBusinessName :: Maybe Text
- accountBusinessURL :: Maybe Text
- accountBusinessLogo :: Maybe Text
- accountSupportPhone :: Maybe Text
- data Balance = Balance {}
- data BalanceAmount = BalanceAmount {}
- data BalanceTransaction = BalanceTransaction {
- balanceTransactionId :: TransactionId
- balanceTransactionObject :: Text
- balanceTransactionAmount :: Int
- balanceTransactionCurrency :: Currency
- balanceTransactionNet :: Int
- balanceTransactionType :: TransactionType
- balanceTransactionCreated :: UTCTime
- balanceTransactionAvailableOn :: UTCTime
- balanceTransactionStatus :: Text
- balanceTransactionFee :: Int
- balanceTransactionFeeDetails :: [FeeDetails]
- balanceTransactionFeeSource :: Expandable ChargeId
- balanceTransactionFeeDescription :: Maybe Description
- newtype TransactionId = TransactionId Text
- data FeeDetails = FeeDetails {}
- newtype Source a = Source {
- getSource :: a
- data TransactionType
- data EventType
- = AccountUpdatedEvent
- | AccountApplicationDeauthorizedEvent
- | ApplicationFeeCreatedEvent
- | ApplicationFeeRefundedEvent
- | BalanceAvailableEvent
- | ChargeSucceededEvent
- | ChargeFailedEvent
- | ChargeRefundedEvent
- | ChargeCapturedEvent
- | ChargeUpdatedEvent
- | ChargeDisputeCreatedEvent
- | ChargeDisputeUpdatedEvent
- | ChargeDisputeClosedEvent
- | ChargeDisputeFundsWithdrawnEvent
- | ChargeDisputeFundsReinstatedEvent
- | CustomerCreatedEvent
- | CustomerUpdatedEvent
- | CustomerDeletedEvent
- | CustomerCardCreatedEvent
- | CustomerCardUpdatedEvent
- | CustomerCardDeletedEvent
- | CustomerSubscriptionCreatedEvent
- | CustomerSubscriptionUpdatedEvent
- | CustomerSubscriptionDeletedEvent
- | CustomerSubscriptionTrialWillEndEvent
- | CustomerDiscountCreatedEvent
- | CustomerDiscountUpdatedEvent
- | CustomerDiscountDeletedEvent
- | InvoiceCreatedEvent
- | InvoiceUpdatedEvent
- | InvoicePaymentSucceededEvent
- | InvoicePaymentFailedEvent
- | InvoiceItemCreatedEvent
- | InvoiceItemUpdatedEvent
- | InvoiceItemDeletedEvent
- | PlanCreatedEvent
- | PlanUpdatedEvent
- | PlanDeletedEvent
- | CouponCreatedEvent
- | CouponUpdatedEvent
- | CouponDeletedEvent
- | RecipientCreatedEvent
- | RecipientUpdatedEvent
- | RecipientDeletedEvent
- | TransferCreatedEvent
- | TransferUpdatedEvent
- | TransferCanceledEvent
- | TransferPaidEvent
- | TransferFailedEvent
- | PingEvent
- | UnknownEvent
- newtype EventId = EventId Text
- data EventData
- = TransferEvent Transfer
- | AccountEvent Account
- | AccountApplicationEvent ConnectApp
- | ApplicationFeeEvent ApplicationFee
- | InvoiceEvent Invoice
- | PlanEvent Plan
- | RecipientEvent Recipient
- | CouponEvent Coupon
- | BalanceEvent Balance
- | ChargeEvent Charge
- | DisputeEvent Dispute
- | CustomerEvent Customer
- | CardEvent Card
- | SubscriptionEvent Subscription
- | DiscountEvent Discount
- | InvoiceItemEvent InvoiceItem
- | UnknownEventData
- | Ping
- data Event = Event {}
- data ConnectApp = ConnectApp {}
- newtype TokenId = TokenId Text
- data TokenType
- data Token a = Token {
- tokenId :: TokenId
- tokenLiveMode :: Bool
- tokenCreated :: UTCTime
- tokenUsed :: Bool
- tokenObject :: Text
- tokenType :: TokenType
- tokenData :: a
- data StripeList a = StripeList {}
- newtype Limit = Limit Int
- newtype StartingAfter a = StartingAfter a
- newtype EndingBefore a = EndingBefore a
- data StripeDeleteResult = StripeDeleteResult {}
- newtype MetaData = MetaData [(Text, Text)]
- newtype ExpandParams = ExpandParams {
- getExpandParams :: [Text]
- type ID = Text
- type URL = Text
- newtype Name = Name {}
- newtype PlanName = PlanName {
- getPlanName :: Text
- newtype Description = Description Text
- newtype Quantity = Quantity Int
- newtype Prorate = Prorate Bool
- newtype AtPeriodEnd = AtPeriodEnd Bool
- newtype Email = Email Text
- newtype ReceiptEmail = ReceiptEmail Text
- data Currency
- = AED
- | AFN
- | ALL
- | AMD
- | ANG
- | AOA
- | ARS
- | AUD
- | AWG
- | AZN
- | BAM
- | BBD
- | BDT
- | BGN
- | BIF
- | BMD
- | BND
- | BOB
- | BRL
- | BSD
- | BWP
- | BZD
- | CAD
- | CDF
- | CHF
- | CLP
- | CNY
- | COP
- | CRC
- | CVE
- | CZK
- | DJF
- | DKK
- | DOP
- | DZD
- | EEK
- | EGP
- | ETB
- | EUR
- | FJD
- | FKP
- | GBP
- | GEL
- | GIP
- | GMD
- | GNF
- | GTQ
- | GYD
- | HKD
- | HNL
- | HRK
- | HTG
- | HUF
- | IDR
- | ILS
- | INR
- | ISK
- | JMD
- | JPY
- | KES
- | KGS
- | KHR
- | KMF
- | KRW
- | KYD
- | KZT
- | LAK
- | LBP
- | LKR
- | LRD
- | LSL
- | LTL
- | LVL
- | MAD
- | MDL
- | MGA
- | MKD
- | MNT
- | MOP
- | MRO
- | MUR
- | MVR
- | MWK
- | MXN
- | MYR
- | MZN
- | NAD
- | NGN
- | NIO
- | NOK
- | NPR
- | NZD
- | PAB
- | PEN
- | PGK
- | PHP
- | PKR
- | PLN
- | PYG
- | QAR
- | RON
- | RSD
- | RUB
- | RWF
- | SAR
- | SBD
- | SCR
- | SEK
- | SGD
- | SHP
- | SLL
- | SOS
- | SRD
- | STD
- | SVC
- | SZL
- | THB
- | TJS
- | TOP
- | TRY
- | TTD
- | TWD
- | TZS
- | UAH
- | UGX
- | USD
- | UYU
- | UZS
- | VND
- | VUV
- | WST
- | XAF
- | XCD
- | XOF
- | XPF
- | YER
- | ZAR
- | ZMW
- | UnknownCurrency
- data BitcoinReceiver = BitcoinReceiver {
- btcId :: BitcoinReceiverId
- btcObject :: Text
- btcCreated :: UTCTime
- btcLiveMode :: Bool
- btcActive :: Bool
- btcAmount :: Integer
- btcAmountReceived :: Integer
- btcBitcoinAmount :: Integer
- btcBitcoinAmountReceived :: Integer
- btcBitcoinUri :: Text
- btcCurrency :: Currency
- btcFilled :: Bool
- btcInboundAddress :: Text
- btcUncapturedFunds :: Bool
- btcDescription :: Maybe Text
- btcEmail :: Text
- btcMetadata :: MetaData
- btcRefundAddress :: Maybe Text
- btcTransactions :: Maybe Transactions
- btcPayment :: Maybe PaymentId
- btcCustomer :: Maybe CustomerId
- data Transactions = Transactions {}
- data BitcoinTransaction = BitcoinTransaction {}
- newtype BitcoinTransactionId = BitcoinTransactionId Text
- newtype BitcoinReceiverId = BitcoinReceiverId Text
- newtype PaymentId = PaymentId Text
- showAmount :: Currency -> Int -> String
- currencyDivisor :: Currency -> Int -> Float
Documentation
type family ExpandsTo id :: * Source #
Expandable
values
maps from an id to an object, e.g. CardId
to Card
Instances
type ExpandsTo TransactionId Source # | |
Defined in Web.Stripe.Types | |
type ExpandsTo AccountId Source # | |
Defined in Web.Stripe.Types | |
type ExpandsTo RecipientId Source # | |
Defined in Web.Stripe.Types | |
type ExpandsTo InvoiceItemId Source # | |
Defined in Web.Stripe.Types | |
type ExpandsTo InvoiceId Source # | |
Defined in Web.Stripe.Types | |
type ExpandsTo RecipientCardId Source # | |
Defined in Web.Stripe.Types | |
type ExpandsTo CardId Source # | |
Defined in Web.Stripe.Types | |
type ExpandsTo CustomerId Source # | |
Defined in Web.Stripe.Types | |
type ExpandsTo ChargeId Source # | |
Defined in Web.Stripe.Types |
data Expandable id Source #
a wrapper for fields which can either be an id or an expanded object
Instances
specify a TimeRange
FIXME: this is a little awkward to use. How can we make it moar better?
Instances
StripeHasParam GetBalanceTransactionHistory (TimeRange Created) Source # | |
Defined in Web.Stripe.Balance | |
StripeHasParam GetBalanceTransactionHistory (TimeRange AvailableOn) Source # | |
Defined in Web.Stripe.Balance | |
Eq a => Eq (TimeRange a) Source # | |
Data a => Data (TimeRange a) Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeRange a -> c (TimeRange a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TimeRange a) # toConstr :: TimeRange a -> Constr # dataTypeOf :: TimeRange a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TimeRange a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TimeRange a)) # gmapT :: (forall b. Data b => b -> b) -> TimeRange a -> TimeRange a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeRange a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeRange a -> r # gmapQ :: (forall d. Data d => d -> u) -> TimeRange a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeRange a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeRange a -> m (TimeRange a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeRange a -> m (TimeRange a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeRange a -> m (TimeRange a) # | |
Ord a => Ord (TimeRange a) Source # | |
Defined in Web.Stripe.Types | |
Read a => Read (TimeRange a) Source # | |
Show a => Show (TimeRange a) Source # | |
ToStripeParam a => ToStripeParam (TimeRange a) Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: TimeRange a -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # |
emptyTimeRange :: TimeRange a Source #
Time range with all values set to Nothing
newtype AvailableOn Source #
Instances
Instances
Instances
Eq Date Source # | |
Data Date Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Date -> c Date # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Date # dataTypeOf :: Date -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Date) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Date) # gmapT :: (forall b. Data b => b -> b) -> Date -> Date # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Date -> r # gmapQ :: (forall d. Data d => d -> u) -> Date -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Date -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Date -> m Date # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Date -> m Date # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Date -> m Date # | |
Ord Date Source # | |
Read Date Source # | |
Show Date Source # | |
ToStripeParam Date Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Date -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam GetTransfers Date Source # | |
Defined in Web.Stripe.Transfer |
Instances
newtype StatementDescription Source #
StatementDescription
to be added to a Charge
Instances
Charge
object in Stripe
API
Instances
Eq Charge Source # | |
Data Charge Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Charge -> c Charge # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Charge # toConstr :: Charge -> Constr # dataTypeOf :: Charge -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Charge) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Charge) # gmapT :: (forall b. Data b => b -> b) -> Charge -> Charge # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Charge -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Charge -> r # gmapQ :: (forall d. Data d => d -> u) -> Charge -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Charge -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Charge -> m Charge # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Charge -> m Charge # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Charge -> m Charge # | |
Ord Charge Source # | |
Read Charge Source # | |
Show Charge Source # | |
FromJSON Charge Source # | JSON Instance for |
Capture for Charge
Instances
Eq Capture Source # | |
Data Capture Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Capture -> c Capture # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Capture # toConstr :: Capture -> Constr # dataTypeOf :: Capture -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Capture) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Capture) # gmapT :: (forall b. Data b => b -> b) -> Capture -> Capture # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Capture -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Capture -> r # gmapQ :: (forall d. Data d => d -> u) -> Capture -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Capture -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Capture -> m Capture # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Capture -> m Capture # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Capture -> m Capture # | |
Ord Capture Source # | |
Read Capture Source # | |
Show Capture Source # | |
ToStripeParam Capture Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Capture -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam CreateCharge Capture Source # | |
Defined in Web.Stripe.Charge |
Instances
Refund
Object
Instances
Eq Refund Source # | |
Data Refund Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Refund -> c Refund # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Refund # toConstr :: Refund -> Constr # dataTypeOf :: Refund -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Refund) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Refund) # gmapT :: (forall b. Data b => b -> b) -> Refund -> Refund # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Refund -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Refund -> r # gmapQ :: (forall d. Data d => d -> u) -> Refund -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Refund -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Refund -> m Refund # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Refund -> m Refund # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Refund -> m Refund # | |
Ord Refund Source # | |
Read Refund Source # | |
Show Refund Source # | |
FromJSON Refund Source # | JSON Instance for |
newtype RefundApplicationFee Source #
Instances
data RefundReason Source #
Instances
newtype CustomerId Source #
CustomerId
for a Customer
Instances
Customer
object
Instances
Eq Customer Source # | |
Data Customer Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Customer -> c Customer # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Customer # toConstr :: Customer -> Constr # dataTypeOf :: Customer -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Customer) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Customer) # gmapT :: (forall b. Data b => b -> b) -> Customer -> Customer # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Customer -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Customer -> r # gmapQ :: (forall d. Data d => d -> u) -> Customer -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Customer -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Customer -> m Customer # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Customer -> m Customer # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Customer -> m Customer # | |
Ord Customer Source # | |
Defined in Web.Stripe.Types | |
Read Customer Source # | |
Show Customer Source # | |
FromJSON Customer Source # | JSON Instance for |
newtype AccountBalance Source #
AccountBalance for a Customer
Instances
CardId for a Customer
Instances
newtype RecipientCardId Source #
CardId for a Recipient
Instances
newtype CardNumber Source #
Number associated with a Card
Instances
Expiration Month for a Card
Instances
Eq ExpMonth Source # | |
Data ExpMonth Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExpMonth -> c ExpMonth # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExpMonth # toConstr :: ExpMonth -> Constr # dataTypeOf :: ExpMonth -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExpMonth) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExpMonth) # gmapT :: (forall b. Data b => b -> b) -> ExpMonth -> ExpMonth # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExpMonth -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExpMonth -> r # gmapQ :: (forall d. Data d => d -> u) -> ExpMonth -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExpMonth -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExpMonth -> m ExpMonth # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpMonth -> m ExpMonth # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpMonth -> m ExpMonth # | |
Ord ExpMonth Source # | |
Defined in Web.Stripe.Types | |
Read ExpMonth Source # | |
Show ExpMonth Source # | |
ToStripeParam ExpMonth Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: ExpMonth -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipientCard ExpMonth Source # | |
Defined in Web.Stripe.Card | |
StripeHasParam UpdateCustomerCard ExpMonth Source # | |
Defined in Web.Stripe.Card |
Expiration Year for a Card
Instances
Eq ExpYear Source # | |
Data ExpYear Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExpYear -> c ExpYear # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExpYear # toConstr :: ExpYear -> Constr # dataTypeOf :: ExpYear -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExpYear) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExpYear) # gmapT :: (forall b. Data b => b -> b) -> ExpYear -> ExpYear # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExpYear -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExpYear -> r # gmapQ :: (forall d. Data d => d -> u) -> ExpYear -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExpYear -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExpYear -> m ExpYear # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpYear -> m ExpYear # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpYear -> m ExpYear # | |
Ord ExpYear Source # | |
Read ExpYear Source # | |
Show ExpYear Source # | |
ToStripeParam ExpYear Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: ExpYear -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipientCard ExpYear Source # | |
Defined in Web.Stripe.Card | |
StripeHasParam UpdateCustomerCard ExpYear Source # | |
Defined in Web.Stripe.Card |
CVC for a Card
Instances
Eq CVC Source # | |
Data CVC Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CVC -> c CVC # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CVC # dataTypeOf :: CVC -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CVC) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CVC) # gmapT :: (forall b. Data b => b -> b) -> CVC -> CVC # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CVC -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CVC -> r # gmapQ :: (forall d. Data d => d -> u) -> CVC -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CVC -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CVC -> m CVC # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CVC -> m CVC # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CVC -> m CVC # | |
Ord CVC Source # | |
Read CVC Source # | |
Show CVC Source # | |
ToStripeParam CVC Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: CVC -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # |
newtype AddressCity Source #
City address for a Card
Instances
newtype AddressCountry Source #
Country address for a Card
Instances
newtype AddressLine1 Source #
Address Line One for a Card
Instances
newtype AddressLine2 Source #
Address Line Two for a Card
Instances
newtype AddressState Source #
Address State for a Card
Instances
newtype AddressZip Source #
Address Zip Code for a Card
Instances
newtype IsVerified Source #
IsVerified
Recipients
Instances
Credit / Debit Card Brand
Instances
Eq Brand Source # | |
Data Brand Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Brand -> c Brand # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Brand # dataTypeOf :: Brand -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Brand) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Brand) # gmapT :: (forall b. Data b => b -> b) -> Brand -> Brand # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Brand -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Brand -> r # gmapQ :: (forall d. Data d => d -> u) -> Brand -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Brand -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Brand -> m Brand # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Brand -> m Brand # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Brand -> m Brand # | |
Ord Brand Source # | |
Read Brand Source # | |
Show Brand Source # | |
FromJSON Brand Source # | JSON Instance for |
Card
Object
Instances
Eq Card Source # | |
Data Card Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Card -> c Card # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Card # dataTypeOf :: Card -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Card) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Card) # gmapT :: (forall b. Data b => b -> b) -> Card -> Card # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Card -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Card -> r # gmapQ :: (forall d. Data d => d -> u) -> Card -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Card -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Card -> m Card # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Card -> m Card # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Card -> m Card # | |
Ord Card Source # | |
Read Card Source # | |
Show Card Source # | |
FromJSON Card Source # | JSON Instance for |
data RecipientCard Source #
RecipientCard
object
Instances
Instances
mkNewCard :: CardNumber -> ExpMonth -> ExpYear -> NewCard Source #
create a NewCard
with only the required fields
data DefaultCard Source #
set the DefaultCard
Instances
newtype SubscriptionId Source #
SubscriptionId
for a Subscription
Instances
data Subscription Source #
Subscription Object
Instances
data SubscriptionStatus Source #
Status of a Subscription
Instances
newtype TaxPercent Source #
TaxPercent
for a Subscription
Instances
Instances
Plan object
Plan | |
|
Instances
Eq Plan Source # | |
Data Plan Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Plan -> c Plan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Plan # dataTypeOf :: Plan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Plan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Plan) # gmapT :: (forall b. Data b => b -> b) -> Plan -> Plan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Plan -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Plan -> r # gmapQ :: (forall d. Data d => d -> u) -> Plan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Plan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Plan -> m Plan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Plan -> m Plan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Plan -> m Plan # | |
Ord Plan Source # | |
Read Plan Source # | |
Show Plan Source # | |
FromJSON Plan Source # | JSON Instance for |
newtype TrialPeriod Source #
TrialPeriod
for a Plan
Instances
Eq TrialPeriod Source # | |
Defined in Web.Stripe.Types (==) :: TrialPeriod -> TrialPeriod -> Bool # (/=) :: TrialPeriod -> TrialPeriod -> Bool # | |
Show TrialPeriod Source # | |
Defined in Web.Stripe.Types showsPrec :: Int -> TrialPeriod -> ShowS # show :: TrialPeriod -> String # showList :: [TrialPeriod] -> ShowS # |
TrialEnd
for a Plan
Instances
Interval for Plan
s
Instances
Eq Interval Source # | |
Data Interval Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Interval -> c Interval # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Interval # toConstr :: Interval -> Constr # dataTypeOf :: Interval -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Interval) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Interval) # gmapT :: (forall b. Data b => b -> b) -> Interval -> Interval # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Interval -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Interval -> r # gmapQ :: (forall d. Data d => d -> u) -> Interval -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Interval -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Interval -> m Interval # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Interval -> m Interval # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Interval -> m Interval # | |
Ord Interval Source # | |
Defined in Web.Stripe.Types | |
Read Interval Source # | |
Show Interval Source # | |
FromJSON Interval Source # | JSON Instance for |
ToStripeParam Interval Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Interval -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # |
Coupon
Duration
Instances
Eq Duration Source # | |
Data Duration Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Duration -> c Duration # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Duration # toConstr :: Duration -> Constr # dataTypeOf :: Duration -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Duration) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Duration) # gmapT :: (forall b. Data b => b -> b) -> Duration -> Duration # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Duration -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Duration -> r # gmapQ :: (forall d. Data d => d -> u) -> Duration -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Duration -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Duration -> m Duration # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Duration -> m Duration # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Duration -> m Duration # | |
Ord Duration Source # | |
Defined in Web.Stripe.Types | |
Read Duration Source # | |
Show Duration Source # | |
FromJSON Duration Source # | JSON Instance for |
ToStripeParam Duration Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Duration -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # |
Coupon
Object
Instances
Eq Coupon Source # | |
Data Coupon Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Coupon -> c Coupon # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Coupon # toConstr :: Coupon -> Constr # dataTypeOf :: Coupon -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Coupon) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Coupon) # gmapT :: (forall b. Data b => b -> b) -> Coupon -> Coupon # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Coupon -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Coupon -> r # gmapQ :: (forall d. Data d => d -> u) -> Coupon -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Coupon -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Coupon -> m Coupon # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Coupon -> m Coupon # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Coupon -> m Coupon # | |
Ord Coupon Source # | |
Read Coupon Source # | |
Show Coupon Source # | |
FromJSON Coupon Source # | JSON Instance for |
Instances
Instances
Eq AmountOff Source # | |
Data AmountOff Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AmountOff -> c AmountOff # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AmountOff # toConstr :: AmountOff -> Constr # dataTypeOf :: AmountOff -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AmountOff) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AmountOff) # gmapT :: (forall b. Data b => b -> b) -> AmountOff -> AmountOff # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AmountOff -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AmountOff -> r # gmapQ :: (forall d. Data d => d -> u) -> AmountOff -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AmountOff -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AmountOff -> m AmountOff # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AmountOff -> m AmountOff # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AmountOff -> m AmountOff # | |
Ord AmountOff Source # | |
Defined in Web.Stripe.Types | |
Read AmountOff Source # | |
Show AmountOff Source # | |
ToStripeParam AmountOff Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: AmountOff -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam CreateCoupon AmountOff Source # | |
Defined in Web.Stripe.Coupon |
newtype MaxRedemptions Source #
MaxRedemptions
for a Coupon
Instances
newtype PercentOff Source #
PercentOff
for a Coupon
Instances
Instances
Eq RedeemBy Source # | |
Data RedeemBy Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RedeemBy -> c RedeemBy # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RedeemBy # toConstr :: RedeemBy -> Constr # dataTypeOf :: RedeemBy -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RedeemBy) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RedeemBy) # gmapT :: (forall b. Data b => b -> b) -> RedeemBy -> RedeemBy # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RedeemBy -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RedeemBy -> r # gmapQ :: (forall d. Data d => d -> u) -> RedeemBy -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RedeemBy -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RedeemBy -> m RedeemBy # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RedeemBy -> m RedeemBy # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RedeemBy -> m RedeemBy # | |
Ord RedeemBy Source # | |
Defined in Web.Stripe.Types | |
Read RedeemBy Source # | |
Show RedeemBy Source # | |
ToStripeParam RedeemBy Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: RedeemBy -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam CreateCoupon RedeemBy Source # | |
Defined in Web.Stripe.Coupon |
newtype DurationInMonths Source #
DurationInMonths
for a Coupon
Instances
newtype IntervalCount Source #
IntervalCount
for a Coupon
Instances
newtype TrialPeriodDays Source #
TrialPeriodDays
for a Coupon
Instances
Amount representing a monetary value. Stripe represents pennies as whole numbers i.e. 100 = $1
Instances
Instances
Eq Discount Source # | |
Data Discount Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Discount -> c Discount # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Discount # toConstr :: Discount -> Constr # dataTypeOf :: Discount -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Discount) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Discount) # gmapT :: (forall b. Data b => b -> b) -> Discount -> Discount # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Discount -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Discount -> r # gmapQ :: (forall d. Data d => d -> u) -> Discount -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Discount -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Discount -> m Discount # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Discount -> m Discount # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Discount -> m Discount # | |
Ord Discount Source # | |
Defined in Web.Stripe.Types | |
Read Discount Source # | |
Show Discount Source # | |
FromJSON Discount Source # | JSON Instance for |
Instances
Invoice
Object
Instances
Eq Invoice Source # | |
Data Invoice Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Invoice -> c Invoice # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Invoice # toConstr :: Invoice -> Constr # dataTypeOf :: Invoice -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Invoice) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Invoice) # gmapT :: (forall b. Data b => b -> b) -> Invoice -> Invoice # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Invoice -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Invoice -> r # gmapQ :: (forall d. Data d => d -> u) -> Invoice -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Invoice -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Invoice -> m Invoice # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Invoice -> m Invoice # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Invoice -> m Invoice # | |
Ord Invoice Source # | |
Read Invoice Source # | |
Show Invoice Source # | |
FromJSON Invoice Source # | JSON Instance for |
newtype InvoiceItemId Source #
Instances
data InvoiceItem Source #
InvoiceItem
object
Instances
newtype InvoiceLineItemId Source #
InvoiceLineItemId
for an InvoiceLineItem
Instances
data InvoiceLineItemType Source #
Type of InvoiceItem
Instances
data InvoiceLineItem Source #
InvoiceLineItem
Object
Instances
Period for an InvoiceLineItem
Instances
Eq Period Source # | |
Data Period Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Period -> c Period # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Period # toConstr :: Period -> Constr # dataTypeOf :: Period -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Period) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Period) # gmapT :: (forall b. Data b => b -> b) -> Period -> Period # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Period -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Period -> r # gmapQ :: (forall d. Data d => d -> u) -> Period -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Period -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Period -> m Period # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Period -> m Period # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Period -> m Period # | |
Ord Period Source # | |
Read Period Source # | |
Show Period Source # | |
FromJSON Period Source # | JSON Instance for |
Closed
- invoice closed or not
Instances
Eq Closed Source # | |
Data Closed Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Closed -> c Closed # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Closed # toConstr :: Closed -> Constr # dataTypeOf :: Closed -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Closed) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Closed) # gmapT :: (forall b. Data b => b -> b) -> Closed -> Closed # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Closed -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Closed -> r # gmapQ :: (forall d. Data d => d -> u) -> Closed -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Closed -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Closed -> m Closed # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Closed -> m Closed # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Closed -> m Closed # | |
Ord Closed Source # | |
Read Closed Source # | |
Show Closed Source # | |
ToStripeParam Closed Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Closed -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateInvoice Closed Source # | |
Defined in Web.Stripe.Invoice |
Forgiven
- invoice forgiven or not
Instances
Eq Forgiven Source # | |
Data Forgiven Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Forgiven -> c Forgiven # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Forgiven # toConstr :: Forgiven -> Constr # dataTypeOf :: Forgiven -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Forgiven) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Forgiven) # gmapT :: (forall b. Data b => b -> b) -> Forgiven -> Forgiven # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Forgiven -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Forgiven -> r # gmapQ :: (forall d. Data d => d -> u) -> Forgiven -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Forgiven -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Forgiven -> m Forgiven # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Forgiven -> m Forgiven # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Forgiven -> m Forgiven # | |
Ord Forgiven Source # | |
Defined in Web.Stripe.Types | |
Read Forgiven Source # | |
Show Forgiven Source # | |
ToStripeParam Forgiven Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Forgiven -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateInvoice Forgiven Source # | |
Defined in Web.Stripe.Invoice |
data DisputeStatus Source #
Status of a Dispute
Instances
data DisputeReason Source #
Reason of a Dispute
Duplicate | |
Fraudulent | |
SubscriptionCanceled | |
ProductUnacceptable | |
ProductNotReceived | |
Unrecognized | |
CreditNotProcessed | |
General |
Instances
Dispute
Object
Instances
Eq Dispute Source # | |
Data Dispute Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dispute -> c Dispute # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dispute # toConstr :: Dispute -> Constr # dataTypeOf :: Dispute -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Dispute) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dispute) # gmapT :: (forall b. Data b => b -> b) -> Dispute -> Dispute # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dispute -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dispute -> r # gmapQ :: (forall d. Data d => d -> u) -> Dispute -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dispute -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dispute -> m Dispute # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dispute -> m Dispute # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dispute -> m Dispute # | |
Ord Dispute Source # | |
Read Dispute Source # | |
Show Dispute Source # | |
FromJSON Dispute Source # | JSON Instance for |
Instances
Eq Evidence Source # | |
Data Evidence Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Evidence -> c Evidence # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Evidence # toConstr :: Evidence -> Constr # dataTypeOf :: Evidence -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Evidence) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Evidence) # gmapT :: (forall b. Data b => b -> b) -> Evidence -> Evidence # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Evidence -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Evidence -> r # gmapQ :: (forall d. Data d => d -> u) -> Evidence -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Evidence -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Evidence -> m Evidence # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Evidence -> m Evidence # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Evidence -> m Evidence # | |
Ord Evidence Source # | |
Defined in Web.Stripe.Types | |
Read Evidence Source # | |
Show Evidence Source # | |
ToStripeParam Evidence Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Evidence -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateDispute Evidence Source # | |
Defined in Web.Stripe.Dispute |
newtype TransferId Source #
Instances
data TransferStatus Source #
Status of a Transfer
Instances
data TransferType Source #
Type of a Transfer
Instances
Transfer
Object
Instances
Eq Transfer Source # | |
Data Transfer Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Transfer -> c Transfer # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Transfer # toConstr :: Transfer -> Constr # dataTypeOf :: Transfer -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Transfer) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Transfer) # gmapT :: (forall b. Data b => b -> b) -> Transfer -> Transfer # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Transfer -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Transfer -> r # gmapQ :: (forall d. Data d => d -> u) -> Transfer -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Transfer -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Transfer -> m Transfer # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Transfer -> m Transfer # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Transfer -> m Transfer # | |
Ord Transfer Source # | |
Defined in Web.Stripe.Types | |
Read Transfer Source # | |
Show Transfer Source # | |
FromJSON Transfer Source # | JSON Instance for |
data BankAccount Source #
BankAccount
Object
Instances
newtype BankAccountId Source #
Instances
data BankAccountStatus Source #
BankAccountStatus
Object
Instances
newtype RoutingNumber Source #
Routing Number for Bank Account
Instances
Country
Instances
Eq Country Source # | |
Data Country Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Country -> c Country # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Country # toConstr :: Country -> Constr # dataTypeOf :: Country -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Country) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Country) # gmapT :: (forall b. Data b => b -> b) -> Country -> Country # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Country -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Country -> r # gmapQ :: (forall d. Data d => d -> u) -> Country -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Country -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Country -> m Country # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Country -> m Country # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Country -> m Country # | |
Ord Country Source # | |
Read Country Source # | |
Show Country Source # | |
newtype AccountNumber Source #
Account Number of a Bank Account
Instances
data NewBankAccount Source #
create a new BankAccount
Instances
Instances
Eq FirstName Source # | |
Data FirstName Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FirstName -> c FirstName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FirstName # toConstr :: FirstName -> Constr # dataTypeOf :: FirstName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FirstName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FirstName) # gmapT :: (forall b. Data b => b -> b) -> FirstName -> FirstName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FirstName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FirstName -> r # gmapQ :: (forall d. Data d => d -> u) -> FirstName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FirstName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FirstName -> m FirstName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FirstName -> m FirstName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FirstName -> m FirstName # | |
Ord FirstName Source # | |
Defined in Web.Stripe.Types | |
Read FirstName Source # | |
Show FirstName Source # | |
Instances
Eq LastName Source # | |
Data LastName Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LastName -> c LastName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LastName # toConstr :: LastName -> Constr # dataTypeOf :: LastName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LastName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LastName) # gmapT :: (forall b. Data b => b -> b) -> LastName -> LastName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LastName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LastName -> r # gmapQ :: (forall d. Data d => d -> u) -> LastName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LastName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LastName -> m LastName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LastName -> m LastName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LastName -> m LastName # | |
Ord LastName Source # | |
Defined in Web.Stripe.Types | |
Read LastName Source # | |
Show LastName Source # | |
type MiddleInitial = Char Source #
Middle Initial of a Recipient
newtype RecipientId Source #
RecipientId
for a Recipient
Instances
Instances
Eq TaxID Source # | |
Data TaxID Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TaxID -> c TaxID # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TaxID # dataTypeOf :: TaxID -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TaxID) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TaxID) # gmapT :: (forall b. Data b => b -> b) -> TaxID -> TaxID # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TaxID -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TaxID -> r # gmapQ :: (forall d. Data d => d -> u) -> TaxID -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TaxID -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TaxID -> m TaxID # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TaxID -> m TaxID # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TaxID -> m TaxID # | |
Ord TaxID Source # | |
Read TaxID Source # | |
Show TaxID Source # | |
ToStripeParam TaxID Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: TaxID -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipient TaxID Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam CreateRecipient TaxID Source # | |
Defined in Web.Stripe.Recipient |
data RecipientType Source #
Type of Recipient
Instances
Recipient Object
Instances
Eq Recipient Source # | |
Data Recipient Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Recipient -> c Recipient # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Recipient # toConstr :: Recipient -> Constr # dataTypeOf :: Recipient -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Recipient) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Recipient) # gmapT :: (forall b. Data b => b -> b) -> Recipient -> Recipient # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Recipient -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Recipient -> r # gmapQ :: (forall d. Data d => d -> u) -> Recipient -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Recipient -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Recipient -> m Recipient # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Recipient -> m Recipient # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Recipient -> m Recipient # | |
Ord Recipient Source # | |
Defined in Web.Stripe.Types | |
Read Recipient Source # | |
Show Recipient Source # | |
FromJSON Recipient Source # | JSON Instance for |
newtype ApplicationFeeId Source #
Instances
data ApplicationFee Source #
ApplicationFee Object
Instances
newtype ApplicationFeePercent Source #
ApplicationFeePercent
Instances
newtype ApplicationFeeAmount Source #
ApplicationFeeAmount
Instances
newtype ApplicationId Source #
ApplicationId
object
Instances
FeeId
for objects with Fees
Instances
Eq FeeId Source # | |
Data FeeId Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FeeId -> c FeeId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FeeId # dataTypeOf :: FeeId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FeeId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FeeId) # gmapT :: (forall b. Data b => b -> b) -> FeeId -> FeeId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FeeId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FeeId -> r # gmapQ :: (forall d. Data d => d -> u) -> FeeId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FeeId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FeeId -> m FeeId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FeeId -> m FeeId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FeeId -> m FeeId # | |
Ord FeeId Source # | |
Read FeeId Source # | |
Show FeeId Source # | |
data ApplicationFeeRefund Source #
Application Fee Refunds
Instances
Instances
Eq AccountId Source # | |
Data AccountId Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountId -> c AccountId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountId # toConstr :: AccountId -> Constr # dataTypeOf :: AccountId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AccountId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountId) # gmapT :: (forall b. Data b => b -> b) -> AccountId -> AccountId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountId -> r # gmapQ :: (forall d. Data d => d -> u) -> AccountId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountId -> m AccountId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountId -> m AccountId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountId -> m AccountId # | |
Ord AccountId Source # | |
Defined in Web.Stripe.Types | |
Read AccountId Source # | |
Show AccountId Source # | |
FromJSON AccountId Source # | JSON Instance for |
type ExpandsTo AccountId Source # | |
Defined in Web.Stripe.Types |
Account
Object
Instances
Eq Account Source # | |
Data Account Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Account -> c Account # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Account # toConstr :: Account -> Constr # dataTypeOf :: Account -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Account) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Account) # gmapT :: (forall b. Data b => b -> b) -> Account -> Account # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r # gmapQ :: (forall d. Data d => d -> u) -> Account -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Account -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Account -> m Account # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account # | |
Ord Account Source # | |
Read Account Source # | |
Show Account Source # | |
FromJSON Account Source # | JSON Instance for |
Balance
Object
Balance | |
|
Instances
Eq Balance Source # | |
Data Balance Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Balance -> c Balance # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Balance # toConstr :: Balance -> Constr # dataTypeOf :: Balance -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Balance) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Balance) # gmapT :: (forall b. Data b => b -> b) -> Balance -> Balance # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Balance -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Balance -> r # gmapQ :: (forall d. Data d => d -> u) -> Balance -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Balance -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Balance -> m Balance # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Balance -> m Balance # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Balance -> m Balance # | |
Ord Balance Source # | |
Read Balance Source # | |
Show Balance Source # | |
FromJSON Balance Source # | JSON Instance for |
data BalanceAmount Source #
BalanceAmount
Object
Instances
data BalanceTransaction Source #
BalanceTransaction
Object
Instances
newtype TransactionId Source #
TransactionId
of a Transaction
Instances
data FeeDetails Source #
FeeDetails
Object
Instances
Instances
ToStripeParam a => StripeHasParam GetBalanceTransactionHistory (Source a) Source # | |
Defined in Web.Stripe.Balance | |
Eq a => Eq (Source a) Source # | |
Data a => Data (Source a) Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Source a -> c (Source a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Source a) # toConstr :: Source a -> Constr # dataTypeOf :: Source a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Source a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Source a)) # gmapT :: (forall b. Data b => b -> b) -> Source a -> Source a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Source a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Source a -> r # gmapQ :: (forall d. Data d => d -> u) -> Source a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Source a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Source a -> m (Source a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Source a -> m (Source a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Source a -> m (Source a) # | |
Ord a => Ord (Source a) Source # | |
Defined in Web.Stripe.Types | |
Read a => Read (Source a) Source # | |
Show a => Show (Source a) Source # | |
ToStripeParam a => ToStripeParam (Source a) Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Source a -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # |
data TransactionType Source #
transaction type for BalanceTransaction
ChargeTxn | |
RefundTxn | |
AdjustmentTxn | |
ApplicationFeeTxn | |
ApplicationFeeRefundTxn | |
TransferTxn | |
TransferCancelTxn | |
TransferFailureTxn |
Instances
Event
Types
Instances
Eq EventType Source # | |
Data EventType Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventType -> c EventType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventType # toConstr :: EventType -> Constr # dataTypeOf :: EventType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EventType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventType) # gmapT :: (forall b. Data b => b -> b) -> EventType -> EventType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventType -> r # gmapQ :: (forall d. Data d => d -> u) -> EventType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EventType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventType -> m EventType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventType -> m EventType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventType -> m EventType # | |
Ord EventType Source # | |
Defined in Web.Stripe.Types | |
Read EventType Source # | |
Show EventType Source # | |
FromJSON EventType Source # | Event Types JSON Instance |
Instances
Eq EventId Source # | |
Data EventId Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventId -> c EventId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventId # toConstr :: EventId -> Constr # dataTypeOf :: EventId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EventId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventId) # gmapT :: (forall b. Data b => b -> b) -> EventId -> EventId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventId -> r # gmapQ :: (forall d. Data d => d -> u) -> EventId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EventId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventId -> m EventId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventId -> m EventId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventId -> m EventId # | |
Ord EventId Source # | |
Read EventId Source # | |
Show EventId Source # | |
ToStripeParam EventId Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: EventId -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam GetEvents (EndingBefore EventId) Source # | |
Defined in Web.Stripe.Event | |
StripeHasParam GetEvents (StartingAfter EventId) Source # | |
Defined in Web.Stripe.Event |
EventData
Instances
Eq EventData Source # | |
Data EventData Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EventData -> c EventData # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EventData # toConstr :: EventData -> Constr # dataTypeOf :: EventData -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EventData) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EventData) # gmapT :: (forall b. Data b => b -> b) -> EventData -> EventData # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EventData -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EventData -> r # gmapQ :: (forall d. Data d => d -> u) -> EventData -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> EventData -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EventData -> m EventData # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EventData -> m EventData # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EventData -> m EventData # | |
Ord EventData Source # | |
Defined in Web.Stripe.Types | |
Read EventData Source # | |
Show EventData Source # | |
Event
Object
Event | |
|
Instances
Eq Event Source # | |
Data Event Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Event -> c Event # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Event # dataTypeOf :: Event -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Event) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Event) # gmapT :: (forall b. Data b => b -> b) -> Event -> Event # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Event -> r # gmapQ :: (forall d. Data d => d -> u) -> Event -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Event -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Event -> m Event # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Event -> m Event # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Event -> m Event # | |
Ord Event Source # | |
Read Event Source # | |
Show Event Source # | |
FromJSON Event Source # | JSON Instance for |
data ConnectApp Source #
Connect Application
Instances
Instances
Type of Token
Instances
Eq TokenType Source # | |
Data TokenType Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TokenType -> c TokenType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TokenType # toConstr :: TokenType -> Constr # dataTypeOf :: TokenType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TokenType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenType) # gmapT :: (forall b. Data b => b -> b) -> TokenType -> TokenType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TokenType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TokenType -> r # gmapQ :: (forall d. Data d => d -> u) -> TokenType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TokenType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TokenType -> m TokenType # | |
Ord TokenType Source # | |
Defined in Web.Stripe.Types | |
Read TokenType Source # | |
Show TokenType Source # | |
FromJSON TokenType Source # | JSON Instance for |
Token
Object
Token | |
|
Instances
Eq a => Eq (Token a) Source # | |
Data a => Data (Token a) Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Token a -> c (Token a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Token a) # toConstr :: Token a -> Constr # dataTypeOf :: Token a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Token a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Token a)) # gmapT :: (forall b. Data b => b -> b) -> Token a -> Token a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Token a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Token a -> r # gmapQ :: (forall d. Data d => d -> u) -> Token a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Token a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Token a -> m (Token a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Token a -> m (Token a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Token a -> m (Token a) # | |
Ord a => Ord (Token a) Source # | |
Read a => Read (Token a) Source # | |
Show a => Show (Token a) Source # | |
FromJSON a => FromJSON (Token a) Source # | JSON Instance for |
data StripeList a Source #
Generic handling of Stripe JSON arrays
Instances
Pagination Option for StripeList
Instances
newtype StartingAfter a Source #
Pagination Option for StripeList
Instances
newtype EndingBefore a Source #
Pagination Option for StripeList
Instances
data StripeDeleteResult Source #
JSON returned from a Stripe
deletion request
Instances
Type of MetaData for use on Stripe
objects
Instances
newtype ExpandParams Source #
Type of Expansion Parameters for use on Stripe
objects
Instances
a cardholder's full name
Instances
Eq Name Source # | |
Data Name Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name # dataTypeOf :: Name -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) # gmapT :: (forall b. Data b => b -> b) -> Name -> Name # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # | |
Ord Name Source # | |
Read Name Source # | |
Show Name Source # | |
FromJSON Name Source # | |
ToStripeParam Name Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Name -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipient Name Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam UpdateRecipientCard Name Source # | |
Defined in Web.Stripe.Card | |
StripeHasParam UpdateCustomerCard Name Source # | |
Defined in Web.Stripe.Card |
a plan name
Instances
Eq PlanName Source # | |
Data PlanName Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PlanName -> c PlanName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PlanName # toConstr :: PlanName -> Constr # dataTypeOf :: PlanName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PlanName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PlanName) # gmapT :: (forall b. Data b => b -> b) -> PlanName -> PlanName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PlanName -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PlanName -> r # gmapQ :: (forall d. Data d => d -> u) -> PlanName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PlanName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PlanName -> m PlanName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PlanName -> m PlanName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PlanName -> m PlanName # | |
Ord PlanName Source # | |
Defined in Web.Stripe.Types | |
Read PlanName Source # | |
Show PlanName Source # | |
FromJSON PlanName Source # | |
ToStripeParam PlanName Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: PlanName -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdatePlan PlanName Source # | |
Defined in Web.Stripe.Plan |
newtype Description Source #
Generic Description for use in constructing API Calls
Instances
Generic Quantity
type to be used with Customer
,
Subscription
and InvoiceLineItem
API requests
Instances
Prorate
Instances
Eq Prorate Source # | |
Data Prorate Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Prorate -> c Prorate # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Prorate # toConstr :: Prorate -> Constr # dataTypeOf :: Prorate -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Prorate) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Prorate) # gmapT :: (forall b. Data b => b -> b) -> Prorate -> Prorate # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Prorate -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Prorate -> r # gmapQ :: (forall d. Data d => d -> u) -> Prorate -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Prorate -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Prorate -> m Prorate # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Prorate -> m Prorate # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Prorate -> m Prorate # | |
Ord Prorate Source # | |
Read Prorate Source # | |
Show Prorate Source # | |
ToStripeParam Prorate Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Prorate -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateSubscription Prorate Source # | |
Defined in Web.Stripe.Subscription | |
StripeHasParam CreateSubscription Prorate Source # | |
Defined in Web.Stripe.Subscription |
newtype AtPeriodEnd Source #
A flag that if set to true will delay the cancellation of the subscription until the end of the current period.
Instances
Instances
Eq Email Source # | |
Data Email Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Email -> c Email # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Email # dataTypeOf :: Email -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Email) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Email) # gmapT :: (forall b. Data b => b -> b) -> Email -> Email # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Email -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Email -> r # gmapQ :: (forall d. Data d => d -> u) -> Email -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Email -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Email -> m Email # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Email -> m Email # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Email -> m Email # | |
Ord Email Source # | |
Read Email Source # | |
Show Email Source # | |
ToStripeParam Email Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Email -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipient Email Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam CreateRecipient Email Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam UpdateCustomer Email Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam CreateCustomer Email Source # | |
Defined in Web.Stripe.Customer |
newtype ReceiptEmail Source #
Email
to send receipt to
Instances
Stripe supports 138 currencies
AED | United Arab Emirates Dirham |
AFN | Afghan Afghani |
ALL | Albanian Lek |
AMD | Armenian Dram |
ANG | Netherlands Antillean Gulden |
AOA | Angolan Kwanza |
ARS | Argentine Peso |
AUD | Australian Dollar |
AWG | Aruban Florin |
AZN | Azerbaijani Manat |
BAM | Bosnia & Herzegovina Convertible Mark |
BBD | Barbadian Dollar |
BDT | Bangladeshi Taka |
BGN | Bulgarian Lev |
BIF | Burundian Franc |
BMD | Bermudian Dollar |
BND | Brunei Dollar |
BOB | Bolivian Boliviano |
BRL | Brazilian Real |
BSD | Bahamian Dollar |
BWP | Botswana Pula |
BZD | Belize Dollar |
CAD | Canadian Dollar |
CDF | Congolese Franc |
CHF | Swiss Franc |
CLP | Chilean Peso |
CNY | Chinese Renminbi Yuan |
COP | Colombian Peso |
CRC | Costa Rican Colón |
CVE | Cape Verdean Escudo |
CZK | Czech Koruna |
DJF | Djiboutian Franc |
DKK | Danish Krone |
DOP | Dominican Peso |
DZD | Algerian Dinar |
EEK | Estonian Kroon |
EGP | Egyptian Pound |
ETB | Ethiopian Birr |
EUR | Euro |
FJD | Fijian Dollar |
FKP | Falkland Islands Pound |
GBP | British Pound |
GEL | Georgian Lari |
GIP | Gibraltar Pound |
GMD | Gambian Dalasi |
GNF | Guinean Franc |
GTQ | Guatemalan Quetzal |
GYD | Guyanese Dollar |
HKD | Hong Kong Dollar |
HNL | Honduran Lempira |
HRK | Croatian Kuna |
HTG | Haitian Gourde |
HUF | Hungarian Forint |
IDR | Indonesian Rupiah |
ILS | Israeli New Sheqel |
INR | Indian Rupee |
ISK | Icelandic Króna |
JMD | Jamaican Dollar |
JPY | Japanese Yen |
KES | Kenyan Shilling |
KGS | Kyrgyzstani Som |
KHR | Cambodian Riel |
KMF | Comorian Franc |
KRW | South Korean Won |
KYD | Cayman Islands Dollar |
KZT | Kazakhstani Tenge |
LAK | Lao Kip |
LBP | Lebanese Pound |
LKR | Sri Lankan Rupee |
LRD | Liberian Dollar |
LSL | Lesotho Loti |
LTL | Lithuanian Litas |
LVL | Latvian Lats |
MAD | Moroccan Dirham |
MDL | Moldovan Leu |
MGA | Malagasy Ariary |
MKD | Macedonian Denar |
MNT | Mongolian Tögrög |
MOP | Macanese Pataca |
MRO | Mauritanian Ouguiya |
MUR | Mauritian Rupee |
MVR | Maldivian Rufiyaa |
MWK | Malawian Kwacha |
MXN | Mexican Peso |
MYR | Malaysian Ringgit |
MZN | Mozambican Metical |
NAD | Namibian Dollar |
NGN | Nigerian Naira |
NIO | Nicaraguan Córdoba |
NOK | Norwegian Krone |
NPR | Nepalese Rupee |
NZD | New Zealand Dollar |
PAB | Panamanian Balboa |
PEN | Peruvian Nuevo Sol |
PGK | Papua New Guinean Kina |
PHP | Philippine Peso |
PKR | Pakistani Rupee |
PLN | Polish Złoty |
PYG | Paraguayan Guaraní |
QAR | Qatari Riyal |
RON | Romanian Leu |
RSD | Serbian Dinar |
RUB | Russian Ruble |
RWF | Rwandan Franc |
SAR | Saudi Riyal |
SBD | Solomon Islands Dollar |
SCR | Seychellois Rupee |
SEK | Swedish Krona |
SGD | Singapore Dollar |
SHP | Saint Helenian Pound |
SLL | Sierra Leonean Leone |
SOS | Somali Shilling |
SRD | Surinamese Dollar |
STD | São Tomé and Príncipe Dobra |
SVC | Salvadoran Colón |
SZL | Swazi Lilangeni |
THB | Thai Baht |
TJS | Tajikistani Somoni |
TOP | Tongan Paʻanga |
TRY | Turkish Lira |
TTD | Trinidad and Tobago Dollar |
TWD | New Taiwan Dollar |
TZS | Tanzanian Shilling |
UAH | Ukrainian Hryvnia |
UGX | Ugandan Shilling |
USD | United States Dollar |
UYU | Uruguayan Peso |
UZS | Uzbekistani Som |
VND | Vietnamese Đồng |
VUV | Vanuatu Vatu |
WST | Samoan Tala |
XAF | Central African Cfa Franc |
XCD | East Caribbean Dollar |
XOF | West African Cfa Franc |
XPF | Cfp Franc |
YER | Yemeni Rial |
ZAR | South African Rand |
ZMW | Zambian Kwacha |
UnknownCurrency | Unknown Currency |
Instances
Eq Currency Source # | |
Data Currency Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Currency -> c Currency # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Currency # toConstr :: Currency -> Constr # dataTypeOf :: Currency -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Currency) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Currency) # gmapT :: (forall b. Data b => b -> b) -> Currency -> Currency # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Currency -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Currency -> r # gmapQ :: (forall d. Data d => d -> u) -> Currency -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Currency -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Currency -> m Currency # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Currency -> m Currency # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Currency -> m Currency # | |
Ord Currency Source # | |
Defined in Web.Stripe.Types | |
Read Currency Source # | |
Show Currency Source # | |
FromJSON Currency Source # |
|
ToStripeParam Currency Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Currency -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam CreateCoupon Currency Source # | |
Defined in Web.Stripe.Coupon | |
StripeHasParam GetBalanceTransactionHistory Currency Source # | |
Defined in Web.Stripe.Balance |
data BitcoinReceiver Source #
BTC ReceiverObject
Instances
Eq BitcoinReceiver Source # | |
Defined in Web.Stripe.Types (==) :: BitcoinReceiver -> BitcoinReceiver -> Bool # (/=) :: BitcoinReceiver -> BitcoinReceiver -> Bool # | |
Show BitcoinReceiver Source # | |
Defined in Web.Stripe.Types showsPrec :: Int -> BitcoinReceiver -> ShowS # show :: BitcoinReceiver -> String # showList :: [BitcoinReceiver] -> ShowS # | |
FromJSON BitcoinReceiver Source # | FromJSON for BitcoinReceiverId |
Defined in Web.Stripe.Types parseJSON :: Value -> Parser BitcoinReceiver # parseJSONList :: Value -> Parser [BitcoinReceiver] # |
data Transactions Source #
Bitcoin Transactions
Instances
Eq Transactions Source # | |
Defined in Web.Stripe.Types (==) :: Transactions -> Transactions -> Bool # (/=) :: Transactions -> Transactions -> Bool # | |
Show Transactions Source # | |
Defined in Web.Stripe.Types showsPrec :: Int -> Transactions -> ShowS # show :: Transactions -> String # showList :: [Transactions] -> ShowS # | |
FromJSON Transactions Source # | Bitcoin Transactions data |
Defined in Web.Stripe.Types parseJSON :: Value -> Parser Transactions # parseJSONList :: Value -> Parser [Transactions] # |
data BitcoinTransaction Source #
Bitcoin Transaction
Instances
Eq BitcoinTransaction Source # | |
Defined in Web.Stripe.Types (==) :: BitcoinTransaction -> BitcoinTransaction -> Bool # (/=) :: BitcoinTransaction -> BitcoinTransaction -> Bool # | |
Show BitcoinTransaction Source # | |
Defined in Web.Stripe.Types showsPrec :: Int -> BitcoinTransaction -> ShowS # show :: BitcoinTransaction -> String # showList :: [BitcoinTransaction] -> ShowS # | |
FromJSON BitcoinTransaction Source # | FromJSON BitcoinTransaction |
Defined in Web.Stripe.Types parseJSON :: Value -> Parser BitcoinTransaction # parseJSONList :: Value -> Parser [BitcoinTransaction] # |
newtype BitcoinTransactionId Source #
BitcoinTransactionId
Instances
Eq BitcoinTransactionId Source # | |
Defined in Web.Stripe.Types (==) :: BitcoinTransactionId -> BitcoinTransactionId -> Bool # (/=) :: BitcoinTransactionId -> BitcoinTransactionId -> Bool # | |
Show BitcoinTransactionId Source # | |
Defined in Web.Stripe.Types showsPrec :: Int -> BitcoinTransactionId -> ShowS # show :: BitcoinTransactionId -> String # showList :: [BitcoinTransactionId] -> ShowS # | |
FromJSON BitcoinTransactionId Source # | FromJSON BitcoinTransactionId |
Defined in Web.Stripe.Types parseJSON :: Value -> Parser BitcoinTransactionId # parseJSONList :: Value -> Parser [BitcoinTransactionId] # |
newtype BitcoinReceiverId Source #
BTC ReceiverId
Instances
Eq BitcoinReceiverId Source # | |
Defined in Web.Stripe.Types (==) :: BitcoinReceiverId -> BitcoinReceiverId -> Bool # (/=) :: BitcoinReceiverId -> BitcoinReceiverId -> Bool # | |
Show BitcoinReceiverId Source # | |
Defined in Web.Stripe.Types showsPrec :: Int -> BitcoinReceiverId -> ShowS # show :: BitcoinReceiverId -> String # showList :: [BitcoinReceiverId] -> ShowS # | |
FromJSON BitcoinReceiverId Source # | FromJSON for BitcoinReceiverId |
Defined in Web.Stripe.Types parseJSON :: Value -> Parser BitcoinReceiverId # parseJSONList :: Value -> Parser [BitcoinReceiverId] # |
BTC PaymentId
Show an amount accounting for zero currencies
https://support.stripe.com/questions/which-zero-decimal-currencies-does-stripe-support