stripe-core-2.0.0: 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 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 

newtype ExpandParams Source

Type of Expansion Parameters for use on Stripe objects

Constructors

ExpandParams 

Fields

getExpandParams :: [Text]
 

data StripeList a Source

Generic handling of Stripe JSON arrays

Constructors

StripeList 

Fields

list :: [a]
 
stripeUrl :: Text
 
object :: Text
 
totalCount :: Maybe Int
 
hasMore :: Bool
 

Instances