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

Contents

Description

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

{-# LANGUAGE OverloadedStrings #-}
import Web.Stripe
import Web.Stripe.ApplicationFeeRefund

main :: IO ()
main = do
  let config = StripeConfig (StripeKey "secret_key")
  result <- stripe config $ getApplicationFeeRefund (FeeId "fee_id") (RefundId "refund_id")
  case result of
    Right applicationFeeRefund -> print applicationFeeRefund
    Left stripeError           -> print stripeError

Synopsis

API

getApplicationFeeRefund Source

Arguments

:: FeeId

The FeeID associated with the ApplicationFee

-> RefundId

The ReufndId associated with the ApplicationFeeRefund

-> StripeRequest GetApplicationFeeRefund 

Retrieve an existing ApplicationFeeRefund

updateApplicationFeeRefund Source

Arguments

:: FeeId

The FeeID associated with the application

-> RefundId

The RefundId associated with the application

-> StripeRequest UpdateApplicationFeeRefund 

Update an ApplicationFeeRefund for a given Application FeeId and RefundId

getApplicationFeeRefunds Source

Arguments

:: FeeId

The FeeID associated with the application

-> StripeRequest GetApplicationFeeRefunds 

Retrieve a list of all ApplicationFeeRefunds for a given Application FeeId

Types

newtype FeeId Source

FeeId for objects with Fees

Constructors

FeeId 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

newtype ExpandParams Source

Type of Expansion Parameters for use on Stripe objects

Constructors

ExpandParams 

Fields

getExpandParams :: [Text]