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

Contents

Description

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

{-# LANGUAGE OverloadedStrings #-}
import Web.Stripe
import Web.Stripe.Customer
import Web.Stripe.Charge
import Web.Stripe.Refund

main :: IO ()
main = do
  let config = StripeConfig (StripeKey "secret_key")
      credit = CardNumber "4242424242424242"
      em  = ExpMonth 12
      ey  = ExpYear 2015
      cvc = CVC "123"
      cardinfo = (mkNewCard credit em ey) { newCardCVC = Just cvc }
  result <- stripe config $ createCustomer -&- cardinfo
  case result of
    (Left stripeError) -> print stripeError
    (Right (Customer { customerId = cid })) -> do
      result <- stripe config $ createCharge (Amount 100) USD -&- cid
      case result of
        (Left stripeError) -> print stripeError
        (Right (Charge { chargeId   = chid })) -> do
          result <- stripe config $ createRefund chid
          case result of
            (Left stripeError) -> print stripeError
            (Right refund)     -> print refund

Synopsis

API

createRefund Source

Arguments

:: ChargeId

ChargeId associated with the Charge to be refunded

-> StripeRequest CreateRefund 

create a Refund

getRefund Source

Arguments

:: ChargeId

ChargeId associated with the Refund to be retrieved

-> RefundId

RefundId associated with the Refund to be retrieved

-> StripeRequest GetRefund 

Retrieve a Refund by ChargeId and RefundId

getRefunds Source

Arguments

:: ChargeId

ChargeId associated with the Refunds to get

-> StripeRequest GetRefunds 

Retrieve a lot of Refunds by ChargeId

updateRefund Source

Arguments

:: ChargeId

ChargeId associated with the Charge to be updated

-> RefundId

RefundId associated with the Refund to be retrieved

-> StripeRequest UpdateRefund 

Update a Refund by ChargeId and RefundId

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