Copyright | (c) David Johnson 2014 |
---|---|
Maintainer | djohnson.m@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
https://stripe.com/docs/api#invoiceitems
{-# LANGUAGE OverloadedStrings #-} import Web.Stripe import Web.Stripe.Customer import Web.Stripe.InvoiceItem main :: IO () main = do let config = StripeConfig (StripeKey "secret_key") result <- stripe config $ createCustomer case result of (Left stripeError) -> print stripeError (Right (Customer { customerId = cid })) -> do result <- stripe config $ createInvoiceItem cid (Amount 100) USD -&- (Description "description") case result of Left stripeError -> print stripeError Right invoiceitem -> print invoiceitem
Synopsis
- data CreateInvoiceItem
- createInvoiceItem :: CustomerId -> Amount -> Currency -> StripeRequest CreateInvoiceItem
- data GetInvoiceItem
- getInvoiceItem :: InvoiceItemId -> StripeRequest GetInvoiceItem
- data UpdateInvoiceItem
- updateInvoiceItem :: InvoiceItemId -> StripeRequest UpdateInvoiceItem
- data DeleteInvoiceItem
- deleteInvoiceItem :: InvoiceItemId -> StripeRequest DeleteInvoiceItem
- data GetInvoiceItems
- getInvoiceItems :: StripeRequest GetInvoiceItems
- newtype InvoiceItemId = InvoiceItemId Text
- data InvoiceItem = InvoiceItem {
- invoiceItemObject :: Text
- invoiceItemId :: InvoiceItemId
- invoiceItemDate :: UTCTime
- invoiceItemAmount :: Int
- invoiceItemLiveMode :: Bool
- invoiceItemProration :: Bool
- invoiceItemCurrency :: Currency
- invoiceItemCustomer :: Expandable CustomerId
- invoiceItemDescription :: Maybe Description
- invoiceItemInvoice :: Maybe (Expandable InvoiceId)
- invoiceItemQuantity :: Maybe Quantity
- invoiceItemSubscription :: Maybe SubscriptionId
- invoiceItemMetaData :: MetaData
- newtype Created = Created UTCTime
- newtype CustomerId = CustomerId Text
- 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 EndingBefore a = EndingBefore a
- newtype ExpandParams = ExpandParams {
- getExpandParams :: [Text]
- newtype InvoiceId = InvoiceId Text
- data Invoice = Invoice {
- invoiceDate :: UTCTime
- invoiceId :: Maybe InvoiceId
- invoicePeriodStart :: UTCTime
- invoicePeriodEnd :: UTCTime
- invoiceLineItems :: StripeList InvoiceLineItem
- invoiceSubTotal :: Int
- invoiceTotal :: Int
- invoiceCustomer :: Expandable CustomerId
- invoiceObject :: Text
- invoiceAttempted :: Bool
- invoiceClosed :: Bool
- invoiceForgiven :: Bool
- invoicePaid :: Bool
- invoiceLiveMode :: Bool
- invoiceAttemptCount :: Int
- invoiceAmountDue :: Int
- invoiceCurrency :: Currency
- invoiceStartingBalance :: Int
- invoiceEndingBalance :: Maybe Int
- invoiceNextPaymentAttempt :: Maybe UTCTime
- invoiceWebHooksDeliveredAt :: Maybe UTCTime
- invoiceCharge :: Maybe (Expandable ChargeId)
- invoiceDiscount :: Maybe Discount
- invoiceApplicateFee :: Maybe FeeId
- invoiceSubscription :: Maybe SubscriptionId
- invoiceStatementDescription :: Maybe StatementDescription
- invoiceDescription :: Maybe Description
- invoiceMetaData :: MetaData
- newtype Limit = Limit Int
- newtype SubscriptionId = SubscriptionId {}
- newtype StartingAfter a = StartingAfter a
- data StripeDeleteResult = StripeDeleteResult {}
- data StripeList a = StripeList {}
- newtype Description = Description Text
- newtype Amount = Amount {}
API
data CreateInvoiceItem Source #
Instances
StripeHasParam CreateInvoiceItem Description Source # | |
Defined in Web.Stripe.InvoiceItem | |
StripeHasParam CreateInvoiceItem MetaData Source # | |
Defined in Web.Stripe.InvoiceItem | |
StripeHasParam CreateInvoiceItem InvoiceId Source # | |
Defined in Web.Stripe.InvoiceItem | |
StripeHasParam CreateInvoiceItem SubscriptionId Source # | |
Defined in Web.Stripe.InvoiceItem | |
type StripeReturn CreateInvoiceItem Source # | |
Defined in Web.Stripe.InvoiceItem |
:: CustomerId |
|
-> Amount |
|
-> Currency |
|
-> StripeRequest CreateInvoiceItem |
Create an invoice for a Customer
data GetInvoiceItem Source #
Instances
StripeHasParam GetInvoiceItem ExpandParams Source # | |
Defined in Web.Stripe.InvoiceItem | |
type StripeReturn GetInvoiceItem Source # | |
Defined in Web.Stripe.InvoiceItem |
:: InvoiceItemId |
|
-> StripeRequest GetInvoiceItem |
Retrieve an InvoiceItem
by InvoiceItemId
data UpdateInvoiceItem Source #
Instances
StripeHasParam UpdateInvoiceItem Description Source # | |
Defined in Web.Stripe.InvoiceItem | |
StripeHasParam UpdateInvoiceItem MetaData Source # | |
Defined in Web.Stripe.InvoiceItem | |
StripeHasParam UpdateInvoiceItem Amount Source # | |
Defined in Web.Stripe.InvoiceItem | |
type StripeReturn UpdateInvoiceItem Source # | |
Defined in Web.Stripe.InvoiceItem |
:: InvoiceItemId |
|
-> StripeRequest UpdateInvoiceItem |
Update an InvoiceItem
by InvoiceItemId
data DeleteInvoiceItem Source #
Instances
type StripeReturn DeleteInvoiceItem Source # | |
Defined in Web.Stripe.InvoiceItem |
:: InvoiceItemId |
|
-> StripeRequest DeleteInvoiceItem |
Delete an InvoiceItem
by InvoiceItemId
data GetInvoiceItems Source #
Instances
StripeHasParam GetInvoiceItems ExpandParams Source # | |
Defined in Web.Stripe.InvoiceItem | |
StripeHasParam GetInvoiceItems Limit Source # | |
Defined in Web.Stripe.InvoiceItem | |
StripeHasParam GetInvoiceItems CustomerId Source # | |
Defined in Web.Stripe.InvoiceItem | |
StripeHasParam GetInvoiceItems Created Source # | |
Defined in Web.Stripe.InvoiceItem | |
StripeHasParam GetInvoiceItems (EndingBefore InvoiceItemId) Source # | |
Defined in Web.Stripe.InvoiceItem | |
StripeHasParam GetInvoiceItems (StartingAfter InvoiceItemId) Source # | |
Defined in Web.Stripe.InvoiceItem | |
type StripeReturn GetInvoiceItems Source # | |
Defined in Web.Stripe.InvoiceItem |
Types
newtype InvoiceItemId Source #
Instances
data InvoiceItem Source #
InvoiceItem
object
Instances
Instances
newtype CustomerId Source #
CustomerId
for a Customer
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 EndingBefore a Source #
Pagination Option for StripeList
Instances
newtype ExpandParams Source #
Type of Expansion Parameters for use on Stripe
objects
Instances
Instances
Invoice
Object
Instances
Eq Invoice Source # | |
Data Invoice Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Invoice -> c Invoice # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Invoice # toConstr :: Invoice -> Constr # dataTypeOf :: Invoice -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Invoice) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Invoice) # gmapT :: (forall b. Data b => b -> b) -> Invoice -> Invoice # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Invoice -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Invoice -> r # gmapQ :: (forall d. Data d => d -> u) -> Invoice -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Invoice -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Invoice -> m Invoice # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Invoice -> m Invoice # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Invoice -> m Invoice # | |
Ord Invoice Source # | |
Read Invoice Source # | |
Show Invoice Source # | |
FromJSON Invoice Source # | JSON Instance for |
Pagination Option for StripeList
Instances
newtype SubscriptionId Source #
SubscriptionId
for a Subscription
Instances
newtype StartingAfter a Source #
Pagination Option for StripeList
Instances
data StripeDeleteResult Source #
JSON returned from a Stripe
deletion request
Instances
data StripeList a Source #
Generic handling of Stripe JSON arrays
Instances
newtype Description Source #
Generic Description for use in constructing API Calls
Instances
Amount representing a monetary value. Stripe represents pennies as whole numbers i.e. 100 = $1