| Copyright | (c) David Johnson 2014 |
|---|---|
| Maintainer | djohnson.m@gmail.com |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
Web.Stripe.Refund
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
- data CreateRefund
- createRefund :: ChargeId -> StripeRequest CreateRefund
- data GetRefund
- getRefund :: ChargeId -> RefundId -> StripeRequest GetRefund
- data GetRefunds
- getRefunds :: ChargeId -> StripeRequest GetRefunds
- data UpdateRefund
- updateRefund :: ChargeId -> RefundId -> StripeRequest UpdateRefund
- newtype Amount = Amount {}
- data Charge = Charge {
- chargeId :: ChargeId
- chargeObject :: Text
- chargeCreated :: UTCTime
- chargeLiveMode :: Bool
- chargePaid :: Bool
- chargeAmount :: Amount
- chargeCurrency :: Currency
- chargeRefunded :: Bool
- chargeCreditCard :: Card
- chargeCaptured :: Bool
- chargeRefunds :: StripeList Refund
- chargeBalanceTransaction :: Maybe (Expandable TransactionId)
- chargeFailureMessage :: Maybe Text
- chargeFailureCode :: Maybe Text
- chargeAmountRefunded :: Int
- chargeCustomerId :: Maybe (Expandable CustomerId)
- chargeInvoice :: Maybe (Expandable InvoiceId)
- chargeDescription :: Maybe Description
- chargeDispute :: Maybe Dispute
- chargeMetaData :: MetaData
- chargeStatementDescription :: Maybe StatementDescription
- chargeReceiptEmail :: Maybe Text
- chargeReceiptNumber :: Maybe Text
- newtype ChargeId = ChargeId Text
- newtype EndingBefore a = EndingBefore a
- newtype ExpandParams = ExpandParams {
- getExpandParams :: [Text]
- data Refund = Refund {}
- newtype RefundApplicationFee = RefundApplicationFee {}
- data RefundReason
- newtype RefundId = RefundId Text
- data StripeList a = StripeList {}
API
data CreateRefund Source #
Arguments
| :: ChargeId | |
| -> StripeRequest CreateRefund |
create a Refund
Instances
Arguments
| :: ChargeId | |
| -> RefundId | |
| -> StripeRequest GetRefund |
data GetRefunds Source #
Arguments
| :: ChargeId |
|
| -> StripeRequest GetRefunds |
Retrieve a lot of Refunds by ChargeId
data UpdateRefund Source #
Instances
Arguments
| :: ChargeId | |
| -> RefundId | |
| -> StripeRequest UpdateRefund |
Types
Amount representing a monetary value. Stripe represents pennies as whole numbers i.e. 100 = $1
Instances
Charge object in Stripe API
Constructors
Instances
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
newtype RefundApplicationFee Source #
Constructors
| RefundApplicationFee | |
Fields | |
data RefundReason Source #
Constructors
| RefundDuplicate | |
| RefundFraudulent | |
| RefundRequestedByCustomer |
Instances
data StripeList a Source #
Generic handling of Stripe JSON arrays
Constructors
| StripeList | |
Instances
| Eq a => Eq (StripeList a) Source # | |
| Data a => Data (StripeList a) Source # | |
| Ord a => Ord (StripeList a) Source # | |
| Read a => Read (StripeList a) Source # | |
| Show a => Show (StripeList a) Source # | |
| FromJSON a => FromJSON (StripeList a) Source # | JSON Instance for |