| Copyright | (c) David Johnson 2014 | 
|---|---|
| Maintainer | djohnson.m@gmail.com | 
| Stability | experimental | 
| Portability | POSIX | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Web.Stripe.Subscription
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
- data CreateSubscription
- createSubscription :: CustomerId -> PlanId -> StripeRequest CreateSubscription
- data GetSubscription
- getSubscription :: CustomerId -> SubscriptionId -> StripeRequest GetSubscription
- data UpdateSubscription
- updateSubscription :: CustomerId -> SubscriptionId -> StripeRequest UpdateSubscription
- data CancelSubscription
- cancelSubscription :: CustomerId -> SubscriptionId -> StripeRequest CancelSubscription
- data GetSubscriptions
- getSubscriptions :: StripeRequest GetSubscriptions
- data GetSubscriptionsByCustomerId
- getSubscriptionsByCustomerId :: CustomerId -> StripeRequest GetSubscriptionsByCustomerId
- newtype ApplicationFeePercent = ApplicationFeePercent Double
- newtype AtPeriodEnd = AtPeriodEnd Bool
- newtype CustomerId = CustomerId Text
- newtype CouponId = CouponId Text
- data Coupon = Coupon {- couponId :: CouponId
- couponCreated :: UTCTime
- couponPercentOff :: Maybe Int
- couponAmountOff :: Maybe Int
- couponCurrency :: Maybe Currency
- couponLiveMode :: Bool
- couponDuration :: Duration
- couponRedeemBy :: Maybe UTCTime
- couponMaxRedemptions :: Maybe Int
- couponTimesRedeemed :: Maybe Int
- couponDurationInMonths :: Maybe Int
- couponValid :: Bool
- couponMetaData :: MetaData
 
- newtype EndingBefore a = EndingBefore a
- newtype ExpandParams = ExpandParams {- getExpandParams :: [Text]
 
- newtype Limit = Limit Int
- newtype MetaData = MetaData [(Text, Text)]
- newtype PlanId = PlanId Text
- newtype Prorate = Prorate Bool
- newtype Quantity = Quantity Int
- newtype StartingAfter a = StartingAfter a
- data StripeList a = StripeList {}
- data Subscription = Subscription {- subscriptionId :: SubscriptionId
- subscriptionPlan :: Plan
- subscriptionObject :: Text
- subscriptionStart :: UTCTime
- subscriptionStatus :: SubscriptionStatus
- subscriptionCustomerId :: Expandable CustomerId
- subscriptionCancelAtPeriodEnd :: Bool
- subscriptionCurrentPeriodStart :: UTCTime
- subscriptionCurrentPeriodEnd :: UTCTime
- subscriptionEndedAt :: Maybe UTCTime
- subscriptionTrialStart :: Maybe UTCTime
- subscriptionTrialEnd :: Maybe UTCTime
- subscriptionCanceledAt :: Maybe UTCTime
- subscriptionQuantity :: Quantity
- subscriptionApplicationFeePercent :: Maybe Double
- subscriptionDiscount :: Maybe Discount
- subscriptionMetaData :: MetaData
- subscriptionTaxPercent :: Maybe Double
 
- newtype SubscriptionId = SubscriptionId {}
- data SubscriptionStatus
- newtype TaxPercent = TaxPercent Double
- newtype TrialEnd = TrialEnd UTCTime
API
data CreateSubscription Source #
Instances
Arguments
| :: CustomerId | The  | 
| -> PlanId | The  | 
| -> StripeRequest CreateSubscription | 
Create a Subscription by CustomerId and PlanId
data GetSubscription Source #
Instances
| StripeHasParam GetSubscription ExpandParams Source # | |
| Defined in Web.Stripe.Subscription | |
| type StripeReturn GetSubscription Source # | |
| Defined in Web.Stripe.Subscription | |
Arguments
| :: CustomerId | The  | 
| -> SubscriptionId | The  | 
| -> StripeRequest GetSubscription | 
Retrieve a Subscription by CustomerId and SubscriptionId
data UpdateSubscription Source #
Instances
Arguments
| :: CustomerId | The  | 
| -> SubscriptionId | The  | 
| -> StripeRequest UpdateSubscription | 
Update a Subscription by CustomerId and SubscriptionId
data CancelSubscription Source #
Instances
| StripeHasParam CancelSubscription AtPeriodEnd Source # | |
| Defined in Web.Stripe.Subscription | |
| type StripeReturn CancelSubscription Source # | |
| Defined in Web.Stripe.Subscription | |
Arguments
| :: CustomerId | The  | 
| -> SubscriptionId | The  | 
| -> StripeRequest CancelSubscription | 
Delete a Subscription by CustomerId and SubscriptionId
data GetSubscriptions Source #
Instances
| StripeHasParam GetSubscriptions ExpandParams Source # | |
| Defined in Web.Stripe.Subscription | |
| StripeHasParam GetSubscriptions Limit Source # | |
| Defined in Web.Stripe.Subscription | |
| StripeHasParam GetSubscriptions (EndingBefore SubscriptionId) Source # | |
| Defined in Web.Stripe.Subscription | |
| StripeHasParam GetSubscriptions (StartingAfter SubscriptionId) Source # | |
| Defined in Web.Stripe.Subscription | |
| type StripeReturn GetSubscriptions Source # | |
| Defined in Web.Stripe.Subscription | |
getSubscriptions :: StripeRequest GetSubscriptions Source #
Retrieve all active Subscriptions
data GetSubscriptionsByCustomerId Source #
Instances
getSubscriptionsByCustomerId :: CustomerId -> StripeRequest GetSubscriptionsByCustomerId Source #
Retrieve a customer's Subscriptions
Types
newtype ApplicationFeePercent Source #
ApplicationFeePercent
Constructors
| ApplicationFeePercent Double | 
Instances
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
newtype CustomerId Source #
CustomerId for a Customer
Constructors
| CustomerId Text | 
Instances
Instances
Coupon Object
Constructors
| Coupon | |
| Fields 
 | |
Instances
| Eq Coupon Source # | |
| Data Coupon Source # | |
| Defined in Web.Stripe.Types 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  | 
newtype EndingBefore a Source #
Pagination Option for StripeList
Constructors
| EndingBefore a | 
Instances
newtype ExpandParams Source #
Type of Expansion Parameters for use on Stripe objects
Constructors
| ExpandParams | |
| Fields 
 | |
Instances
Pagination Option for StripeList
Instances
Type of MetaData for use on Stripe objects
Instances
Instances
| Eq PlanId Source # | |
| Data PlanId Source # | |
| Defined in Web.Stripe.Types 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 # | |
| Defined in Web.Stripe.StripeRequest Methods toStripeParam :: PlanId -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
| StripeHasParam UpdateSubscription PlanId Source # | |
| Defined in Web.Stripe.Subscription | |
| StripeHasParam CreateCustomer PlanId Source # | |
| Defined in Web.Stripe.Customer | |
| StripeHasParam GetPlans (EndingBefore PlanId) Source # | |
| Defined in Web.Stripe.Plan | |
| StripeHasParam GetPlans (StartingAfter PlanId) Source # | |
| Defined in Web.Stripe.Plan | |
Prorate
Instances
| Eq Prorate Source # | |
| Data Prorate Source # | |
| Defined in Web.Stripe.Types 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 # | |
| Defined in Web.Stripe.StripeRequest Methods toStripeParam :: Prorate -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
| StripeHasParam UpdateSubscription Prorate Source # | |
| Defined in Web.Stripe.Subscription | |
| StripeHasParam CreateSubscription Prorate Source # | |
| Defined in Web.Stripe.Subscription | |
Generic Quantity type to be used with Customer,
 Subscription and InvoiceLineItem API requests
Instances
newtype StartingAfter a Source #
Pagination Option for StripeList
Constructors
| StartingAfter a | 
Instances
data StripeList a Source #
Generic handling of Stripe JSON arrays
Constructors
| StripeList | |
Instances
| Eq a => Eq (StripeList a) Source # | |
| Defined in Web.Stripe.Types | |
| Data a => Data (StripeList a) Source # | |
| Defined in Web.Stripe.Types 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 # | |
| Defined in Web.Stripe.Types Methods compare :: StripeList a -> StripeList a -> Ordering # (<) :: StripeList a -> StripeList a -> Bool # (<=) :: StripeList a -> StripeList a -> Bool # (>) :: StripeList a -> StripeList a -> Bool # (>=) :: StripeList a -> StripeList a -> Bool # max :: StripeList a -> StripeList a -> StripeList a # min :: StripeList a -> StripeList a -> StripeList a # | |
| Read a => Read (StripeList a) Source # | |
| Defined in Web.Stripe.Types Methods readsPrec :: Int -> ReadS (StripeList a) # readList :: ReadS [StripeList a] # readPrec :: ReadPrec (StripeList a) # readListPrec :: ReadPrec [StripeList a] # | |
| Show a => Show (StripeList a) Source # | |
| Defined in Web.Stripe.Types Methods showsPrec :: Int -> StripeList a -> ShowS # show :: StripeList a -> String # showList :: [StripeList a] -> ShowS # | |
| FromJSON a => FromJSON (StripeList a) Source # | JSON Instance for  | 
| Defined in Web.Stripe.Types Methods parseJSON :: Value -> Parser (StripeList a) # parseJSONList :: Value -> Parser [StripeList a] # | |
data Subscription Source #
Subscription Object
Constructors
Instances
newtype SubscriptionId Source #
SubscriptionId for a Subscription
Constructors
| SubscriptionId | |
| Fields | |
Instances
data SubscriptionStatus Source #
Status of a Subscription
Instances
newtype TaxPercent Source #
TaxPercent for a Subscription
Constructors
| TaxPercent Double | 
Instances
TrialEnd for a Plan