stripe-core-2.2.1: Stripe API for Haskell - Pure Core

Copyright(c) David Johnson 2014
Maintainerdjohnson.m@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Web.Stripe.StripeRequest

Contents

Description

 

Synopsis

Types

data Method Source #

HTTP Method

The other methods are not required by the Stripe API

Constructors

DELETE 
GET 
POST 

data Expandable id Source #

a wrapper for fields which can either be an id or an expanded object

Constructors

Id id

an id such as CardId, AccountId, CustomerId, etc

Expanded (ExpandsTo id)

expanded object such as Card, Account, Customer, etc

Instances

(Eq id, Eq (ExpandsTo id)) => Eq (Expandable id) Source # 

Methods

(==) :: Expandable id -> Expandable id -> Bool #

(/=) :: Expandable id -> Expandable id -> Bool #

(Data id, Data (ExpandsTo id)) => Data (Expandable id) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Expandable id -> c (Expandable id) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Expandable id) #

toConstr :: Expandable id -> Constr #

dataTypeOf :: Expandable id -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Expandable id)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Expandable id)) #

gmapT :: (forall b. Data b => b -> b) -> Expandable id -> Expandable id #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Expandable id -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Expandable id -> r #

gmapQ :: (forall d. Data d => d -> u) -> Expandable id -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Expandable id -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Expandable id -> m (Expandable id) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Expandable id -> m (Expandable id) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Expandable id -> m (Expandable id) #

(Ord id, Ord (ExpandsTo id)) => Ord (Expandable id) Source # 

Methods

compare :: Expandable id -> Expandable id -> Ordering #

(<) :: Expandable id -> Expandable id -> Bool #

(<=) :: Expandable id -> Expandable id -> Bool #

(>) :: Expandable id -> Expandable id -> Bool #

(>=) :: Expandable id -> Expandable id -> Bool #

max :: Expandable id -> Expandable id -> Expandable id #

min :: Expandable id -> Expandable id -> Expandable id #

(Read id, Read (ExpandsTo id)) => Read (Expandable id) Source # 
(Show id, Show (ExpandsTo id)) => Show (Expandable id) Source # 

Methods

showsPrec :: Int -> Expandable id -> ShowS #

show :: Expandable id -> String #

showList :: [Expandable id] -> ShowS #

(FromJSON id, FromJSON (ExpandsTo id)) => FromJSON (Expandable id) Source #

JSON Instance for Expandable

newtype ExpandParams Source #

Type of Expansion Parameters for use on Stripe objects

Constructors

ExpandParams 

Fields

Instances

Eq ExpandParams Source # 
Data ExpandParams Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExpandParams -> c ExpandParams #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExpandParams #

toConstr :: ExpandParams -> Constr #

dataTypeOf :: ExpandParams -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ExpandParams) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExpandParams) #

gmapT :: (forall b. Data b => b -> b) -> ExpandParams -> ExpandParams #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExpandParams -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExpandParams -> r #

gmapQ :: (forall d. Data d => d -> u) -> ExpandParams -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExpandParams -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExpandParams -> m ExpandParams #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpandParams -> m ExpandParams #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpandParams -> m ExpandParams #

Ord ExpandParams Source # 
Read ExpandParams Source # 
Show ExpandParams Source # 
ToStripeParam ExpandParams Source # 
StripeHasParam GetSubscriptions ExpandParams Source # 
StripeHasParam GetSubscription ExpandParams Source # 
StripeHasParam GetTransfers ExpandParams Source # 
StripeHasParam GetTransfer ExpandParams Source # 
StripeHasParam GetRefunds ExpandParams Source # 
StripeHasParam GetRefund ExpandParams Source # 
StripeHasParam GetRecipients ExpandParams Source # 
StripeHasParam GetRecipient ExpandParams Source # 
StripeHasParam GetInvoiceItems ExpandParams Source # 
StripeHasParam GetInvoiceItem ExpandParams Source # 
StripeHasParam GetInvoices ExpandParams Source # 
StripeHasParam GetInvoice ExpandParams Source # 
StripeHasParam GetCustomers ExpandParams Source # 
StripeHasParam GetCustomer ExpandParams Source # 
StripeHasParam GetCharges ExpandParams Source # 
StripeHasParam GetCharge ExpandParams Source # 
StripeHasParam CreateCharge ExpandParams Source # 
StripeHasParam GetRecipientCards ExpandParams Source # 
StripeHasParam GetCustomerCards ExpandParams Source # 
StripeHasParam GetRecipientCard ExpandParams Source # 
StripeHasParam GetCustomerCard ExpandParams Source # 
StripeHasParam GetBalanceTransaction ExpandParams Source # 
StripeHasParam GetApplicationFeeRefunds ExpandParams Source # 
StripeHasParam GetApplicationFeeRefund ExpandParams Source # 
StripeHasParam GetApplicationFees ExpandParams Source # 
StripeHasParam GetApplicationFee ExpandParams Source # 

newtype Param k v Source #

used to set a specific key/value pair when the type is not enough

Constructors

Param (k, v) 

type Params = [(ByteString, ByteString)] Source #

HTTP Params

data StripeRequest a Source #

Stripe Request holding Method, URL and Params for a Request. Also includes the function needed to decode the response.

Constructors

StripeRequest 

Fields

type family StripeReturn a :: * Source #

return type of stripe request

Instances

type StripeReturn GetSubscriptions Source # 
type StripeReturn CancelSubscription Source # 
type StripeReturn UpdateSubscription Source # 
type StripeReturn GetSubscription Source # 
type StripeReturn CreateSubscription Source # 
type StripeReturn GetBankAccountToken Source # 
type StripeReturn GetCardToken Source # 
type StripeReturn CreateBankAccountToken Source # 
type StripeReturn CreateCardToken Source # 
type StripeReturn GetTransfers Source # 
type StripeReturn CancelTransfer Source # 
type StripeReturn UpdateTransfer Source # 
type StripeReturn GetTransfer Source # 
type StripeReturn CreateTransfer Source # 
type StripeReturn GetRefunds Source # 
type StripeReturn UpdateRefund Source # 
type StripeReturn GetRefund Source # 
type StripeReturn CreateRefund Source # 
type StripeReturn GetRecipients Source # 
type StripeReturn DeleteRecipient Source # 
type StripeReturn UpdateRecipient Source # 
type StripeReturn GetRecipient Source # 
type StripeReturn CreateRecipient Source # 
type StripeReturn GetPlans Source # 
type StripeReturn DeletePlan Source # 
type StripeReturn UpdatePlan Source # 
type StripeReturn GetPlan Source # 
type StripeReturn CreatePlan Source # 
type StripeReturn GetInvoiceItems Source # 
type StripeReturn DeleteInvoiceItem Source # 
type StripeReturn UpdateInvoiceItem Source # 
type StripeReturn GetInvoiceItem Source # 
type StripeReturn CreateInvoiceItem Source # 
type StripeReturn PayInvoice Source # 
type StripeReturn UpdateInvoice Source # 
type StripeReturn GetUpcomingInvoice Source # 
type StripeReturn GetInvoiceLineItems Source # 
type StripeReturn GetInvoices Source # 
type StripeReturn GetInvoice Source # 
type StripeReturn CreateInvoice Source # 
type StripeReturn GetEvents Source # 
type StripeReturn GetEvent Source # 
type StripeReturn CloseDispute Source # 
type StripeReturn UpdateDispute Source # 
type StripeReturn DeleteSubscriptionDiscount Source # 
type StripeReturn DeleteCustomerDiscount Source # 
type StripeReturn GetCustomers Source # 
type StripeReturn DeleteCustomer Source # 
type StripeReturn UpdateCustomer Source # 
type StripeReturn GetCustomer Source # 
type StripeReturn CreateCustomer Source # 
type StripeReturn GetCoupons Source # 
type StripeReturn DeleteCoupon Source # 
type StripeReturn UpdateCoupon Source # 
type StripeReturn GetCoupon Source # 
type StripeReturn CreateCoupon Source # 
type StripeReturn GetCharges Source # 
type StripeReturn CaptureCharge Source # 
type StripeReturn UpdateCharge Source # 
type StripeReturn GetCharge Source # 
type StripeReturn CreateCharge Source # 
type StripeReturn GetRecipientCards Source # 
type StripeReturn GetCustomerCards Source # 
type StripeReturn DeleteRecipientCard Source # 
type StripeReturn DeleteCustomerCard Source # 
type StripeReturn UpdateRecipientCard Source # 
type StripeReturn UpdateCustomerCard Source # 
type StripeReturn GetRecipientCard Source # 
type StripeReturn GetCustomerCard Source # 
type StripeReturn CreateRecipientCard Source # 
type StripeReturn CreateCustomerCard Source # 
type StripeReturn CreateRecipientCardByToken Source # 
type StripeReturn CreateCustomerCardByToken Source # 
type StripeReturn GetBalanceTransactionHistory Source # 
type StripeReturn GetBalanceTransaction Source # 
type StripeReturn GetBalance Source # 
type StripeReturn GetApplicationFeeRefunds Source # 
type StripeReturn UpdateApplicationFeeRefund Source # 
type StripeReturn GetApplicationFeeRefund Source # 
type StripeReturn CreateApplicationFeeRefund Source # 
type StripeReturn GetApplicationFees Source # 
type StripeReturn GetApplicationFee Source # 
type StripeReturn GetAccountDetails Source # 

class ToStripeParam param => StripeHasParam request param Source #

indicate if a request allows an optional parameter

Instances

StripeHasParam GetSubscriptions ExpandParams Source # 
StripeHasParam GetSubscriptions Limit Source # 
StripeHasParam CancelSubscription AtPeriodEnd Source # 
StripeHasParam UpdateSubscription Prorate Source # 
StripeHasParam UpdateSubscription Quantity Source # 
StripeHasParam UpdateSubscription MetaData Source # 
StripeHasParam UpdateSubscription ApplicationFeePercent Source # 
StripeHasParam UpdateSubscription CouponId Source # 
StripeHasParam UpdateSubscription TrialEnd Source # 
StripeHasParam UpdateSubscription PlanId Source # 
StripeHasParam UpdateSubscription TaxPercent Source # 
StripeHasParam UpdateSubscription CardId Source # 
StripeHasParam GetSubscription ExpandParams Source # 
StripeHasParam CreateSubscription Prorate Source # 
StripeHasParam CreateSubscription Quantity Source # 
StripeHasParam CreateSubscription MetaData Source # 
StripeHasParam CreateSubscription ApplicationFeePercent Source # 
StripeHasParam CreateSubscription CouponId Source # 
StripeHasParam CreateSubscription TrialEnd Source # 
StripeHasParam CreateSubscription TaxPercent Source # 
StripeHasParam CreateSubscription CardId Source # 
StripeHasParam CreateCardToken CustomerId Source # 
StripeHasParam GetTransfers ExpandParams Source # 
StripeHasParam GetTransfers Limit Source # 
StripeHasParam GetTransfers RecipientId Source # 
StripeHasParam GetTransfers TransferStatus Source # 
StripeHasParam GetTransfers Date Source # 
StripeHasParam GetTransfers Created Source # 
StripeHasParam UpdateTransfer Description Source # 
StripeHasParam UpdateTransfer MetaData Source # 
StripeHasParam GetTransfer ExpandParams Source # 
StripeHasParam CreateTransfer Description Source # 
StripeHasParam CreateTransfer MetaData Source # 
StripeHasParam CreateTransfer BankAccountId Source # 
StripeHasParam CreateTransfer CardId Source # 
StripeHasParam CreateTransfer StatementDescription Source # 
StripeHasParam GetRefunds ExpandParams Source # 
StripeHasParam GetRefunds Limit Source # 
StripeHasParam UpdateRefund MetaData Source # 
StripeHasParam GetRefund ExpandParams Source # 
StripeHasParam CreateRefund MetaData Source # 
StripeHasParam CreateRefund Amount Source # 
StripeHasParam CreateRefund RefundReason Source # 
StripeHasParam CreateRefund RefundApplicationFee Source # 
StripeHasParam GetRecipients ExpandParams Source # 
StripeHasParam GetRecipients Limit Source # 
StripeHasParam GetRecipients IsVerified Source # 
StripeHasParam UpdateRecipient Email Source # 
StripeHasParam UpdateRecipient Description Source # 
StripeHasParam UpdateRecipient Name Source # 
StripeHasParam UpdateRecipient MetaData Source # 
StripeHasParam UpdateRecipient TokenId Source # 
StripeHasParam UpdateRecipient TaxID Source # 
StripeHasParam UpdateRecipient NewBankAccount Source # 
StripeHasParam UpdateRecipient DefaultCard Source # 
StripeHasParam UpdateRecipient NewCard Source # 
StripeHasParam UpdateRecipient CardId Source # 
StripeHasParam GetRecipient ExpandParams Source # 
StripeHasParam CreateRecipient Email Source # 
StripeHasParam CreateRecipient Description Source # 
StripeHasParam CreateRecipient MetaData Source # 
StripeHasParam CreateRecipient TokenId Source # 
StripeHasParam CreateRecipient TaxID Source # 
StripeHasParam CreateRecipient NewBankAccount Source # 
StripeHasParam CreateRecipient NewCard Source # 
StripeHasParam CreateRecipient CardId Source # 
StripeHasParam GetPlans Limit Source # 
StripeHasParam UpdatePlan PlanName Source # 
StripeHasParam UpdatePlan MetaData Source # 
StripeHasParam UpdatePlan StatementDescription Source # 
StripeHasParam CreatePlan MetaData Source # 
StripeHasParam CreatePlan TrialPeriodDays Source # 
StripeHasParam CreatePlan IntervalCount Source # 
StripeHasParam CreatePlan StatementDescription Source # 
StripeHasParam GetInvoiceItems ExpandParams Source # 
StripeHasParam GetInvoiceItems Limit Source # 
StripeHasParam GetInvoiceItems CustomerId Source # 
StripeHasParam GetInvoiceItems Created Source # 
StripeHasParam UpdateInvoiceItem Description Source # 
StripeHasParam UpdateInvoiceItem MetaData Source # 
StripeHasParam UpdateInvoiceItem Amount Source # 
StripeHasParam GetInvoiceItem ExpandParams Source # 
StripeHasParam CreateInvoiceItem Description Source # 
StripeHasParam CreateInvoiceItem MetaData Source # 
StripeHasParam CreateInvoiceItem InvoiceId Source # 
StripeHasParam CreateInvoiceItem SubscriptionId Source # 
StripeHasParam UpdateInvoice Description Source # 
StripeHasParam UpdateInvoice MetaData Source # 
StripeHasParam UpdateInvoice ApplicationFeeId Source # 
StripeHasParam UpdateInvoice Forgiven Source # 
StripeHasParam UpdateInvoice Closed Source # 
StripeHasParam UpdateInvoice StatementDescription Source # 
StripeHasParam GetUpcomingInvoice SubscriptionId Source # 
StripeHasParam GetInvoiceLineItems Limit Source # 
StripeHasParam GetInvoiceLineItems SubscriptionId Source # 
StripeHasParam GetInvoiceLineItems CustomerId Source # 
StripeHasParam GetInvoices ExpandParams Source # 
StripeHasParam GetInvoices Limit Source # 
StripeHasParam GetInvoice ExpandParams Source # 
StripeHasParam CreateInvoice Description Source # 
StripeHasParam CreateInvoice MetaData Source # 
StripeHasParam CreateInvoice ApplicationFeeId Source # 
StripeHasParam CreateInvoice SubscriptionId Source # 
StripeHasParam CreateInvoice StatementDescription Source # 
StripeHasParam GetEvents Limit Source # 
StripeHasParam GetEvents Created Source # 
StripeHasParam UpdateDispute MetaData Source # 
StripeHasParam UpdateDispute Evidence Source # 
StripeHasParam GetCustomers ExpandParams Source # 
StripeHasParam GetCustomers Limit Source # 
StripeHasParam GetCustomers Created Source # 
StripeHasParam UpdateCustomer Email Source # 
StripeHasParam UpdateCustomer Description Source # 
StripeHasParam UpdateCustomer MetaData Source # 
StripeHasParam UpdateCustomer TokenId Source # 
StripeHasParam UpdateCustomer CouponId Source # 
StripeHasParam UpdateCustomer DefaultCard Source # 
StripeHasParam UpdateCustomer NewCard Source # 
StripeHasParam UpdateCustomer AccountBalance Source # 
StripeHasParam GetCustomer ExpandParams Source # 
StripeHasParam CreateCustomer Email Source # 
StripeHasParam CreateCustomer Quantity Source # 
StripeHasParam CreateCustomer Description Source # 
StripeHasParam CreateCustomer MetaData Source # 
StripeHasParam CreateCustomer TokenId Source # 
StripeHasParam CreateCustomer CouponId Source # 
StripeHasParam CreateCustomer TrialEnd Source # 
StripeHasParam CreateCustomer PlanId Source # 
StripeHasParam CreateCustomer NewCard Source # 
StripeHasParam CreateCustomer AccountBalance Source # 
StripeHasParam GetCoupons Limit Source # 
StripeHasParam UpdateCoupon MetaData Source # 
StripeHasParam CreateCoupon Currency Source # 
StripeHasParam CreateCoupon MetaData Source # 
StripeHasParam CreateCoupon DurationInMonths Source # 
StripeHasParam CreateCoupon RedeemBy Source # 
StripeHasParam CreateCoupon PercentOff Source # 
StripeHasParam CreateCoupon MaxRedemptions Source # 
StripeHasParam CreateCoupon AmountOff Source # 
StripeHasParam GetCharges ExpandParams Source # 
StripeHasParam GetCharges Limit Source # 
StripeHasParam GetCharges CustomerId Source # 
StripeHasParam GetCharges Created Source # 
StripeHasParam CaptureCharge ReceiptEmail Source # 
StripeHasParam CaptureCharge Amount Source # 
StripeHasParam UpdateCharge Description Source # 
StripeHasParam UpdateCharge MetaData Source # 
StripeHasParam GetCharge ExpandParams Source # 
StripeHasParam CreateCharge ReceiptEmail Source # 
StripeHasParam CreateCharge Description Source # 
StripeHasParam CreateCharge ExpandParams Source # 
StripeHasParam CreateCharge MetaData Source # 
StripeHasParam CreateCharge TokenId Source # 
StripeHasParam CreateCharge ApplicationFeeAmount Source # 
StripeHasParam CreateCharge NewCard Source # 
StripeHasParam CreateCharge CustomerId Source # 
StripeHasParam CreateCharge Capture Source # 
StripeHasParam CreateCharge StatementDescription Source # 
StripeHasParam GetRecipientCards ExpandParams Source # 
StripeHasParam GetRecipientCards Limit Source # 
StripeHasParam GetCustomerCards ExpandParams Source # 
StripeHasParam GetCustomerCards Limit Source # 
StripeHasParam UpdateRecipientCard Name Source # 
StripeHasParam UpdateRecipientCard AddressZip Source # 
StripeHasParam UpdateRecipientCard AddressState Source # 
StripeHasParam UpdateRecipientCard AddressLine2 Source # 
StripeHasParam UpdateRecipientCard AddressLine1 Source # 
StripeHasParam UpdateRecipientCard AddressCountry Source # 
StripeHasParam UpdateRecipientCard AddressCity Source # 
StripeHasParam UpdateRecipientCard ExpYear Source # 
StripeHasParam UpdateRecipientCard ExpMonth Source # 
StripeHasParam UpdateCustomerCard Name Source # 
StripeHasParam UpdateCustomerCard AddressZip Source # 
StripeHasParam UpdateCustomerCard AddressState Source # 
StripeHasParam UpdateCustomerCard AddressLine2 Source # 
StripeHasParam UpdateCustomerCard AddressLine1 Source # 
StripeHasParam UpdateCustomerCard AddressCountry Source # 
StripeHasParam UpdateCustomerCard AddressCity Source # 
StripeHasParam UpdateCustomerCard ExpYear Source # 
StripeHasParam UpdateCustomerCard ExpMonth Source # 
StripeHasParam GetRecipientCard ExpandParams Source # 
StripeHasParam GetCustomerCard ExpandParams Source # 
StripeHasParam GetBalanceTransactionHistory Currency Source # 
StripeHasParam GetBalanceTransactionHistory Limit Source # 
StripeHasParam GetBalanceTransactionHistory TransactionType Source # 
StripeHasParam GetBalanceTransactionHistory TransferId Source # 
StripeHasParam GetBalanceTransactionHistory Created Source # 
StripeHasParam GetBalanceTransactionHistory AvailableOn Source # 
StripeHasParam GetBalanceTransaction ExpandParams Source # 
StripeHasParam GetApplicationFeeRefunds ExpandParams Source # 
StripeHasParam GetApplicationFeeRefunds Limit Source # 
StripeHasParam UpdateApplicationFeeRefund MetaData Source # 
StripeHasParam GetApplicationFeeRefund ExpandParams Source # 
StripeHasParam CreateApplicationFeeRefund MetaData Source # 
StripeHasParam CreateApplicationFeeRefund Amount Source # 
StripeHasParam GetApplicationFees ExpandParams Source # 
StripeHasParam GetApplicationFees Limit Source # 
StripeHasParam GetApplicationFees ChargeId Source # 
StripeHasParam GetApplicationFees Created Source # 
StripeHasParam GetApplicationFee ExpandParams Source # 
StripeHasParam GetSubscriptions (EndingBefore SubscriptionId) Source # 
StripeHasParam GetSubscriptions (StartingAfter SubscriptionId) Source # 
StripeHasParam GetTransfers (EndingBefore TransferId) Source # 
StripeHasParam GetTransfers (StartingAfter TransferId) Source # 
StripeHasParam GetRefunds (EndingBefore RefundId) Source # 
StripeHasParam GetRefunds (StartingAfter RefundId) Source # 
StripeHasParam GetRecipients (EndingBefore RecipientId) Source # 
StripeHasParam GetRecipients (StartingAfter RecipientId) Source # 
StripeHasParam GetPlans (EndingBefore PlanId) Source # 
StripeHasParam GetPlans (StartingAfter PlanId) Source # 
StripeHasParam GetInvoiceItems (EndingBefore InvoiceItemId) Source # 
StripeHasParam GetInvoiceItems (StartingAfter InvoiceItemId) Source # 
StripeHasParam GetInvoiceLineItems (EndingBefore InvoiceLineItemId) Source # 
StripeHasParam GetInvoiceLineItems (StartingAfter InvoiceLineItemId) Source # 
StripeHasParam GetInvoices (EndingBefore InvoiceId) Source # 
StripeHasParam GetInvoices (StartingAfter InvoiceId) Source # 
StripeHasParam GetEvents (EndingBefore EventId) Source # 
StripeHasParam GetEvents (StartingAfter EventId) Source # 
StripeHasParam GetCustomers (EndingBefore CustomerId) Source # 
StripeHasParam GetCustomers (StartingAfter CustomerId) Source # 
StripeHasParam GetCoupons (EndingBefore CouponId) Source # 
StripeHasParam GetCoupons (StartingAfter CouponId) Source # 
StripeHasParam GetCharges (EndingBefore ChargeId) Source # 
StripeHasParam GetCharges (StartingAfter ChargeId) Source # 
StripeHasParam GetRecipientCards (EndingBefore CardId) Source # 
StripeHasParam GetRecipientCards (StartingAfter CardId) Source # 
StripeHasParam GetCustomerCards (EndingBefore CardId) Source # 
StripeHasParam GetCustomerCards (StartingAfter CardId) Source # 
StripeHasParam GetBalanceTransactionHistory (EndingBefore TransactionId) Source # 
StripeHasParam GetBalanceTransactionHistory (StartingAfter TransactionId) Source # 
ToStripeParam a => StripeHasParam GetBalanceTransactionHistory (Source a) Source # 
StripeHasParam GetBalanceTransactionHistory (TimeRange Created) Source # 
StripeHasParam GetBalanceTransactionHistory (TimeRange AvailableOn) Source # 
StripeHasParam GetApplicationFeeRefunds (EndingBefore RefundId) Source # 
StripeHasParam GetApplicationFeeRefunds (StartingAfter RefundId) Source # 
StripeHasParam GetApplicationFees (EndingBefore ApplicationFeeId) Source # 
StripeHasParam GetApplicationFees (StartingAfter ApplicationFeeId) Source # 

class ToStripeParam param where Source #

convert a parameter to a key/value

Minimal complete definition

toStripeParam

Instances

ToStripeParam Currency Source # 
ToStripeParam ReceiptEmail Source # 
ToStripeParam Email Source # 
ToStripeParam AtPeriodEnd Source # 
ToStripeParam Prorate Source # 
ToStripeParam Quantity Source # 
ToStripeParam Description Source # 
ToStripeParam PlanName Source # 
ToStripeParam Name Source # 
ToStripeParam ExpandParams Source # 
ToStripeParam MetaData Source # 
ToStripeParam Limit Source # 
ToStripeParam TokenId Source # 
ToStripeParam EventId Source # 
ToStripeParam TransactionType Source # 
ToStripeParam TransactionId Source # 
ToStripeParam ApplicationFeeAmount Source # 
ToStripeParam ApplicationFeePercent Source # 
ToStripeParam ApplicationFeeId Source # 
ToStripeParam RecipientType Source # 
ToStripeParam TaxID Source # 
ToStripeParam RecipientId Source # 
ToStripeParam NewBankAccount Source # 
ToStripeParam BankAccountId Source # 
ToStripeParam TransferStatus Source # 
ToStripeParam TransferId Source # 
ToStripeParam Evidence Source # 
ToStripeParam Forgiven Source # 
ToStripeParam Closed Source # 
ToStripeParam InvoiceLineItemId Source # 
ToStripeParam InvoiceItemId Source # 
ToStripeParam InvoiceId Source # 
ToStripeParam Amount Source # 
ToStripeParam TrialPeriodDays Source # 
ToStripeParam IntervalCount Source # 
ToStripeParam DurationInMonths Source # 
ToStripeParam RedeemBy Source # 
ToStripeParam PercentOff Source # 
ToStripeParam MaxRedemptions Source # 
ToStripeParam AmountOff Source # 
ToStripeParam CouponId Source # 
ToStripeParam Duration Source # 
ToStripeParam Interval Source # 
ToStripeParam TrialEnd Source # 
ToStripeParam PlanId Source # 
ToStripeParam TaxPercent Source # 
ToStripeParam SubscriptionId Source # 
ToStripeParam DefaultCard Source # 
ToStripeParam NewCard Source # 
ToStripeParam IsVerified Source # 
ToStripeParam AddressZip Source # 
ToStripeParam AddressState Source # 
ToStripeParam AddressLine2 Source # 
ToStripeParam AddressLine1 Source # 
ToStripeParam AddressCountry Source # 
ToStripeParam AddressCity Source # 
ToStripeParam CVC Source # 
ToStripeParam ExpYear Source # 
ToStripeParam ExpMonth Source # 
ToStripeParam CardNumber Source # 
ToStripeParam CardId Source # 
ToStripeParam AccountBalance Source # 
ToStripeParam CustomerId Source # 
ToStripeParam RefundReason Source # 
ToStripeParam RefundApplicationFee Source # 
ToStripeParam RefundId Source # 
ToStripeParam Capture Source # 
ToStripeParam StatementDescription Source # 
ToStripeParam ChargeId Source # 
ToStripeParam Date Source # 
ToStripeParam Created Source # 
ToStripeParam AvailableOn Source # 
ToStripeParam param => ToStripeParam (EndingBefore param) Source # 
ToStripeParam param => ToStripeParam (StartingAfter param) Source # 
ToStripeParam a => ToStripeParam (Source a) Source # 
ToStripeParam a => ToStripeParam (TimeRange a) Source # 
ToStripeParam (Param Text Text) Source # 

(-&-) :: StripeHasParam request param => StripeRequest request -> param -> StripeRequest request Source #

add an optional parameter to a StripeRequest

mkStripeRequest :: Method -> Text -> Params -> StripeRequest a Source #

HTTP Params

helper function for building a StripeRequest