Copyright | (c) David Johnson 2014 |
---|---|
Maintainer | djohnson.m@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
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
- data CreateCharge
- createCharge :: Amount -> Currency -> StripeRequest CreateCharge
- data GetCharge
- getCharge :: ChargeId -> StripeRequest GetCharge
- data GetCharges
- getCharges :: StripeRequest GetCharges
- data UpdateCharge
- updateCharge :: ChargeId -> StripeRequest UpdateCharge
- data CaptureCharge
- captureCharge :: ChargeId -> StripeRequest CaptureCharge
- newtype Amount = Amount {}
- newtype ApplicationFeeAmount = ApplicationFeeAmount Integer
- newtype CardNumber = CardNumber Text
- newtype Capture = Capture {
- getCapture :: Bool
- data Charge = Charge {
- chargeId :: ChargeId
- chargeObject :: Text
- chargeCreated :: UTCTime
- chargeLiveMode :: Bool
- chargePaid :: Bool
- chargeAmount :: Amount
- chargeCurrency :: Currency
- chargeRefunded :: Bool
- chargeCreditCard :: Maybe Card
- chargeCaptured :: Bool
- chargeRefunds :: StripeList Refund
- chargeBalanceTransaction :: Maybe (Expandable TransactionId)
- chargeFailureMessage :: Maybe Text
- chargeFailureCode :: Maybe Text
- chargeAmountRefunded :: Int
- chargeCustomerId :: Maybe (Expandable CustomerId)
- chargeInvoice :: Maybe (Expandable InvoiceId)
- chargeDescription :: Maybe Description
- chargeDispute :: Maybe Dispute
- chargeMetaData :: MetaData
- chargeStatementDescription :: Maybe StatementDescription
- chargeReceiptEmail :: Maybe Text
- chargeReceiptNumber :: Maybe Text
- newtype ChargeId = ChargeId Text
- newtype Created = Created UTCTime
- data Currency
- = AED
- | AFN
- | ALL
- | AMD
- | ANG
- | AOA
- | ARS
- | AUD
- | AWG
- | AZN
- | BAM
- | BBD
- | BDT
- | BGN
- | BIF
- | BMD
- | BND
- | BOB
- | BRL
- | BSD
- | BWP
- | BZD
- | CAD
- | CDF
- | CHF
- | CLP
- | CNY
- | COP
- | CRC
- | CVE
- | CZK
- | DJF
- | DKK
- | DOP
- | DZD
- | EEK
- | EGP
- | ETB
- | EUR
- | FJD
- | FKP
- | GBP
- | GEL
- | GIP
- | GMD
- | GNF
- | GTQ
- | GYD
- | HKD
- | HNL
- | HRK
- | HTG
- | HUF
- | IDR
- | ILS
- | INR
- | ISK
- | JMD
- | JPY
- | KES
- | KGS
- | KHR
- | KMF
- | KRW
- | KYD
- | KZT
- | LAK
- | LBP
- | LKR
- | LRD
- | LSL
- | LTL
- | LVL
- | MAD
- | MDL
- | MGA
- | MKD
- | MNT
- | MOP
- | MRO
- | MUR
- | MVR
- | MWK
- | MXN
- | MYR
- | MZN
- | NAD
- | NGN
- | NIO
- | NOK
- | NPR
- | NZD
- | PAB
- | PEN
- | PGK
- | PHP
- | PKR
- | PLN
- | PYG
- | QAR
- | RON
- | RSD
- | RUB
- | RWF
- | SAR
- | SBD
- | SCR
- | SEK
- | SGD
- | SHP
- | SLL
- | SOS
- | SRD
- | STD
- | SVC
- | SZL
- | THB
- | TJS
- | TOP
- | TRY
- | TTD
- | TWD
- | TZS
- | UAH
- | UGX
- | USD
- | UYU
- | UZS
- | VND
- | VUV
- | WST
- | XAF
- | XCD
- | XOF
- | XPF
- | YER
- | ZAR
- | ZMW
- | UnknownCurrency
- newtype CustomerId = CustomerId Text
- data Customer
- = Customer {
- customerObject :: Text
- customerCreated :: UTCTime
- customerId :: CustomerId
- customerLiveMode :: Bool
- customerDescription :: Maybe Description
- customerEmail :: Maybe Email
- customerDelinquent :: Bool
- customerSubscriptions :: StripeList Subscription
- customerDiscount :: Maybe Discount
- customerAccountBalance :: Int
- customerCards :: StripeList Card
- customerCurrency :: Maybe Currency
- customerDefaultCard :: Maybe (Expandable CardId)
- customerMetaData :: MetaData
- | DeletedCustomer { }
- = Customer {
- newtype CVC = CVC Text
- newtype Description = Description Text
- newtype Email = Email Text
- newtype EndingBefore a = EndingBefore a
- newtype ExpandParams = ExpandParams {
- getExpandParams :: [Text]
- newtype ExpMonth = ExpMonth Int
- newtype ExpYear = ExpYear Int
- newtype Limit = Limit Int
- newtype MetaData = MetaData [(Text, Text)]
- data NewCard = NewCard {
- newCardCardNumber :: CardNumber
- newCardExpMonth :: ExpMonth
- newCardExpYear :: ExpYear
- newCardCVC :: Maybe CVC
- newCardName :: Maybe Name
- newCardAddressLine1 :: Maybe AddressLine1
- newCardAddressLine2 :: Maybe AddressLine2
- newCardAddressCity :: Maybe AddressCity
- newCardAddressZip :: Maybe AddressZip
- newCardAddressState :: Maybe AddressState
- newCardAddressCountry :: Maybe AddressCountry
- newtype ReceiptEmail = ReceiptEmail Text
- newtype StartingAfter a = StartingAfter a
- newtype StatementDescription = StatementDescription Text
- data StripeList a = StripeList {}
- newtype TokenId = TokenId Text
API
data CreateCharge Source #
Instances
StripeHasParam CreateCharge ReceiptEmail Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam CreateCharge Description Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam CreateCharge ExpandParams Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam CreateCharge MetaData Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam CreateCharge TokenId Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam CreateCharge ApplicationFeeAmount Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam CreateCharge NewCard Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam CreateCharge CustomerId Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam CreateCharge Capture Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam CreateCharge StatementDescription Source # | |
Defined in Web.Stripe.Charge | |
type StripeReturn CreateCharge Source # | |
Defined in Web.Stripe.Charge |
:: Amount |
|
-> Currency |
|
-> StripeRequest CreateCharge |
Create a Charge
Instances
StripeHasParam GetCharge ExpandParams Source # | |
Defined in Web.Stripe.Charge | |
type StripeReturn GetCharge Source # | |
Defined in Web.Stripe.Charge |
:: ChargeId | The |
-> StripeRequest GetCharge |
data GetCharges Source #
Instances
StripeHasParam GetCharges ExpandParams Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam GetCharges Limit Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam GetCharges CustomerId Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam GetCharges Created Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam GetCharges (EndingBefore ChargeId) Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam GetCharges (StartingAfter ChargeId) Source # | |
Defined in Web.Stripe.Charge | |
type StripeReturn GetCharges Source # | |
Defined in Web.Stripe.Charge |
getCharges :: StripeRequest GetCharges Source #
Retrieve all Charge
s
data UpdateCharge Source #
Instances
StripeHasParam UpdateCharge Description Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam UpdateCharge MetaData Source # | |
Defined in Web.Stripe.Charge | |
type StripeReturn UpdateCharge Source # | |
Defined in Web.Stripe.Charge |
:: ChargeId | The |
-> StripeRequest UpdateCharge |
A Charge
to be updated
data CaptureCharge Source #
Instances
StripeHasParam CaptureCharge ReceiptEmail Source # | |
Defined in Web.Stripe.Charge | |
StripeHasParam CaptureCharge Amount Source # | |
Defined in Web.Stripe.Charge | |
type StripeReturn CaptureCharge Source # | |
Defined in Web.Stripe.Charge |
a Charge
to be captured
Types
Amount representing a monetary value. Stripe represents pennies as whole numbers i.e. 100 = $1
Instances
newtype ApplicationFeeAmount Source #
ApplicationFeeAmount
Instances
newtype CardNumber Source #
Number associated with a Card
Instances
Capture for Charge
Instances
Eq Capture Source # | |
Data Capture Source # | |
Defined in Web.Stripe.Types 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 # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Capture -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam CreateCharge Capture Source # | |
Defined in Web.Stripe.Charge |
Charge
object in Stripe
API
Instances
Eq Charge Source # | |
Data Charge Source # | |
Defined in Web.Stripe.Types 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 |
Instances
Instances
Stripe supports 138 currencies
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 # | |
Defined in Web.Stripe.Types 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 # | |
Defined in Web.Stripe.Types | |
Read Currency Source # | |
Show Currency Source # | |
FromJSON Currency Source # |
|
ToStripeParam Currency Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Currency -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam CreateCoupon Currency Source # | |
Defined in Web.Stripe.Coupon | |
StripeHasParam GetBalanceTransactionHistory Currency Source # | |
Defined in Web.Stripe.Balance |
newtype CustomerId Source #
CustomerId
for a Customer
Instances
Customer
object
Instances
Eq Customer Source # | |
Data Customer Source # | |
Defined in Web.Stripe.Types 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 # | |
Defined in Web.Stripe.Types | |
Read Customer Source # | |
Show Customer Source # | |
FromJSON Customer Source # | JSON Instance for |
CVC for a Card
Instances
Eq CVC Source # | |
Data CVC Source # | |
Defined in Web.Stripe.Types 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 # 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 # | |
Read CVC Source # | |
Show CVC Source # | |
ToStripeParam CVC Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: CVC -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # |
newtype Description Source #
Generic Description for use in constructing API Calls
Instances
Instances
Eq Email Source # | |
Data Email Source # | |
Defined in Web.Stripe.Types 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 # 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 # | |
Read Email Source # | |
Show Email Source # | |
ToStripeParam Email Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Email -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipient Email Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam CreateRecipient Email Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam UpdateCustomer Email Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam CreateCustomer Email Source # | |
Defined in Web.Stripe.Customer |
newtype EndingBefore a Source #
Pagination Option for StripeList
Instances
newtype ExpandParams Source #
Type of Expansion Parameters for use on Stripe
objects
Instances
Expiration Month for a Card
Instances
Eq ExpMonth Source # | |
Data ExpMonth Source # | |
Defined in Web.Stripe.Types 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 # | |
Defined in Web.Stripe.Types | |
Read ExpMonth Source # | |
Show ExpMonth Source # | |
ToStripeParam ExpMonth Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: ExpMonth -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipientCard ExpMonth Source # | |
Defined in Web.Stripe.Card | |
StripeHasParam UpdateCustomerCard ExpMonth Source # | |
Defined in Web.Stripe.Card |
Expiration Year for a Card
Instances
Eq ExpYear Source # | |
Data ExpYear Source # | |
Defined in Web.Stripe.Types 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 # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: ExpYear -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipientCard ExpYear Source # | |
Defined in Web.Stripe.Card | |
StripeHasParam UpdateCustomerCard ExpYear Source # | |
Defined in Web.Stripe.Card |
Pagination Option for StripeList
Instances
Type of MetaData for use on Stripe
objects
Instances
Instances
newtype ReceiptEmail Source #
Email
to send receipt to
Instances
newtype StartingAfter a Source #
Pagination Option for StripeList
Instances
newtype StatementDescription Source #
StatementDescription
to be added to a Charge
Instances
data StripeList a Source #
Generic handling of Stripe JSON arrays