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

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

Web.Stripe.Transfer

Contents

Description

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

{-# LANGUAGE OverloadedStrings #-}
import Web.Stripe
import Web.Stripe.Transfer
import Web.Stripe.Recipient

main :: IO ()
main = do
  let config = StripeConfig (StripeKey "secret_key")
  result <- stripe config $ getRecipient (RecipientId "recipient_id")
  case result of
    (Left stripeError) -> print stripeError
    (Right (Recipient { recipientId = recipientid })) -> do
      result <- stripe config $ createTransfer recipientid (Amount 100) USD
      case result of
       Left  stripeError -> print stripeError
       Right transfer    -> print transfer
Synopsis

API

createTransfer Source #

Arguments

:: RecipientId

The RecipientId of the Recipient who will receive the Transfer

-> Amount

The Amount of money to transfer to the Recipient

-> Currency

The Currency in which to perform the Transfer

-> StripeRequest CreateTransfer 

Create a Transfer

getTransfer Source #

Arguments

:: TransferId

TransferId associated with the Transfer to retrieve

-> StripeRequest GetTransfer 

Retrieve a Transfer

getTransfers :: StripeRequest GetTransfers Source #

Retrieve StripeList of Transfers

Types

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

newtype BankAccountId Source #

Constructors

BankAccountId Text 
Instances
Eq BankAccountId Source # 
Instance details

Defined in Web.Stripe.Types

Data BankAccountId 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) -> BankAccountId -> c BankAccountId #

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

toConstr :: BankAccountId -> Constr #

dataTypeOf :: BankAccountId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BankAccountId Source # 
Instance details

Defined in Web.Stripe.Types

Read BankAccountId Source # 
Instance details

Defined in Web.Stripe.Types

Show BankAccountId Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam BankAccountId Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam CreateTransfer BankAccountId Source # 
Instance details

Defined in Web.Stripe.Transfer

data Card Source #

Card Object

Instances
Eq Card Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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

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

Data Card 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) -> Card -> c Card #

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

toConstr :: Card -> Constr #

dataTypeOf :: Card -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Card Source # 
Instance details

Defined in Web.Stripe.Types

Methods

compare :: Card -> Card -> Ordering #

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

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

(>) :: Card -> Card -> Bool #

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

max :: Card -> Card -> Card #

min :: Card -> Card -> Card #

Read Card Source # 
Instance details

Defined in Web.Stripe.Types

Show Card Source # 
Instance details

Defined in Web.Stripe.Types

Methods

showsPrec :: Int -> Card -> ShowS #

show :: Card -> String #

showList :: [Card] -> ShowS #

FromJSON Card Source #

JSON Instance for Card

Instance details

Defined in Web.Stripe.Types

newtype CardId Source #

CardId for a Customer

Constructors

CardId Text 
Instances
Eq CardId Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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

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

Data CardId 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) -> CardId -> c CardId #

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

toConstr :: CardId -> Constr #

dataTypeOf :: CardId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CardId Source # 
Instance details

Defined in Web.Stripe.Types

Read CardId Source # 
Instance details

Defined in Web.Stripe.Types

Show CardId Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON CardId Source #

JSON Instance for CardId

Instance details

Defined in Web.Stripe.Types

ToStripeParam CardId Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam CreateTransfer CardId Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam UpdateSubscription CardId Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam CreateSubscription CardId Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam UpdateRecipient CardId Source # 
Instance details

Defined in Web.Stripe.Recipient

StripeHasParam CreateRecipient CardId Source # 
Instance details

Defined in Web.Stripe.Recipient

StripeHasParam GetRecipientCards (EndingBefore CardId) Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetRecipientCards (StartingAfter CardId) Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetCustomerCards (EndingBefore CardId) Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetCustomerCards (StartingAfter CardId) Source # 
Instance details

Defined in Web.Stripe.Card

type ExpandsTo CardId Source # 
Instance details

Defined in Web.Stripe.Types

newtype Created Source #

Constructors

Created UTCTime 
Instances
Eq Created Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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

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

Data Created 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) -> 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 # 
Instance details

Defined in Web.Stripe.Types

Read Created Source # 
Instance details

Defined in Web.Stripe.Types

Show Created Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam Created Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam GetTransfers Created Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam GetInvoiceItems Created Source # 
Instance details

Defined in Web.Stripe.InvoiceItem

StripeHasParam GetEvents Created Source # 
Instance details

Defined in Web.Stripe.Event

StripeHasParam GetCustomers Created Source # 
Instance details

Defined in Web.Stripe.Customer

StripeHasParam GetCharges Created Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam GetBalanceTransactionHistory Created Source # 
Instance details

Defined in Web.Stripe.Balance

StripeHasParam GetApplicationFees Created Source # 
Instance details

Defined in Web.Stripe.ApplicationFee

StripeHasParam GetBalanceTransactionHistory (TimeRange Created) Source # 
Instance details

Defined in Web.Stripe.Balance

data Currency Source #

Stripe supports 138 currencies

Constructors

AED

United Arab Emirates Dirham

AFN

Afghan Afghani

ALL

Albanian Lek

AMD

Armenian Dram

ANG

Netherlands Antillean Gulden

AOA

Angolan Kwanza

ARS

Argentine Peso

AUD

Australian Dollar

AWG

Aruban Florin

AZN

Azerbaijani Manat

BAM

Bosnia & Herzegovina Convertible Mark

BBD

Barbadian Dollar

BDT

Bangladeshi Taka

BGN

Bulgarian Lev

BIF

Burundian Franc

BMD

Bermudian Dollar

BND

Brunei Dollar

BOB

Bolivian Boliviano

BRL

Brazilian Real

BSD

Bahamian Dollar

BWP

Botswana Pula

BZD

Belize Dollar

CAD

Canadian Dollar

CDF

Congolese Franc

CHF

Swiss Franc

CLP

Chilean Peso

CNY

Chinese Renminbi Yuan

COP

Colombian Peso

CRC

Costa Rican Colón

CVE

Cape Verdean Escudo

CZK

Czech Koruna

DJF

Djiboutian Franc

DKK

Danish Krone

DOP

Dominican Peso

DZD

Algerian Dinar

EEK

Estonian Kroon

EGP

Egyptian Pound

ETB

Ethiopian Birr

EUR

Euro

FJD

Fijian Dollar

FKP

Falkland Islands Pound

GBP

British Pound

GEL

Georgian Lari

GIP

Gibraltar Pound

GMD

Gambian Dalasi

GNF

Guinean Franc

GTQ

Guatemalan Quetzal

GYD

Guyanese Dollar

HKD

Hong Kong Dollar

HNL

Honduran Lempira

HRK

Croatian Kuna

HTG

Haitian Gourde

HUF

Hungarian Forint

IDR

Indonesian Rupiah

ILS

Israeli New Sheqel

INR

Indian Rupee

ISK

Icelandic Króna

JMD

Jamaican Dollar

JPY

Japanese Yen

KES

Kenyan Shilling

KGS

Kyrgyzstani Som

KHR

Cambodian Riel

KMF

Comorian Franc

KRW

South Korean Won

KYD

Cayman Islands Dollar

KZT

Kazakhstani Tenge

LAK

Lao Kip

LBP

Lebanese Pound

LKR

Sri Lankan Rupee

LRD

Liberian Dollar

LSL

Lesotho Loti

LTL

Lithuanian Litas

LVL

Latvian Lats

MAD

Moroccan Dirham

MDL

Moldovan Leu

MGA

Malagasy Ariary

MKD

Macedonian Denar

MNT

Mongolian Tögrög

MOP

Macanese Pataca

MRO

Mauritanian Ouguiya

MUR

Mauritian Rupee

MVR

Maldivian Rufiyaa

MWK

Malawian Kwacha

MXN

Mexican Peso

MYR

Malaysian Ringgit

MZN

Mozambican Metical

NAD

Namibian Dollar

NGN

Nigerian Naira

NIO

Nicaraguan Córdoba

NOK

Norwegian Krone

NPR

Nepalese Rupee

NZD

New Zealand Dollar

PAB

Panamanian Balboa

PEN

Peruvian Nuevo Sol

PGK

Papua New Guinean Kina

PHP

Philippine Peso

PKR

Pakistani Rupee

PLN

Polish Złoty

PYG

Paraguayan Guaraní

QAR

Qatari Riyal

RON

Romanian Leu

RSD

Serbian Dinar

RUB

Russian Ruble

RWF

Rwandan Franc

SAR

Saudi Riyal

SBD

Solomon Islands Dollar

SCR

Seychellois Rupee

SEK

Swedish Krona

SGD

Singapore Dollar

SHP

Saint Helenian Pound

SLL

Sierra Leonean Leone

SOS

Somali Shilling

SRD

Surinamese Dollar

STD

São Tomé and Príncipe Dobra

SVC

Salvadoran Colón

SZL

Swazi Lilangeni

THB

Thai Baht

TJS

Tajikistani Somoni

TOP

Tongan Paʻanga

TRY

Turkish Lira

TTD

Trinidad and Tobago Dollar

TWD

New Taiwan Dollar

TZS

Tanzanian Shilling

UAH

Ukrainian Hryvnia

UGX

Ugandan Shilling

USD

United States Dollar

UYU

Uruguayan Peso

UZS

Uzbekistani Som

VND

Vietnamese Đồng

VUV

Vanuatu Vatu

WST

Samoan Tala

XAF

Central African Cfa Franc

XCD

East Caribbean Dollar

XOF

West African Cfa Franc

XPF

Cfp Franc

YER

Yemeni Rial

ZAR

South African Rand

ZMW

Zambian Kwacha

UnknownCurrency

Unknown Currency

Instances
Eq Currency Source # 
Instance details

Defined in Web.Stripe.Types

Data Currency 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) -> Currency -> c Currency #

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

toConstr :: Currency -> Constr #

dataTypeOf :: Currency -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Currency Source # 
Instance details

Defined in Web.Stripe.Types

Read Currency Source # 
Instance details

Defined in Web.Stripe.Types

Show Currency Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON Currency Source #

Currency JSON instances

Instance details

Defined in Web.Stripe.Types

ToStripeParam Currency Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam CreateCoupon Currency Source # 
Instance details

Defined in Web.Stripe.Coupon

StripeHasParam GetBalanceTransactionHistory Currency Source # 
Instance details

Defined in Web.Stripe.Balance

newtype Date Source #

Constructors

Date UTCTime 
Instances
Eq Date Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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

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

Data Date 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) -> Date -> c Date #

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

toConstr :: Date -> Constr #

dataTypeOf :: Date -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Date Source # 
Instance details

Defined in Web.Stripe.Types

Methods

compare :: Date -> Date -> Ordering #

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

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

(>) :: Date -> Date -> Bool #

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

max :: Date -> Date -> Date #

min :: Date -> Date -> Date #

Read Date Source # 
Instance details

Defined in Web.Stripe.Types

Show Date Source # 
Instance details

Defined in Web.Stripe.Types

Methods

showsPrec :: Int -> Date -> ShowS #

show :: Date -> String #

showList :: [Date] -> ShowS #

ToStripeParam Date Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam GetTransfers Date Source # 
Instance details

Defined in Web.Stripe.Transfer

newtype Description Source #

Generic Description for use in constructing API Calls

Constructors

Description Text 
Instances
Eq Description Source # 
Instance details

Defined in Web.Stripe.Types

Data Description 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) -> Description -> c Description #

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

toConstr :: Description -> Constr #

dataTypeOf :: Description -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Description Source # 
Instance details

Defined in Web.Stripe.Types

Read Description Source # 
Instance details

Defined in Web.Stripe.Types

Show Description Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON Description Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam Description Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam UpdateTransfer Description Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam CreateTransfer Description Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam UpdateRecipient Description Source # 
Instance details

Defined in Web.Stripe.Recipient

StripeHasParam CreateRecipient Description Source # 
Instance details

Defined in Web.Stripe.Recipient

StripeHasParam UpdateInvoiceItem Description Source # 
Instance details

Defined in Web.Stripe.InvoiceItem

StripeHasParam CreateInvoiceItem Description Source # 
Instance details

Defined in Web.Stripe.InvoiceItem

StripeHasParam UpdateInvoice Description Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam CreateInvoice Description Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam UpdateCustomer Description Source # 
Instance details

Defined in Web.Stripe.Customer

StripeHasParam CreateCustomer Description Source # 
Instance details

Defined in Web.Stripe.Customer

StripeHasParam UpdateCharge Description Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam CreateCharge Description Source # 
Instance details

Defined in Web.Stripe.Charge

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

data Recipient Source #

Recipient Object

Instances
Eq Recipient Source # 
Instance details

Defined in Web.Stripe.Types

Data Recipient 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) -> Recipient -> c Recipient #

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

toConstr :: Recipient -> Constr #

dataTypeOf :: Recipient -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Recipient Source # 
Instance details

Defined in Web.Stripe.Types

Read Recipient Source # 
Instance details

Defined in Web.Stripe.Types

Show Recipient Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON Recipient Source #

JSON Instance for Recipient

Instance details

Defined in Web.Stripe.Types

newtype RecipientId Source #

Constructors

RecipientId Text 
Instances
Eq RecipientId Source # 
Instance details

Defined in Web.Stripe.Types

Data RecipientId 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) -> RecipientId -> c RecipientId #

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

toConstr :: RecipientId -> Constr #

dataTypeOf :: RecipientId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RecipientId Source # 
Instance details

Defined in Web.Stripe.Types

Read RecipientId Source # 
Instance details

Defined in Web.Stripe.Types

Show RecipientId Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON RecipientId Source #

JSON Instance for RecipientId

Instance details

Defined in Web.Stripe.Types

ToStripeParam RecipientId Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam GetTransfers RecipientId Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam GetRecipients (EndingBefore RecipientId) Source # 
Instance details

Defined in Web.Stripe.Recipient

StripeHasParam GetRecipients (StartingAfter RecipientId) Source # 
Instance details

Defined in Web.Stripe.Recipient

type ExpandsTo RecipientId Source # 
Instance details

Defined in Web.Stripe.Types

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

StatementDescription to be added to a Charge

Instances
Eq StatementDescription Source # 
Instance details

Defined in Web.Stripe.Types

Data StatementDescription 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) -> StatementDescription -> c StatementDescription #

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

toConstr :: StatementDescription -> Constr #

dataTypeOf :: StatementDescription -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord StatementDescription Source # 
Instance details

Defined in Web.Stripe.Types

Read StatementDescription Source # 
Instance details

Defined in Web.Stripe.Types

Show StatementDescription Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON StatementDescription Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam StatementDescription Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam CreateTransfer StatementDescription Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam UpdatePlan StatementDescription Source # 
Instance details

Defined in Web.Stripe.Plan

StripeHasParam CreatePlan StatementDescription Source # 
Instance details

Defined in Web.Stripe.Plan

StripeHasParam UpdateInvoice StatementDescription Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam CreateInvoice StatementDescription Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam CreateCharge StatementDescription Source # 
Instance details

Defined in Web.Stripe.Charge

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

data Transfer Source #

Transfer Object

Instances
Eq Transfer Source # 
Instance details

Defined in Web.Stripe.Types

Data Transfer 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) -> Transfer -> c Transfer #

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

toConstr :: Transfer -> Constr #

dataTypeOf :: Transfer -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Transfer Source # 
Instance details

Defined in Web.Stripe.Types

Read Transfer Source # 
Instance details

Defined in Web.Stripe.Types

Show Transfer Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON Transfer Source #

JSON Instance for Transfer

Instance details

Defined in Web.Stripe.Types

newtype TransferId Source #

Constructors

TransferId Text 
Instances
Eq TransferId Source # 
Instance details

Defined in Web.Stripe.Types

Data TransferId 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) -> TransferId -> c TransferId #

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

toConstr :: TransferId -> Constr #

dataTypeOf :: TransferId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TransferId Source # 
Instance details

Defined in Web.Stripe.Types

Read TransferId Source # 
Instance details

Defined in Web.Stripe.Types

Show TransferId Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam TransferId Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam GetBalanceTransactionHistory TransferId Source # 
Instance details

Defined in Web.Stripe.Balance

StripeHasParam GetTransfers (EndingBefore TransferId) Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam GetTransfers (StartingAfter TransferId) Source # 
Instance details

Defined in Web.Stripe.Transfer

data TransferStatus Source #

Status of a Transfer

Instances
Eq TransferStatus Source # 
Instance details

Defined in Web.Stripe.Types

Data TransferStatus 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) -> TransferStatus -> c TransferStatus #

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

toConstr :: TransferStatus -> Constr #

dataTypeOf :: TransferStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TransferStatus Source # 
Instance details

Defined in Web.Stripe.Types

Read TransferStatus Source # 
Instance details

Defined in Web.Stripe.Types

Show TransferStatus Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON TransferStatus Source #

JSON Instance for TransferStatus

Instance details

Defined in Web.Stripe.Types

ToStripeParam TransferStatus Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam GetTransfers TransferStatus Source # 
Instance details

Defined in Web.Stripe.Transfer

data TransferType Source #

Type of a Transfer

Instances
Eq TransferType Source # 
Instance details

Defined in Web.Stripe.Types

Data TransferType 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) -> TransferType -> c TransferType #

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

toConstr :: TransferType -> Constr #

dataTypeOf :: TransferType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TransferType Source # 
Instance details

Defined in Web.Stripe.Types

Read TransferType Source # 
Instance details

Defined in Web.Stripe.Types

Show TransferType Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON TransferType Source #

JSON Instance for TransferType

Instance details

Defined in Web.Stripe.Types

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