Copyright | (c) David Johnson 2014 |
---|---|
Maintainer | djohnson.m@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
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
- data CreateCustomer
- createCustomer :: StripeRequest CreateCustomer
- data GetCustomer
- getCustomer :: CustomerId -> StripeRequest GetCustomer
- data UpdateCustomer
- updateCustomer :: CustomerId -> StripeRequest UpdateCustomer
- data DeleteCustomer
- deleteCustomer :: CustomerId -> StripeRequest DeleteCustomer
- data GetCustomers
- getCustomers :: StripeRequest GetCustomers
- newtype AccountBalance = AccountBalance Int
- newtype CardId = CardId Text
- newtype CardNumber = CardNumber Text
- newtype CouponId = CouponId Text
- newtype Created = Created UTCTime
- data Customer
- = Customer {
- customerObject :: Text
- customerCreated :: UTCTime
- customerId :: CustomerId
- customerLiveMode :: Bool
- customerDescription :: Maybe Description
- customerEmail :: Maybe Email
- customerDelinquent :: Bool
- customerSubscriptions :: StripeList Subscription
- customerDiscount :: Maybe Discount
- customerAccountBalance :: Int
- customerCards :: StripeList Card
- customerCurrency :: Maybe Currency
- customerDefaultCard :: Maybe (Expandable CardId)
- customerMetaData :: MetaData
- | DeletedCustomer { }
- = Customer {
- newtype CustomerId = CustomerId Text
- newtype CVC = CVC Text
- newtype Description = Description Text
- newtype Email = Email Text
- newtype EndingBefore a = EndingBefore a
- newtype ExpandParams = ExpandParams {
- getExpandParams :: [Text]
- newtype ExpMonth = ExpMonth Int
- newtype ExpYear = ExpYear Int
- newtype Limit = Limit Int
- newtype MetaData = MetaData [(Text, Text)]
- mkNewCard :: CardNumber -> ExpMonth -> ExpYear -> NewCard
- data NewCard = NewCard {
- newCardCardNumber :: CardNumber
- newCardExpMonth :: ExpMonth
- newCardExpYear :: ExpYear
- newCardCVC :: Maybe CVC
- newCardName :: Maybe Name
- newCardAddressLine1 :: Maybe AddressLine1
- newCardAddressLine2 :: Maybe AddressLine2
- newCardAddressCity :: Maybe AddressCity
- newCardAddressZip :: Maybe AddressZip
- newCardAddressState :: Maybe AddressState
- newCardAddressCountry :: Maybe AddressCountry
- newtype PlanId = PlanId Text
- newtype Quantity = Quantity Int
- newtype StartingAfter a = StartingAfter a
- data StripeDeleteResult = StripeDeleteResult {}
- data StripeList a = StripeList {}
- newtype TokenId = TokenId Text
- newtype TrialEnd = TrialEnd UTCTime
API
data CreateCustomer Source #
Instances
StripeHasParam CreateCustomer Email Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam CreateCustomer Quantity Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam CreateCustomer Description Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam CreateCustomer MetaData Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam CreateCustomer TokenId Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam CreateCustomer CouponId Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam CreateCustomer TrialEnd Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam CreateCustomer PlanId Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam CreateCustomer NewCard Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam CreateCustomer AccountBalance Source # | |
Defined in Web.Stripe.Customer | |
type StripeReturn CreateCustomer Source # | |
Defined in Web.Stripe.Customer |
createCustomer :: StripeRequest CreateCustomer Source #
Create a customer
data GetCustomer Source #
Instances
StripeHasParam GetCustomer ExpandParams Source # | |
Defined in Web.Stripe.Customer | |
type StripeReturn GetCustomer Source # | |
Defined in Web.Stripe.Customer |
:: CustomerId |
|
-> StripeRequest GetCustomer |
Retrieve a customer
data UpdateCustomer Source #
Instances
StripeHasParam UpdateCustomer Email Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam UpdateCustomer Description Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam UpdateCustomer MetaData Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam UpdateCustomer TokenId Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam UpdateCustomer CouponId Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam UpdateCustomer DefaultCard Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam UpdateCustomer NewCard Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam UpdateCustomer AccountBalance Source # | |
Defined in Web.Stripe.Customer | |
type StripeReturn UpdateCustomer Source # | |
Defined in Web.Stripe.Customer |
:: CustomerId |
|
-> StripeRequest UpdateCustomer |
Update a Customer
data DeleteCustomer Source #
Deletes the specified Customer
Instances
type StripeReturn DeleteCustomer Source # | |
Defined in Web.Stripe.Customer |
:: CustomerId | The |
-> StripeRequest DeleteCustomer |
data GetCustomers Source #
Instances
StripeHasParam GetCustomers ExpandParams Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam GetCustomers Limit Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam GetCustomers Created Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam GetCustomers (EndingBefore CustomerId) Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam GetCustomers (StartingAfter CustomerId) Source # | |
Defined in Web.Stripe.Customer | |
type StripeReturn GetCustomers Source # | |
Defined in Web.Stripe.Customer |
getCustomers :: StripeRequest GetCustomers Source #
Retrieve up to 100 customers at a time
Types
newtype AccountBalance Source #
AccountBalance for a Customer
Instances
CardId for a Customer
Instances
newtype CardNumber Source #
Number associated with a Card
Instances
Instances
Instances
Customer
object
Instances
Eq Customer Source # | |
Data Customer Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Customer -> c Customer # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Customer # toConstr :: Customer -> Constr # dataTypeOf :: Customer -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Customer) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Customer) # gmapT :: (forall b. Data b => b -> b) -> Customer -> Customer # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Customer -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Customer -> r # gmapQ :: (forall d. Data d => d -> u) -> Customer -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Customer -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Customer -> m Customer # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Customer -> m Customer # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Customer -> m Customer # | |
Ord Customer Source # | |
Defined in Web.Stripe.Types | |
Read Customer Source # | |
Show Customer Source # | |
FromJSON Customer Source # | JSON Instance for |
newtype CustomerId Source #
CustomerId
for a Customer
Instances
CVC for a Card
Instances
Eq CVC Source # | |
Data CVC Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CVC -> c CVC # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CVC # dataTypeOf :: CVC -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CVC) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CVC) # gmapT :: (forall b. Data b => b -> b) -> CVC -> CVC # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CVC -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CVC -> r # gmapQ :: (forall d. Data d => d -> u) -> CVC -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CVC -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CVC -> m CVC # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CVC -> m CVC # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CVC -> m CVC # | |
Ord CVC Source # | |
Read CVC Source # | |
Show CVC Source # | |
ToStripeParam CVC Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: CVC -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # |
newtype Description Source #
Generic Description for use in constructing API Calls
Instances
Instances
Eq Email Source # | |
Data Email Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Email -> c Email # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Email # dataTypeOf :: Email -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Email) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Email) # gmapT :: (forall b. Data b => b -> b) -> Email -> Email # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Email -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Email -> r # gmapQ :: (forall d. Data d => d -> u) -> Email -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Email -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Email -> m Email # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Email -> m Email # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Email -> m Email # | |
Ord Email Source # | |
Read Email Source # | |
Show Email Source # | |
ToStripeParam Email Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Email -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipient Email Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam CreateRecipient Email Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam UpdateCustomer Email Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam CreateCustomer Email Source # | |
Defined in Web.Stripe.Customer |
newtype EndingBefore a Source #
Pagination Option for StripeList
Instances
newtype ExpandParams Source #
Type of Expansion Parameters for use on Stripe
objects
Instances
Expiration Month for a Card
Instances
Eq ExpMonth Source # | |
Data ExpMonth Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExpMonth -> c ExpMonth # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExpMonth # toConstr :: ExpMonth -> Constr # dataTypeOf :: ExpMonth -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExpMonth) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExpMonth) # gmapT :: (forall b. Data b => b -> b) -> ExpMonth -> ExpMonth # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExpMonth -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExpMonth -> r # gmapQ :: (forall d. Data d => d -> u) -> ExpMonth -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExpMonth -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExpMonth -> m ExpMonth # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpMonth -> m ExpMonth # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpMonth -> m ExpMonth # | |
Ord ExpMonth Source # | |
Defined in Web.Stripe.Types | |
Read ExpMonth Source # | |
Show ExpMonth Source # | |
ToStripeParam ExpMonth Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: ExpMonth -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipientCard ExpMonth Source # | |
Defined in Web.Stripe.Card | |
StripeHasParam UpdateCustomerCard ExpMonth Source # | |
Defined in Web.Stripe.Card |
Expiration Year for a Card
Instances
Eq ExpYear Source # | |
Data ExpYear Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExpYear -> c ExpYear # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExpYear # toConstr :: ExpYear -> Constr # dataTypeOf :: ExpYear -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExpYear) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExpYear) # gmapT :: (forall b. Data b => b -> b) -> ExpYear -> ExpYear # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExpYear -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExpYear -> r # gmapQ :: (forall d. Data d => d -> u) -> ExpYear -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExpYear -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExpYear -> m ExpYear # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpYear -> m ExpYear # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpYear -> m ExpYear # | |
Ord ExpYear Source # | |
Read ExpYear Source # | |
Show ExpYear Source # | |
ToStripeParam ExpYear Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: ExpYear -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipientCard ExpYear Source # | |
Defined in Web.Stripe.Card | |
StripeHasParam UpdateCustomerCard ExpYear Source # | |
Defined in Web.Stripe.Card |
Pagination Option for StripeList
Instances
Type of MetaData for use on Stripe
objects
Instances
mkNewCard :: CardNumber -> ExpMonth -> ExpYear -> NewCard Source #
create a NewCard
with only the required fields
Instances
Instances
Generic Quantity
type to be used with Customer
,
Subscription
and InvoiceLineItem
API requests
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
Instances
TrialEnd
for a Plan