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

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

Web.Stripe.ApplicationFeeRefund

Contents

Description

https://stripe.com/docs/api#fee_refunds

{-# LANGUAGE OverloadedStrings #-}
import Web.Stripe
import Web.Stripe.ApplicationFeeRefund

main :: IO ()
main = do
  let config = StripeConfig (StripeKey "secret_key")
  result <- stripe config $ getApplicationFeeRefund (FeeId "fee_id") (RefundId "refund_id")
  case result of
    Right applicationFeeRefund -> print applicationFeeRefund
    Left stripeError           -> print stripeError
Synopsis

API

getApplicationFeeRefund Source #

Arguments

:: FeeId

The FeeID associated with the ApplicationFee

-> RefundId

The ReufndId associated with the ApplicationFeeRefund

-> StripeRequest GetApplicationFeeRefund 

Retrieve an existing ApplicationFeeRefund

updateApplicationFeeRefund Source #

Arguments

:: FeeId

The FeeID associated with the application

-> RefundId

The RefundId associated with the application

-> StripeRequest UpdateApplicationFeeRefund 

Update an ApplicationFeeRefund for a given Application FeeId and RefundId

getApplicationFeeRefunds Source #

Arguments

:: FeeId

The FeeID associated with the application

-> StripeRequest GetApplicationFeeRefunds 

Retrieve a list of all ApplicationFeeRefunds for a given Application FeeId

Types

newtype FeeId Source #

FeeId for objects with Fees

Constructors

FeeId Text 
Instances
Eq FeeId Source # 
Instance details

Defined in Web.Stripe.Types

Methods

(==) :: FeeId -> FeeId -> Bool #

(/=) :: FeeId -> FeeId -> Bool #

Data FeeId Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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 #

toConstr :: FeeId -> Constr #

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 # 
Instance details

Defined in Web.Stripe.Types

Methods

compare :: FeeId -> FeeId -> Ordering #

(<) :: FeeId -> FeeId -> Bool #

(<=) :: FeeId -> FeeId -> Bool #

(>) :: FeeId -> FeeId -> Bool #

(>=) :: FeeId -> FeeId -> Bool #

max :: FeeId -> FeeId -> FeeId #

min :: FeeId -> FeeId -> FeeId #

Read FeeId Source # 
Instance details

Defined in Web.Stripe.Types

Show FeeId Source # 
Instance details

Defined in Web.Stripe.Types

Methods

showsPrec :: Int -> FeeId -> ShowS #

show :: FeeId -> String #

showList :: [FeeId] -> ShowS #

newtype RefundId Source #

Constructors

RefundId Text 
Instances
Eq RefundId Source # 
Instance details

Defined in Web.Stripe.Types

Data RefundId Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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

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

toConstr :: RefundId -> Constr #

dataTypeOf :: RefundId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RefundId Source # 
Instance details

Defined in Web.Stripe.Types

Read RefundId Source # 
Instance details

Defined in Web.Stripe.Types

Show RefundId Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam RefundId Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam GetRefunds (EndingBefore RefundId) Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam GetRefunds (StartingAfter RefundId) Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam GetApplicationFeeRefunds (EndingBefore RefundId) Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund

StripeHasParam GetApplicationFeeRefunds (StartingAfter RefundId) Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund

data ApplicationFee Source #

ApplicationFee Object

Instances
Eq ApplicationFee Source # 
Instance details

Defined in Web.Stripe.Types

Data ApplicationFee Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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

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

toConstr :: ApplicationFee -> Constr #

dataTypeOf :: ApplicationFee -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ApplicationFee Source # 
Instance details

Defined in Web.Stripe.Types

Read ApplicationFee Source # 
Instance details

Defined in Web.Stripe.Types

Show ApplicationFee Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON ApplicationFee Source #

JSON Instance for ApplicationFee

Instance details

Defined in Web.Stripe.Types

data ApplicationFeeRefund Source #

Application Fee Refunds

Instances
Eq ApplicationFeeRefund Source # 
Instance details

Defined in Web.Stripe.Types

Data ApplicationFeeRefund Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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

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

toConstr :: ApplicationFeeRefund -> Constr #

dataTypeOf :: ApplicationFeeRefund -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ApplicationFeeRefund Source # 
Instance details

Defined in Web.Stripe.Types

Read ApplicationFeeRefund Source # 
Instance details

Defined in Web.Stripe.Types

Show ApplicationFeeRefund Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON ApplicationFeeRefund Source #

JSON Instance for ApplicationFeeRefund

Instance details

Defined in Web.Stripe.Types

data StripeList a Source #

Generic handling of Stripe JSON arrays

Constructors

StripeList 

Fields

Instances
Eq a => Eq (StripeList a) Source # 
Instance details

Defined in Web.Stripe.Types

Methods

(==) :: StripeList a -> StripeList a -> Bool #

(/=) :: StripeList a -> StripeList a -> Bool #

Data a => Data (StripeList a) Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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

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

toConstr :: StripeList a -> Constr #

dataTypeOf :: StripeList a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (StripeList a) Source # 
Instance details

Defined in Web.Stripe.Types

Read a => Read (StripeList a) Source # 
Instance details

Defined in Web.Stripe.Types

Show a => Show (StripeList a) Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON a => FromJSON (StripeList a) Source #

JSON Instance for StripeList

Instance details

Defined in Web.Stripe.Types

newtype EndingBefore a Source #

Pagination Option for StripeList

Constructors

EndingBefore a 
Instances
StripeHasParam GetTransfers (EndingBefore TransferId) Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam GetSubscriptionsByCustomerId (EndingBefore SubscriptionId) Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam GetSubscriptions (EndingBefore SubscriptionId) Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam GetRefunds (EndingBefore RefundId) Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam GetRecipients (EndingBefore RecipientId) Source # 
Instance details

Defined in Web.Stripe.Recipient

StripeHasParam GetPlans (EndingBefore PlanId) Source # 
Instance details

Defined in Web.Stripe.Plan

StripeHasParam GetInvoiceItems (EndingBefore InvoiceItemId) Source # 
Instance details

Defined in Web.Stripe.InvoiceItem

StripeHasParam GetInvoiceLineItems (EndingBefore InvoiceLineItemId) Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam GetInvoices (EndingBefore InvoiceId) Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam GetEvents (EndingBefore EventId) Source # 
Instance details

Defined in Web.Stripe.Event

StripeHasParam GetCustomers (EndingBefore CustomerId) Source # 
Instance details

Defined in Web.Stripe.Customer

StripeHasParam GetCoupons (EndingBefore CouponId) Source # 
Instance details

Defined in Web.Stripe.Coupon

StripeHasParam GetCharges (EndingBefore ChargeId) Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam GetRecipientCards (EndingBefore CardId) Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetCustomerCards (EndingBefore CardId) Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetBalanceTransactionHistory (EndingBefore TransactionId) Source # 
Instance details

Defined in Web.Stripe.Balance

StripeHasParam GetApplicationFeeRefunds (EndingBefore RefundId) Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund

StripeHasParam GetApplicationFees (EndingBefore ApplicationFeeId) Source # 
Instance details

Defined in Web.Stripe.ApplicationFee

Eq a => Eq (EndingBefore a) Source # 
Instance details

Defined in Web.Stripe.Types

Data a => Data (EndingBefore a) Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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

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

toConstr :: EndingBefore a -> Constr #

dataTypeOf :: EndingBefore a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (EndingBefore a) Source # 
Instance details

Defined in Web.Stripe.Types

Read a => Read (EndingBefore a) Source # 
Instance details

Defined in Web.Stripe.Types

Show a => Show (EndingBefore a) Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam param => ToStripeParam (EndingBefore param) Source # 
Instance details

Defined in Web.Stripe.StripeRequest

newtype StartingAfter a Source #

Pagination Option for StripeList

Constructors

StartingAfter a 
Instances
StripeHasParam GetTransfers (StartingAfter TransferId) Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam GetSubscriptionsByCustomerId (StartingAfter SubscriptionId) Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam GetSubscriptions (StartingAfter SubscriptionId) Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam GetRefunds (StartingAfter RefundId) Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam GetRecipients (StartingAfter RecipientId) Source # 
Instance details

Defined in Web.Stripe.Recipient

StripeHasParam GetPlans (StartingAfter PlanId) Source # 
Instance details

Defined in Web.Stripe.Plan

StripeHasParam GetInvoiceItems (StartingAfter InvoiceItemId) Source # 
Instance details

Defined in Web.Stripe.InvoiceItem

StripeHasParam GetInvoiceLineItems (StartingAfter InvoiceLineItemId) Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam GetInvoices (StartingAfter InvoiceId) Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam GetEvents (StartingAfter EventId) Source # 
Instance details

Defined in Web.Stripe.Event

StripeHasParam GetCustomers (StartingAfter CustomerId) Source # 
Instance details

Defined in Web.Stripe.Customer

StripeHasParam GetCoupons (StartingAfter CouponId) Source # 
Instance details

Defined in Web.Stripe.Coupon

StripeHasParam GetCharges (StartingAfter ChargeId) Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam GetRecipientCards (StartingAfter CardId) Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetCustomerCards (StartingAfter CardId) Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetBalanceTransactionHistory (StartingAfter TransactionId) Source # 
Instance details

Defined in Web.Stripe.Balance

StripeHasParam GetApplicationFeeRefunds (StartingAfter RefundId) Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund

StripeHasParam GetApplicationFees (StartingAfter ApplicationFeeId) Source # 
Instance details

Defined in Web.Stripe.ApplicationFee

Eq a => Eq (StartingAfter a) Source # 
Instance details

Defined in Web.Stripe.Types

Data a => Data (StartingAfter a) Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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

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

toConstr :: StartingAfter a -> Constr #

dataTypeOf :: StartingAfter a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (StartingAfter a) Source # 
Instance details

Defined in Web.Stripe.Types

Read a => Read (StartingAfter a) Source # 
Instance details

Defined in Web.Stripe.Types

Show a => Show (StartingAfter a) Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam param => ToStripeParam (StartingAfter param) Source # 
Instance details

Defined in Web.Stripe.StripeRequest

newtype Limit Source #

Pagination Option for StripeList

Constructors

Limit Int 
Instances
Eq Limit Source # 
Instance details

Defined in Web.Stripe.Types

Methods

(==) :: Limit -> Limit -> Bool #

(/=) :: Limit -> Limit -> Bool #

Data Limit Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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

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

toConstr :: Limit -> Constr #

dataTypeOf :: Limit -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Limit Source # 
Instance details

Defined in Web.Stripe.Types

Methods

compare :: Limit -> Limit -> Ordering #

(<) :: Limit -> Limit -> Bool #

(<=) :: Limit -> Limit -> Bool #

(>) :: Limit -> Limit -> Bool #

(>=) :: Limit -> Limit -> Bool #

max :: Limit -> Limit -> Limit #

min :: Limit -> Limit -> Limit #

Read Limit Source # 
Instance details

Defined in Web.Stripe.Types

Show Limit Source # 
Instance details

Defined in Web.Stripe.Types

Methods

showsPrec :: Int -> Limit -> ShowS #

show :: Limit -> String #

showList :: [Limit] -> ShowS #

ToStripeParam Limit Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam GetTransfers Limit Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam GetSubscriptionsByCustomerId Limit Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam GetSubscriptions Limit Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam GetRefunds Limit Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam GetRecipients Limit Source # 
Instance details

Defined in Web.Stripe.Recipient

StripeHasParam GetPlans Limit Source # 
Instance details

Defined in Web.Stripe.Plan

StripeHasParam GetInvoiceItems Limit Source # 
Instance details

Defined in Web.Stripe.InvoiceItem

StripeHasParam GetInvoiceLineItems Limit Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam GetInvoices Limit Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam GetEvents Limit Source # 
Instance details

Defined in Web.Stripe.Event

StripeHasParam GetCustomers Limit Source # 
Instance details

Defined in Web.Stripe.Customer

StripeHasParam GetCoupons Limit Source # 
Instance details

Defined in Web.Stripe.Coupon

StripeHasParam GetCharges Limit Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam GetRecipientCards Limit Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetCustomerCards Limit Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetBalanceTransactionHistory Limit Source # 
Instance details

Defined in Web.Stripe.Balance

StripeHasParam GetApplicationFeeRefunds Limit Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund

StripeHasParam GetApplicationFees Limit Source # 
Instance details

Defined in Web.Stripe.ApplicationFee

newtype ExpandParams Source #

Type of Expansion Parameters for use on Stripe objects

Constructors

ExpandParams 

Fields

Instances
Eq ExpandParams Source # 
Instance details

Defined in Web.Stripe.Types

Data ExpandParams Source # 
Instance details

Defined in Web.Stripe.Types

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 # 
Instance details

Defined in Web.Stripe.Types

Read ExpandParams Source # 
Instance details

Defined in Web.Stripe.Types

Show ExpandParams Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam ExpandParams Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam GetTransfers ExpandParams Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam GetTransfer ExpandParams Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam GetSubscriptionsByCustomerId ExpandParams Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam GetSubscriptions ExpandParams Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam GetSubscription ExpandParams Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam GetRefunds ExpandParams Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam GetRefund ExpandParams Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam GetRecipients ExpandParams Source # 
Instance details

Defined in Web.Stripe.Recipient

StripeHasParam GetRecipient ExpandParams Source # 
Instance details

Defined in Web.Stripe.Recipient

StripeHasParam GetInvoiceItems ExpandParams Source # 
Instance details

Defined in Web.Stripe.InvoiceItem

StripeHasParam GetInvoiceItem ExpandParams Source # 
Instance details

Defined in Web.Stripe.InvoiceItem

StripeHasParam GetInvoices ExpandParams Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam GetInvoice ExpandParams Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam GetCustomers ExpandParams Source # 
Instance details

Defined in Web.Stripe.Customer

StripeHasParam GetCustomer ExpandParams Source # 
Instance details

Defined in Web.Stripe.Customer

StripeHasParam GetCharges ExpandParams Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam GetCharge ExpandParams Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam CreateCharge ExpandParams Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam GetRecipientCards ExpandParams Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetCustomerCards ExpandParams Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetRecipientCard ExpandParams Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetCustomerCard ExpandParams Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetBalanceTransaction ExpandParams Source # 
Instance details

Defined in Web.Stripe.Balance

StripeHasParam GetApplicationFeeRefunds ExpandParams Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund

StripeHasParam GetApplicationFeeRefund ExpandParams Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund

StripeHasParam GetApplicationFees ExpandParams Source # 
Instance details

Defined in Web.Stripe.ApplicationFee

StripeHasParam GetApplicationFee ExpandParams Source # 
Instance details

Defined in Web.Stripe.ApplicationFee

newtype MetaData Source #

Type of MetaData for use on Stripe objects

Constructors

MetaData [(Text, Text)] 
Instances
Eq MetaData Source # 
Instance details

Defined in Web.Stripe.Types

Data MetaData Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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

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

toConstr :: MetaData -> Constr #

dataTypeOf :: MetaData -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MetaData Source # 
Instance details

Defined in Web.Stripe.Types

Read MetaData Source # 
Instance details

Defined in Web.Stripe.Types

Show MetaData Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON MetaData Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam MetaData Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam UpdateTransfer MetaData Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam CreateTransfer MetaData Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam UpdateSubscription MetaData Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam CreateSubscription MetaData Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam UpdateRefund MetaData Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam CreateRefund MetaData Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam UpdateRecipient MetaData Source # 
Instance details

Defined in Web.Stripe.Recipient

StripeHasParam CreateRecipient MetaData Source # 
Instance details

Defined in Web.Stripe.Recipient

StripeHasParam UpdatePlan MetaData Source # 
Instance details

Defined in Web.Stripe.Plan

StripeHasParam CreatePlan MetaData Source # 
Instance details

Defined in Web.Stripe.Plan

StripeHasParam UpdateInvoiceItem MetaData Source # 
Instance details

Defined in Web.Stripe.InvoiceItem

StripeHasParam CreateInvoiceItem MetaData Source # 
Instance details

Defined in Web.Stripe.InvoiceItem

StripeHasParam UpdateInvoice MetaData Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam CreateInvoice MetaData Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam UpdateDispute MetaData Source # 
Instance details

Defined in Web.Stripe.Dispute

StripeHasParam UpdateCustomer MetaData Source # 
Instance details

Defined in Web.Stripe.Customer

StripeHasParam CreateCustomer MetaData Source # 
Instance details

Defined in Web.Stripe.Customer

StripeHasParam UpdateCoupon MetaData Source # 
Instance details

Defined in Web.Stripe.Coupon

StripeHasParam CreateCoupon MetaData Source # 
Instance details

Defined in Web.Stripe.Coupon

StripeHasParam UpdateCharge MetaData Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam CreateCharge MetaData Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam UpdateApplicationFeeRefund MetaData Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund

StripeHasParam CreateApplicationFeeRefund MetaData Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund

newtype Amount Source #

Amount representing a monetary value. Stripe represents pennies as whole numbers i.e. 100 = $1

Constructors

Amount 

Fields

Instances
Eq Amount Source # 
Instance details

Defined in Web.Stripe.Types

Methods

(==) :: Amount -> Amount -> Bool #

(/=) :: Amount -> Amount -> Bool #

Data Amount Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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

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

toConstr :: Amount -> Constr #

dataTypeOf :: Amount -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Amount Source # 
Instance details

Defined in Web.Stripe.Types

Read Amount Source # 
Instance details

Defined in Web.Stripe.Types

Show Amount Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam Amount Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam CreateRefund Amount Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam UpdateInvoiceItem Amount Source # 
Instance details

Defined in Web.Stripe.InvoiceItem

StripeHasParam CaptureCharge Amount Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam CreateApplicationFeeRefund Amount Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund