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

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

Web.Stripe.Customer

Contents

Description

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

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

main :: IO ()
main = do
  let config = StripeConfig (StripeKey "secret_key")
  result <- stripe config createCustomer
  case result of
    Right customer    -> print customer
    Left  stripeError -> print stripeError

Synopsis

API

getCustomer Source #

Retrieve a customer

getCustomers :: StripeRequest GetCustomers Source #

Retrieve up to 100 customers at a time

Types

newtype AccountBalance Source #

AccountBalance for a Customer

Constructors

AccountBalance Int 

Instances

Eq AccountBalance Source # 
Data AccountBalance Source # 

Methods

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

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

toConstr :: AccountBalance -> Constr #

dataTypeOf :: AccountBalance -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AccountBalance Source # 
Read AccountBalance Source # 
Show AccountBalance Source # 
ToStripeParam AccountBalance Source # 
StripeHasParam UpdateCustomer AccountBalance Source # 
StripeHasParam CreateCustomer AccountBalance Source # 

newtype CardId Source #

CardId for a Customer

Constructors

CardId Text 

Instances

Eq CardId Source # 

Methods

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

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

Data CardId Source # 

Methods

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

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

toConstr :: CardId -> Constr #

dataTypeOf :: CardId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CardId Source # 
Read CardId Source # 
Show CardId Source # 
FromJSON CardId Source #

JSON Instance for CardId

ToStripeParam CardId Source # 
StripeHasParam UpdateSubscription CardId Source # 
StripeHasParam CreateSubscription CardId Source # 
StripeHasParam CreateTransfer CardId Source # 
StripeHasParam UpdateRecipient CardId Source # 
StripeHasParam CreateRecipient CardId Source # 
StripeHasParam GetRecipientCards (EndingBefore CardId) Source # 
StripeHasParam GetRecipientCards (StartingAfter CardId) Source # 
StripeHasParam GetCustomerCards (EndingBefore CardId) Source # 
StripeHasParam GetCustomerCards (StartingAfter CardId) Source # 
type ExpandsTo CardId 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 CouponId Source #

Constructors

CouponId Text 

Instances

Eq CouponId Source # 
Data CouponId Source # 

Methods

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

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

toConstr :: CouponId -> Constr #

dataTypeOf :: CouponId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CouponId Source # 
Read CouponId Source # 
Show CouponId Source # 
ToStripeParam CouponId Source # 
StripeHasParam UpdateSubscription CouponId Source # 
StripeHasParam CreateSubscription CouponId Source # 
StripeHasParam UpdateCustomer CouponId Source # 
StripeHasParam CreateCustomer CouponId Source # 
StripeHasParam GetCoupons (EndingBefore CouponId) Source # 
StripeHasParam GetCoupons (StartingAfter CouponId) 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 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 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 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 # 

mkNewCard :: CardNumber -> ExpMonth -> ExpYear -> NewCard Source #

create a NewCard with only the required fields

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

PlanId for a Plan

Constructors

PlanId Text 

Instances

Eq PlanId Source # 

Methods

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

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

Data PlanId Source # 

Methods

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

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

toConstr :: PlanId -> Constr #

dataTypeOf :: PlanId -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PlanId Source # 
Read PlanId Source # 
Show PlanId Source # 
ToStripeParam PlanId Source # 
StripeHasParam UpdateSubscription PlanId Source # 
StripeHasParam CreateCustomer PlanId Source # 
StripeHasParam GetPlans (EndingBefore PlanId) Source # 
StripeHasParam GetPlans (StartingAfter PlanId) Source # 

newtype Quantity Source #

Generic Quantity type to be used with Customer, Subscription and InvoiceLineItem API requests

Constructors

Quantity Int 

Instances

Eq Quantity Source # 
Data Quantity Source # 

Methods

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

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

toConstr :: Quantity -> Constr #

dataTypeOf :: Quantity -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Quantity Source # 
Read Quantity Source # 
Show Quantity Source # 
ToStripeParam Quantity Source # 
StripeHasParam UpdateSubscription Quantity Source # 
StripeHasParam CreateSubscription Quantity Source # 
StripeHasParam CreateCustomer Quantity 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 StripeDeleteResult Source #

JSON returned from a Stripe deletion request

Constructors

StripeDeleteResult 

Instances

Eq StripeDeleteResult Source # 
Data StripeDeleteResult Source # 

Methods

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

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

toConstr :: StripeDeleteResult -> Constr #

dataTypeOf :: StripeDeleteResult -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord StripeDeleteResult Source # 
Read StripeDeleteResult Source # 
Show StripeDeleteResult Source # 
FromJSON StripeDeleteResult Source #

JSON Instance for StripeDeleteResult

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 # 

newtype TrialEnd Source #

TrialEnd for a Plan

Constructors

TrialEnd UTCTime 

Instances

Eq TrialEnd Source # 
Data TrialEnd Source # 

Methods

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

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

toConstr :: TrialEnd -> Constr #

dataTypeOf :: TrialEnd -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TrialEnd Source # 
Read TrialEnd Source # 
Show TrialEnd Source # 
ToStripeParam TrialEnd Source # 
StripeHasParam UpdateSubscription TrialEnd Source # 
StripeHasParam CreateSubscription TrialEnd Source # 
StripeHasParam CreateCustomer TrialEnd Source #