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.Subscription

Contents

Description

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

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

main :: IO ()
main = do
  let config = StripeConfig (StripeKey "secret_key")
  result <- stripe config $ createCustomer
  case result of
    (Left stripeError) -> print stripeError
    (Right (Customer { customerId = cid })) -> do
      result <- stripe config $ createPlan (PlanId "free plan")
                                           (Amount 0)
                                           USD
                                           Month
                                           (PlanName "sample plan")
      case result of
        (Left stripeError) -> print stripeError
        (Right (Plan { planId = pid })) -> do
           result <- stripe config $ createSubscription cid pid
           case result of
             (Left stripeError)   -> print stripeError
             (Right subscription) -> print subscription

Synopsis

API

createSubscription Source #

Arguments

:: CustomerId

The CustomerId upon which to create the Subscription

-> PlanId

The PlanId to associate the Subscription with

-> StripeRequest CreateSubscription 

Types

newtype ApplicationFeePercent Source #

ApplicationFeePercent

Instances

Eq ApplicationFeePercent Source # 
Data ApplicationFeePercent Source # 

Methods

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

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

toConstr :: ApplicationFeePercent -> Constr #

dataTypeOf :: ApplicationFeePercent -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ApplicationFeePercent Source # 
Read ApplicationFeePercent Source # 
Show ApplicationFeePercent Source # 
ToStripeParam ApplicationFeePercent Source # 
StripeHasParam UpdateSubscription ApplicationFeePercent Source # 
StripeHasParam CreateSubscription ApplicationFeePercent Source # 

newtype AtPeriodEnd Source #

A flag that if set to true will delay the cancellation of the subscription until the end of the current period.

Constructors

AtPeriodEnd Bool 

Instances

Eq AtPeriodEnd Source # 
Data AtPeriodEnd Source # 

Methods

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

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

toConstr :: AtPeriodEnd -> Constr #

dataTypeOf :: AtPeriodEnd -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AtPeriodEnd Source # 
Read AtPeriodEnd Source # 
Show AtPeriodEnd Source # 
ToStripeParam AtPeriodEnd Source # 
StripeHasParam CancelSubscription AtPeriodEnd 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 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 # 

data Coupon Source #

Coupon Object

Instances

Eq Coupon Source # 

Methods

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

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

Data Coupon Source # 

Methods

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

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

toConstr :: Coupon -> Constr #

dataTypeOf :: Coupon -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Coupon Source # 
Read Coupon Source # 
Show Coupon Source # 
FromJSON Coupon Source #

JSON Instance for Coupon

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

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

Prorate

Constructors

Prorate Bool 

Instances

Eq Prorate Source # 

Methods

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

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

Data Prorate Source # 

Methods

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

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

toConstr :: Prorate -> Constr #

dataTypeOf :: Prorate -> DataType #

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

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

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

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

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

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

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

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

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

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

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

data Subscription Source #

Subscription Object

Instances

Eq Subscription Source # 
Data Subscription Source # 

Methods

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

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

toConstr :: Subscription -> Constr #

dataTypeOf :: Subscription -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Subscription Source # 
Read Subscription Source # 
Show Subscription Source # 
FromJSON Subscription Source #

JSON Instance for Subscription

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

data SubscriptionStatus Source #

Status of a Subscription

Instances

Eq SubscriptionStatus Source # 
Data SubscriptionStatus Source # 

Methods

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

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

toConstr :: SubscriptionStatus -> Constr #

dataTypeOf :: SubscriptionStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SubscriptionStatus Source # 
Read SubscriptionStatus Source # 
Show SubscriptionStatus Source # 
FromJSON SubscriptionStatus Source #

JSON Instance for SubscriptionStatus

newtype TaxPercent Source #

Constructors

TaxPercent Double 

Instances

Eq TaxPercent Source # 
Data TaxPercent Source # 

Methods

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

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

toConstr :: TaxPercent -> Constr #

dataTypeOf :: TaxPercent -> DataType #

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

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

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

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

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

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

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

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

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

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

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