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.ApplicationFee

Contents

Description

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

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

main :: IO ()
main = do
  let config = StripeConfig (StripeKey "secret_key")
  result <- stripe config $ getApplicationFee (FeeId "fee_4xtEGZhPNDEt3w")
  case result of
    Right applicationFee -> print applicationFee
    Left stripeError     -> print stripeError

Synopsis

API

getApplicationFee Source #

Arguments

:: FeeId

The FeeId associated with the Application

-> StripeRequest GetApplicationFee 

ApplicationFee retrieval

Types

newtype ApplicationId Source #

Constructors

ApplicationId Text 

Instances

Eq ApplicationId Source # 
Data ApplicationId Source # 

Methods

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

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

toConstr :: ApplicationId -> Constr #

dataTypeOf :: ApplicationId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ApplicationId Source # 
Read ApplicationId Source # 
Show ApplicationId 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

newtype ApplicationFeeId Source #

PlanId for a Plan

Constructors

ApplicationFeeId Text 

Instances

Eq ApplicationFeeId Source # 
Data ApplicationFeeId Source # 

Methods

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

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

toConstr :: ApplicationFeeId -> Constr #

dataTypeOf :: ApplicationFeeId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ApplicationFeeId Source # 
Read ApplicationFeeId Source # 
Show ApplicationFeeId Source # 
ToStripeParam ApplicationFeeId Source # 
StripeHasParam UpdateInvoice ApplicationFeeId Source # 
StripeHasParam CreateInvoice ApplicationFeeId Source # 
StripeHasParam GetApplicationFees (EndingBefore ApplicationFeeId) Source # 
StripeHasParam GetApplicationFees (StartingAfter ApplicationFeeId) Source # 

newtype ChargeId Source #

ChargeId associated with a Charge

Constructors

ChargeId Text 

Instances

Eq ChargeId Source # 
Data ChargeId Source # 

Methods

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

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

toConstr :: ChargeId -> Constr #

dataTypeOf :: ChargeId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ChargeId Source # 
Read ChargeId Source # 
Show ChargeId Source # 
FromJSON ChargeId Source #

JSON Instance for ChargeId

ToStripeParam ChargeId Source # 
StripeHasParam GetApplicationFees ChargeId Source # 
StripeHasParam GetCharges (EndingBefore ChargeId) Source # 
StripeHasParam GetCharges (StartingAfter ChargeId) Source # 
type ExpandsTo ChargeId Source # 

data ConnectApp Source #

Connect Application

Instances

Eq ConnectApp Source # 
Data ConnectApp Source # 

Methods

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

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

toConstr :: ConnectApp -> Constr #

dataTypeOf :: ConnectApp -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ConnectApp Source # 
Read ConnectApp Source # 
Show ConnectApp Source # 
FromJSON ConnectApp Source #

Connect Application JSON instance

newtype Created Source #

Constructors

Created UTCTime 

Instances

Eq Created Source # 

Methods

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

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

Data Created Source # 

Methods

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

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

toConstr :: Created -> Constr #

dataTypeOf :: Created -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Created Source # 
Read Created Source # 
Show Created Source # 
ToStripeParam Created Source # 
StripeHasParam GetTransfers Created Source # 
StripeHasParam GetInvoiceItems Created Source # 
StripeHasParam GetEvents Created Source # 
StripeHasParam GetCustomers Created Source # 
StripeHasParam GetCharges Created Source # 
StripeHasParam GetBalanceTransactionHistory Created Source # 
StripeHasParam GetApplicationFees Created Source # 
StripeHasParam GetBalanceTransactionHistory (TimeRange Created) Source # 

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

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