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

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

Web.Stripe.Charge

Contents

Description

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

{-# LANGUAGE OverloadedStrings #-}
import Web.Stripe
import Web.Stripe.Customer
import Web.Stripe.Charge

main :: IO ()
main = do
  let config = StripeConfig (StripeKey "secret_key")
      credit = CardNumber "4242424242424242"
      em  = ExpMonth 12
      ey  = ExpYear 2015
      cvc = CVC "123"
      cardinfo = (newCard credit em ey) { newCardCVC = Just cvc }
  result <- stripe config createCustomer
                             -&- cardinfo
  case result of
    (Left stripeError) -> print stripeError
    (Customer { customerId = cid }) ->
      do result <- stripe config $ createCharge (Amount 100) USD
                                     -&- cid
         case result of
           Left  stripeError -> print stripeError
           Right charge      -> print charge

Synopsis

API

createCharge Source #

Arguments

:: Amount

Amount to charge

-> Currency

Currency for charge

-> StripeRequest CreateCharge 

Create a Charge

getCharge Source #

Arguments

:: ChargeId

The Charge to retrive

-> StripeRequest GetCharge 

Retrieve a Charge by ChargeId

updateCharge Source #

Arguments

:: ChargeId

The Charge to update

-> StripeRequest UpdateCharge 

A Charge to be updated

captureCharge Source #

Arguments

:: ChargeId

The ChargeId of the Charge to capture

-> StripeRequest CaptureCharge 

a Charge to be captured

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 # 

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 # 

newtype ApplicationFeeAmount Source #

ApplicationFeeAmount

Instances

Eq ApplicationFeeAmount Source # 
Data ApplicationFeeAmount Source # 

Methods

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

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

toConstr :: ApplicationFeeAmount -> Constr #

dataTypeOf :: ApplicationFeeAmount -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ApplicationFeeAmount Source # 
Read ApplicationFeeAmount Source # 
Show ApplicationFeeAmount Source # 
ToStripeParam ApplicationFeeAmount Source # 
StripeHasParam CreateCharge ApplicationFeeAmount Source # 

newtype CardNumber Source #

Number associated with a Card

Constructors

CardNumber Text 

Instances

Eq CardNumber Source # 
Data CardNumber Source # 

Methods

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

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

toConstr :: CardNumber -> Constr #

dataTypeOf :: CardNumber -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CardNumber Source # 
Read CardNumber Source # 
Show CardNumber Source # 
ToStripeParam CardNumber Source # 

newtype Capture Source #

Capture for Charge

Constructors

Capture 

Fields

Instances

Eq Capture Source # 

Methods

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

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

Data Capture Source # 

Methods

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

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

toConstr :: Capture -> Constr #

dataTypeOf :: Capture -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Capture Source # 
Read Capture Source # 
Show Capture Source # 
ToStripeParam Capture Source # 
StripeHasParam CreateCharge Capture Source # 

data Charge Source #

Charge object in Stripe API

Instances

Eq Charge Source # 

Methods

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

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

Data Charge Source # 

Methods

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

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

toConstr :: Charge -> Constr #

dataTypeOf :: Charge -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Charge Source # 
Read Charge Source # 
Show Charge Source # 
FromJSON Charge Source #

JSON Instance for Charge

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 # 

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 # 

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 # 
Data Currency Source # 

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

Currency JSON instances

ToStripeParam Currency Source # 
StripeHasParam CreateCoupon Currency Source # 
StripeHasParam GetBalanceTransactionHistory Currency Source # 

newtype CustomerId Source #

Constructors

CustomerId Text 

Instances

Eq CustomerId Source # 
Data CustomerId Source # 

Methods

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

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

toConstr :: CustomerId -> Constr #

dataTypeOf :: CustomerId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CustomerId Source # 
Read CustomerId Source # 
Show CustomerId Source # 
FromJSON CustomerId Source #

JSON Instance for CustomerId

ToStripeParam CustomerId Source # 
StripeHasParam CreateCardToken CustomerId Source # 
StripeHasParam GetInvoiceItems CustomerId Source # 
StripeHasParam GetInvoiceLineItems CustomerId Source # 
StripeHasParam GetCharges CustomerId Source # 
StripeHasParam CreateCharge CustomerId Source # 
StripeHasParam GetCustomers (EndingBefore CustomerId) Source # 
StripeHasParam GetCustomers (StartingAfter CustomerId) Source # 
type ExpandsTo CustomerId Source # 

data Customer Source #

Customer object

Instances

Eq Customer Source # 
Data Customer Source # 

Methods

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

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

toConstr :: Customer -> Constr #

dataTypeOf :: Customer -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Customer Source # 
Read Customer Source # 
Show Customer Source # 
FromJSON Customer Source #

JSON Instance for Customer

newtype CVC Source #

CVC for a Card

Constructors

CVC Text 

Instances

Eq CVC Source # 

Methods

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

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

Data CVC Source # 

Methods

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

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

toConstr :: CVC -> Constr #

dataTypeOf :: CVC -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CVC Source # 

Methods

compare :: CVC -> CVC -> Ordering #

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

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

(>) :: CVC -> CVC -> Bool #

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

max :: CVC -> CVC -> CVC #

min :: CVC -> CVC -> CVC #

Read CVC Source # 
Show CVC Source # 

Methods

showsPrec :: Int -> CVC -> ShowS #

show :: CVC -> String #

showList :: [CVC] -> ShowS #

ToStripeParam CVC Source # 

newtype Description Source #

Generic Description for use in constructing API Calls

Constructors

Description Text 

Instances

Eq Description Source # 
Data Description Source # 

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 # 
Read Description Source # 
Show Description Source # 
FromJSON Description Source # 
ToStripeParam Description Source # 
StripeHasParam UpdateTransfer Description Source # 
StripeHasParam CreateTransfer Description Source # 
StripeHasParam UpdateRecipient Description Source # 
StripeHasParam CreateRecipient Description Source # 
StripeHasParam UpdateInvoiceItem Description Source # 
StripeHasParam CreateInvoiceItem Description Source # 
StripeHasParam UpdateInvoice Description Source # 
StripeHasParam CreateInvoice Description Source # 
StripeHasParam UpdateCustomer Description Source # 
StripeHasParam CreateCustomer Description Source # 
StripeHasParam UpdateCharge Description Source # 
StripeHasParam CreateCharge Description Source # 

newtype Email Source #

Email associated with a Customer, Recipient or Charge

Constructors

Email Text 

Instances

Eq Email Source # 

Methods

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

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

Data Email Source # 

Methods

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

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

toConstr :: Email -> Constr #

dataTypeOf :: Email -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Email Source # 

Methods

compare :: Email -> Email -> Ordering #

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

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

(>) :: Email -> Email -> Bool #

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

max :: Email -> Email -> Email #

min :: Email -> Email -> Email #

Read Email Source # 
Show Email Source # 

Methods

showsPrec :: Int -> Email -> ShowS #

show :: Email -> String #

showList :: [Email] -> ShowS #

ToStripeParam Email Source # 
StripeHasParam UpdateRecipient Email Source # 
StripeHasParam CreateRecipient Email Source # 
StripeHasParam UpdateCustomer Email Source # 
StripeHasParam CreateCustomer Email Source # 

newtype EndingBefore a Source #

Pagination Option for StripeList

Constructors

EndingBefore a 

Instances

StripeHasParam GetSubscriptions (EndingBefore SubscriptionId) Source # 
StripeHasParam GetTransfers (EndingBefore TransferId) 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 ExpandParams Source #

Type of Expansion Parameters for use on Stripe objects

Constructors

ExpandParams 

Fields

Instances

Eq ExpandParams Source # 
Data ExpandParams Source # 

Methods

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

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

toConstr :: ExpandParams -> Constr #

dataTypeOf :: ExpandParams -> DataType #

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

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

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

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

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

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

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

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

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

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

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

newtype ExpMonth Source #

Expiration Month for a Card

Constructors

ExpMonth Int 

Instances

Eq ExpMonth Source # 
Data ExpMonth Source # 

Methods

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

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

toConstr :: ExpMonth -> Constr #

dataTypeOf :: ExpMonth -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ExpMonth Source # 
Read ExpMonth Source # 
Show ExpMonth Source # 
ToStripeParam ExpMonth Source # 
StripeHasParam UpdateRecipientCard ExpMonth Source # 
StripeHasParam UpdateCustomerCard ExpMonth Source # 

newtype ExpYear Source #

Expiration Year for a Card

Constructors

ExpYear Int 

Instances

Eq ExpYear Source # 

Methods

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

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

Data ExpYear Source # 

Methods

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

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

toConstr :: ExpYear -> Constr #

dataTypeOf :: ExpYear -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ExpYear Source # 
Read ExpYear Source # 
Show ExpYear Source # 
ToStripeParam ExpYear Source # 
StripeHasParam UpdateRecipientCard ExpYear Source # 
StripeHasParam UpdateCustomerCard ExpYear 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 GetSubscriptions Limit Source # 
StripeHasParam GetTransfers 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 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 UpdateSubscription MetaData Source # 
StripeHasParam CreateSubscription MetaData Source # 
StripeHasParam UpdateTransfer MetaData Source # 
StripeHasParam CreateTransfer 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 # 

data NewCard Source #

NewCard contains the data needed to create a new Card

Instances

Eq NewCard Source # 

Methods

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

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

Data NewCard Source # 

Methods

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

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

toConstr :: NewCard -> Constr #

dataTypeOf :: NewCard -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord NewCard Source # 
Read NewCard Source # 
Show NewCard Source # 
ToStripeParam NewCard Source # 
StripeHasParam UpdateRecipient NewCard Source # 
StripeHasParam CreateRecipient NewCard Source # 
StripeHasParam UpdateCustomer NewCard Source # 
StripeHasParam CreateCustomer NewCard Source # 
StripeHasParam CreateCharge NewCard Source # 

newtype ReceiptEmail Source #

Email to send receipt to

Constructors

ReceiptEmail Text 

Instances

Eq ReceiptEmail Source # 
Data ReceiptEmail Source # 

Methods

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

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

toConstr :: ReceiptEmail -> Constr #

dataTypeOf :: ReceiptEmail -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ReceiptEmail Source # 
Read ReceiptEmail Source # 
Show ReceiptEmail Source # 
ToStripeParam ReceiptEmail Source # 
StripeHasParam CaptureCharge ReceiptEmail Source # 
StripeHasParam CreateCharge ReceiptEmail Source # 

newtype StartingAfter a Source #

Pagination Option for StripeList

Constructors

StartingAfter a 

Instances

StripeHasParam GetSubscriptions (StartingAfter SubscriptionId) Source # 
StripeHasParam GetTransfers (StartingAfter TransferId) 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 StatementDescription Source #

StatementDescription to be added to a Charge

Instances

Eq StatementDescription Source # 
Data StatementDescription Source # 

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 # 
Read StatementDescription Source # 
Show StatementDescription Source # 
FromJSON StatementDescription Source # 
ToStripeParam StatementDescription Source # 
StripeHasParam CreateTransfer StatementDescription Source # 
StripeHasParam UpdatePlan StatementDescription Source # 
StripeHasParam CreatePlan StatementDescription Source # 
StripeHasParam UpdateInvoice StatementDescription Source # 
StripeHasParam CreateInvoice StatementDescription Source # 
StripeHasParam CreateCharge StatementDescription 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 TokenId Source #

Constructors

TokenId Text 

Instances

Eq TokenId Source # 

Methods

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

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

Data TokenId Source # 

Methods

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

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

toConstr :: TokenId -> Constr #

dataTypeOf :: TokenId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TokenId Source # 
Read TokenId Source # 
Show TokenId Source # 
ToStripeParam TokenId Source # 
StripeHasParam UpdateRecipient TokenId Source # 
StripeHasParam CreateRecipient TokenId Source # 
StripeHasParam UpdateCustomer TokenId Source # 
StripeHasParam CreateCustomer TokenId Source # 
StripeHasParam CreateCharge TokenId Source #