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

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

Web.Stripe.Invoice

Contents

Description

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

{-# LANGUAGE OverloadedStrings #-}
import Web.Stripe
import Web.Stripe.Customer
import Web.Stripe.Invoice
import Web.Stripe.InvoiceItem
import Web.Stripe.Plan

main :: IO ()
main = do
  let config = StripeConfig (SecretKey "secret_key")
  result <- stripe config createCustomer
  case result of
    (Left stripeError) -> print stripeError
    (Right (Customer { customerId = cid })) ->
      do result <- stripe config $
           createPlan (PlanId "planid") (Amount 20) USD Day (PlanName "testplan")
         case result of
           (Left stripeError) -> print stripeError
           (Right (Plan {})) ->
             do result <- stripe config $
                  createInvoiceItem cid (Amount 100) USD
                case result of
                  (Left stripeError)  -> print stripeError
                  (Right invoiceItem) ->
                     do result <- stripe config $ createInvoice cid
                        case result of
                          (Left  stripeError) -> print stripeError
                          (Right invoice)     -> print invoice

Synopsis

API

createInvoice Source #

The Invoice to be created for a Customer

getUpcomingInvoice Source #

Arguments

:: CustomerId

The InvoiceId of the Invoice to retrieve

-> StripeRequest GetUpcomingInvoice 

Retrieve an upcoming Invoice for a Customer by CustomerId

Types

newtype ApplicationFeeId Source #

PlanId for a Plan

Constructors

ApplicationFeeId Text 

Instances

Eq ApplicationFeeId Source # 
Data ApplicationFeeId Source # 

Methods

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

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

toConstr :: ApplicationFeeId -> Constr #

dataTypeOf :: ApplicationFeeId -> DataType #

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

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

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

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

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

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

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

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

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

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

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

newtype Closed Source #

Closed - invoice closed or not

Constructors

Closed 

Fields

Instances

Eq Closed Source # 

Methods

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

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

Data Closed Source # 

Methods

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

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

toConstr :: Closed -> Constr #

dataTypeOf :: Closed -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Closed Source # 
Read Closed Source # 
Show Closed Source # 
ToStripeParam Closed Source # 
StripeHasParam UpdateInvoice Closed 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 # 

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 # 

data Discount Source #

Instances

Eq Discount Source # 
Data Discount Source # 

Methods

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

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

toConstr :: Discount -> Constr #

dataTypeOf :: Discount -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Discount Source # 
Read Discount Source # 
Show Discount Source # 
FromJSON Discount Source #

JSON Instance for Discount

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

Forgiven - invoice forgiven or not

Constructors

Forgiven 

Fields

Instances

Eq Forgiven Source # 
Data Forgiven Source # 

Methods

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

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

toConstr :: Forgiven -> Constr #

dataTypeOf :: Forgiven -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Forgiven Source # 
Read Forgiven Source # 
Show Forgiven Source # 
ToStripeParam Forgiven Source # 
StripeHasParam UpdateInvoice Forgiven Source # 

data Invoice Source #

Invoice Object

Instances

Eq Invoice Source # 

Methods

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

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

Data Invoice Source # 

Methods

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 Invoice

newtype InvoiceId Source #

Constructors

InvoiceId Text 

Instances

Eq InvoiceId Source # 
Data InvoiceId Source # 

Methods

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

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

toConstr :: InvoiceId -> Constr #

dataTypeOf :: InvoiceId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InvoiceId Source # 
Read InvoiceId Source # 
Show InvoiceId Source # 
FromJSON InvoiceId Source #

JSON Instance for InvoiceId

ToStripeParam InvoiceId Source # 
StripeHasParam CreateInvoiceItem InvoiceId Source # 
StripeHasParam GetInvoices (EndingBefore InvoiceId) Source # 
StripeHasParam GetInvoices (StartingAfter InvoiceId) Source # 
type ExpandsTo InvoiceId Source # 

data InvoiceLineItem Source #

Instances

Eq InvoiceLineItem Source # 
Data InvoiceLineItem Source # 

Methods

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

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

toConstr :: InvoiceLineItem -> Constr #

dataTypeOf :: InvoiceLineItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InvoiceLineItem Source # 
Read InvoiceLineItem Source # 
Show InvoiceLineItem Source # 
FromJSON InvoiceLineItem Source #

JSON Instance for InvoiceLineItem

newtype InvoiceLineItemId Source #

Constructors

InvoiceLineItemId Text 

Instances

Eq InvoiceLineItemId Source # 
Data InvoiceLineItemId Source # 

Methods

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

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

toConstr :: InvoiceLineItemId -> Constr #

dataTypeOf :: InvoiceLineItemId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InvoiceLineItemId Source # 
Read InvoiceLineItemId Source # 
Show InvoiceLineItemId Source # 
ToStripeParam InvoiceLineItemId Source # 
StripeHasParam GetInvoiceLineItems (EndingBefore InvoiceLineItemId) Source # 
StripeHasParam GetInvoiceLineItems (StartingAfter InvoiceLineItemId) Source # 

data InvoiceLineItemType Source #

Type of InvoiceItem

Instances

Eq InvoiceLineItemType Source # 
Data InvoiceLineItemType Source # 

Methods

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

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

toConstr :: InvoiceLineItemType -> Constr #

dataTypeOf :: InvoiceLineItemType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InvoiceLineItemType Source # 
Read InvoiceLineItemType Source # 
Show InvoiceLineItemType Source # 
FromJSON InvoiceLineItemType Source #

JSON Instance for InvoiceLineItemType

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

Period for an InvoiceLineItem

Constructors

Period 

Fields

Instances

Eq Period Source # 

Methods

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

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

Data Period Source # 

Methods

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

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

toConstr :: Period -> Constr #

dataTypeOf :: Period -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Period Source # 
Read Period Source # 
Show Period Source # 
FromJSON Period Source #

JSON Instance for Period

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 # 

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 # 

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

Constructors

SubscriptionId 

Instances

Eq SubscriptionId Source # 
Data SubscriptionId Source # 

Methods

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

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

toConstr :: SubscriptionId -> Constr #

dataTypeOf :: SubscriptionId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SubscriptionId Source # 
Read SubscriptionId Source # 
Show SubscriptionId Source # 
FromJSON SubscriptionId Source #

JSON Instance for SubscriptionId

ToStripeParam SubscriptionId Source # 
StripeHasParam CreateInvoiceItem SubscriptionId Source # 
StripeHasParam GetUpcomingInvoice SubscriptionId Source # 
StripeHasParam GetInvoiceLineItems SubscriptionId Source # 
StripeHasParam CreateInvoice SubscriptionId Source # 
StripeHasParam GetSubscriptions (EndingBefore SubscriptionId) Source # 
StripeHasParam GetSubscriptions (StartingAfter SubscriptionId) Source #