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

Contents

Description

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

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

main :: IO ()
main = do
  let config = StripeConfig (SecretKey "secret_key")
  result <- stripe config createCustomer
  case result of
    (Left stripeError) -> print stripeError
    (Right (Customer { customerId = cid })) ->
      do result <- stripe config $
           createPlan (PlanId "planid") (Amount 20) USD Day (PlanName "testplan")
         case result of
           (Left stripeError) -> print stripeError
           (Right (Plan {})) ->
             do result <- stripe config $
                  createInvoiceItem cid (Amount 100) USD
                case result of
                  (Left stripeError)  -> print stripeError
                  (Right invoiceItem) ->
                     do result <- stripe config $ createInvoice cid
                        case result of
                          (Left  stripeError) -> print stripeError
                          (Right invoice)     -> print invoice

Synopsis

API

createInvoice Source

The Invoice to be created for a Customer

getUpcomingInvoice Source

Arguments

:: CustomerId

The InvoiceId of the Invoice to retrieve

-> StripeRequest GetUpcomingInvoice 

Retrieve an upcoming Invoice for a Customer by CustomerId

Types

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