stripe-core-2.3.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 # 

Methods

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

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

Data FeeId Source # 

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 # 

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 # 
Show FeeId Source # 

Methods

showsPrec :: Int -> FeeId -> ShowS #

show :: FeeId -> String #

showList :: [FeeId] -> ShowS #

newtype RefundId Source #

Constructors

RefundId Text 

Instances

Eq RefundId Source # 
Data RefundId Source # 

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 # 
Read RefundId Source # 
Show RefundId Source # 
ToStripeParam RefundId Source # 
StripeHasParam GetRefunds (EndingBefore RefundId) Source # 
StripeHasParam GetRefunds (StartingAfter RefundId) Source # 
StripeHasParam GetApplicationFeeRefunds (EndingBefore RefundId) Source # 
StripeHasParam GetApplicationFeeRefunds (StartingAfter RefundId) Source # 

data ApplicationFee Source #

ApplicationFee Object

Instances

Eq ApplicationFee Source # 
Data ApplicationFee Source # 

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 # 
Read ApplicationFee Source # 
Show ApplicationFee Source # 
FromJSON ApplicationFee Source #

JSON Instance for ApplicationFee

data ApplicationFeeRefund Source #

Application Fee Refunds

Instances

Eq ApplicationFeeRefund Source # 
Data ApplicationFeeRefund Source # 

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 # 
Read ApplicationFeeRefund Source # 
Show ApplicationFeeRefund Source # 
FromJSON ApplicationFeeRefund Source #

JSON Instance for ApplicationFeeRefund

data StripeList a Source #

Generic handling of Stripe JSON arrays

Constructors

StripeList 

Fields

Instances

Eq a => Eq (StripeList a) Source # 

Methods

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

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

Data a => Data (StripeList a) Source # 

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 # 
Read a => Read (StripeList a) Source # 
Show a => Show (StripeList a) Source # 
FromJSON a => FromJSON (StripeList a) Source #

JSON Instance for StripeList

newtype EndingBefore a Source #

Pagination Option for StripeList

Constructors

EndingBefore a 

Instances

StripeHasParam GetTransfers (EndingBefore TransferId) Source # 
StripeHasParam GetSubscriptionsByCustomerId (EndingBefore SubscriptionId) Source # 
StripeHasParam GetSubscriptions (EndingBefore SubscriptionId) Source # 
StripeHasParam GetRefunds (EndingBefore RefundId) Source # 
StripeHasParam GetRecipients (EndingBefore RecipientId) Source # 
StripeHasParam GetPlans (EndingBefore PlanId) Source # 
StripeHasParam GetInvoiceItems (EndingBefore InvoiceItemId) Source # 
StripeHasParam GetInvoiceLineItems (EndingBefore InvoiceLineItemId) Source # 
StripeHasParam GetInvoices (EndingBefore InvoiceId) Source # 
StripeHasParam GetEvents (EndingBefore EventId) Source # 
StripeHasParam GetCustomers (EndingBefore CustomerId) Source # 
StripeHasParam GetCoupons (EndingBefore CouponId) Source # 
StripeHasParam GetCharges (EndingBefore ChargeId) Source # 
StripeHasParam GetRecipientCards (EndingBefore CardId) Source # 
StripeHasParam GetCustomerCards (EndingBefore CardId) Source # 
StripeHasParam GetBalanceTransactionHistory (EndingBefore TransactionId) Source # 
StripeHasParam GetApplicationFeeRefunds (EndingBefore RefundId) Source # 
StripeHasParam GetApplicationFees (EndingBefore ApplicationFeeId) Source # 
Eq a => Eq (EndingBefore a) Source # 
Data a => Data (EndingBefore a) Source # 

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 # 
Read a => Read (EndingBefore a) Source # 
Show a => Show (EndingBefore a) Source # 
ToStripeParam param => ToStripeParam (EndingBefore param) Source # 

newtype StartingAfter a Source #

Pagination Option for StripeList

Constructors

StartingAfter a 

Instances

StripeHasParam GetTransfers (StartingAfter TransferId) Source # 
StripeHasParam GetSubscriptionsByCustomerId (StartingAfter SubscriptionId) Source # 
StripeHasParam GetSubscriptions (StartingAfter SubscriptionId) Source # 
StripeHasParam GetRefunds (StartingAfter RefundId) Source # 
StripeHasParam GetRecipients (StartingAfter RecipientId) Source # 
StripeHasParam GetPlans (StartingAfter PlanId) Source # 
StripeHasParam GetInvoiceItems (StartingAfter InvoiceItemId) Source # 
StripeHasParam GetInvoiceLineItems (StartingAfter InvoiceLineItemId) Source # 
StripeHasParam GetInvoices (StartingAfter InvoiceId) Source # 
StripeHasParam GetEvents (StartingAfter EventId) Source # 
StripeHasParam GetCustomers (StartingAfter CustomerId) Source # 
StripeHasParam GetCoupons (StartingAfter CouponId) Source # 
StripeHasParam GetCharges (StartingAfter ChargeId) Source # 
StripeHasParam GetRecipientCards (StartingAfter CardId) Source # 
StripeHasParam GetCustomerCards (StartingAfter CardId) Source # 
StripeHasParam GetBalanceTransactionHistory (StartingAfter TransactionId) Source # 
StripeHasParam GetApplicationFeeRefunds (StartingAfter RefundId) Source # 
StripeHasParam GetApplicationFees (StartingAfter ApplicationFeeId) Source # 
Eq a => Eq (StartingAfter a) Source # 
Data a => Data (StartingAfter a) Source # 

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 # 
Read a => Read (StartingAfter a) Source # 
Show a => Show (StartingAfter a) Source # 
ToStripeParam param => ToStripeParam (StartingAfter param) Source # 

newtype Limit Source #

Pagination Option for StripeList

Constructors

Limit Int 

Instances

Eq Limit Source # 

Methods

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

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

Data Limit Source # 

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 # 

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 # 
Show Limit Source # 

Methods

showsPrec :: Int -> Limit -> ShowS #

show :: Limit -> String #

showList :: [Limit] -> ShowS #

ToStripeParam Limit Source # 
StripeHasParam GetTransfers Limit Source # 
StripeHasParam GetSubscriptionsByCustomerId Limit Source # 
StripeHasParam GetSubscriptions Limit Source # 
StripeHasParam GetRefunds Limit Source # 
StripeHasParam GetRecipients Limit Source # 
StripeHasParam GetPlans Limit Source # 
StripeHasParam GetInvoiceItems Limit Source # 
StripeHasParam GetInvoiceLineItems Limit Source # 
StripeHasParam GetInvoices Limit Source # 
StripeHasParam GetEvents Limit Source # 
StripeHasParam GetCustomers Limit Source # 
StripeHasParam GetCoupons Limit Source # 
StripeHasParam GetCharges Limit Source # 
StripeHasParam GetRecipientCards Limit Source # 
StripeHasParam GetCustomerCards Limit Source # 
StripeHasParam GetBalanceTransactionHistory Limit Source # 
StripeHasParam GetApplicationFeeRefunds Limit Source # 
StripeHasParam GetApplicationFees Limit Source # 

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 GetTransfers ExpandParams Source # 
StripeHasParam GetTransfer ExpandParams Source # 
StripeHasParam GetSubscriptionsByCustomerId ExpandParams Source # 
StripeHasParam GetSubscriptions ExpandParams Source # 
StripeHasParam GetSubscription 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 MetaData Source #

Type of MetaData for use on Stripe objects

Constructors

MetaData [(Text, Text)] 

Instances

Eq MetaData Source # 
Data MetaData Source # 

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 # 
Read MetaData Source # 
Show MetaData Source # 
FromJSON MetaData Source # 
ToStripeParam MetaData Source # 
StripeHasParam UpdateTransfer MetaData Source # 
StripeHasParam CreateTransfer MetaData Source # 
StripeHasParam UpdateSubscription MetaData Source # 
StripeHasParam CreateSubscription MetaData Source # 
StripeHasParam UpdateRefund MetaData Source # 
StripeHasParam CreateRefund MetaData Source # 
StripeHasParam UpdateRecipient MetaData Source # 
StripeHasParam CreateRecipient MetaData Source # 
StripeHasParam UpdatePlan MetaData Source # 
StripeHasParam CreatePlan MetaData Source # 
StripeHasParam UpdateInvoiceItem MetaData Source # 
StripeHasParam CreateInvoiceItem MetaData Source # 
StripeHasParam UpdateInvoice MetaData Source # 
StripeHasParam CreateInvoice MetaData Source # 
StripeHasParam UpdateDispute MetaData Source # 
StripeHasParam UpdateCustomer MetaData Source # 
StripeHasParam CreateCustomer MetaData Source # 
StripeHasParam UpdateCoupon MetaData Source # 
StripeHasParam CreateCoupon MetaData Source # 
StripeHasParam UpdateCharge MetaData Source # 
StripeHasParam CreateCharge MetaData Source # 
StripeHasParam UpdateApplicationFeeRefund MetaData Source # 
StripeHasParam CreateApplicationFeeRefund MetaData Source # 

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 # 

Methods

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

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

Data Amount Source # 

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 # 
Read Amount Source # 
Show Amount Source # 
ToStripeParam Amount Source # 
StripeHasParam CreateRefund Amount Source # 
StripeHasParam UpdateInvoiceItem Amount Source # 
StripeHasParam CaptureCharge Amount Source # 
StripeHasParam CreateApplicationFeeRefund Amount Source #