stripe-core-2.5.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

data GetRefund Source #

Instances
StripeHasParam GetRefund ExpandParams Source # 
Instance details

Defined in Web.Stripe.Refund

type StripeReturn GetRefund Source # 
Instance details

Defined in Web.Stripe.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 Amount Source #

Amount representing a monetary value. Stripe represents pennies as whole numbers i.e. 100 = $1

Constructors

Amount 

Fields

Instances
Eq Amount Source # 
Instance details

Defined in Web.Stripe.Types

Methods

(==) :: Amount -> Amount -> Bool #

(/=) :: Amount -> Amount -> Bool #

Data Amount Source # 
Instance details

Defined in Web.Stripe.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Amount -> c Amount #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Amount #

toConstr :: Amount -> Constr #

dataTypeOf :: Amount -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Amount) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Amount) #

gmapT :: (forall b. Data b => b -> b) -> Amount -> Amount #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Amount -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Amount -> r #

gmapQ :: (forall d. Data d => d -> u) -> Amount -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Amount -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Amount -> m Amount #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Amount -> m Amount #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Amount -> m Amount #

Ord Amount Source # 
Instance details

Defined in Web.Stripe.Types

Read Amount Source # 
Instance details

Defined in Web.Stripe.Types

Show Amount Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam Amount Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam CreateRefund Amount Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam UpdateInvoiceItem Amount Source # 
Instance details

Defined in Web.Stripe.InvoiceItem

StripeHasParam CaptureCharge Amount Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam CreateApplicationFeeRefund Amount Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund

data Charge Source #

Charge object in Stripe API

Instances
Eq Charge Source # 
Instance details

Defined in Web.Stripe.Types

Methods

(==) :: Charge -> Charge -> Bool #

(/=) :: Charge -> Charge -> Bool #

Data Charge Source # 
Instance details

Defined in Web.Stripe.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Charge -> c Charge #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Charge #

toConstr :: Charge -> Constr #

dataTypeOf :: Charge -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Charge) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Charge) #

gmapT :: (forall b. Data b => b -> b) -> Charge -> Charge #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Charge -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Charge -> r #

gmapQ :: (forall d. Data d => d -> u) -> Charge -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Charge -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Charge -> m Charge #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Charge -> m Charge #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Charge -> m Charge #

Ord Charge Source # 
Instance details

Defined in Web.Stripe.Types

Read Charge Source # 
Instance details

Defined in Web.Stripe.Types

Show Charge Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON Charge Source #

JSON Instance for Charge

Instance details

Defined in Web.Stripe.Types

newtype ChargeId Source #

ChargeId associated with a Charge

Constructors

ChargeId Text 
Instances
Eq ChargeId Source # 
Instance details

Defined in Web.Stripe.Types

Data ChargeId Source # 
Instance details

Defined in Web.Stripe.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ChargeId -> c ChargeId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ChargeId #

toConstr :: ChargeId -> Constr #

dataTypeOf :: ChargeId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ChargeId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ChargeId) #

gmapT :: (forall b. Data b => b -> b) -> ChargeId -> ChargeId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ChargeId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ChargeId -> r #

gmapQ :: (forall d. Data d => d -> u) -> ChargeId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ChargeId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ChargeId -> m ChargeId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ChargeId -> m ChargeId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ChargeId -> m ChargeId #

Ord ChargeId Source # 
Instance details

Defined in Web.Stripe.Types

Read ChargeId Source # 
Instance details

Defined in Web.Stripe.Types

Show ChargeId Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON ChargeId Source #

JSON Instance for ChargeId

Instance details

Defined in Web.Stripe.Types

ToStripeParam ChargeId Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam GetApplicationFees ChargeId Source # 
Instance details

Defined in Web.Stripe.ApplicationFee

StripeHasParam GetCharges (EndingBefore ChargeId) Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam GetCharges (StartingAfter ChargeId) Source # 
Instance details

Defined in Web.Stripe.Charge

type ExpandsTo ChargeId Source # 
Instance details

Defined in Web.Stripe.Types

newtype EndingBefore a Source #

Pagination Option for StripeList

Constructors

EndingBefore a 
Instances
StripeHasParam GetTransfers (EndingBefore TransferId) Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam GetSubscriptionsByCustomerId (EndingBefore SubscriptionId) Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam GetSubscriptions (EndingBefore SubscriptionId) Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam GetRefunds (EndingBefore RefundId) Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam GetRecipients (EndingBefore RecipientId) Source # 
Instance details

Defined in Web.Stripe.Recipient

StripeHasParam GetPlans (EndingBefore PlanId) Source # 
Instance details

Defined in Web.Stripe.Plan

StripeHasParam GetInvoiceItems (EndingBefore InvoiceItemId) Source # 
Instance details

Defined in Web.Stripe.InvoiceItem

StripeHasParam GetInvoiceLineItems (EndingBefore InvoiceLineItemId) Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam GetInvoices (EndingBefore InvoiceId) Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam GetEvents (EndingBefore EventId) Source # 
Instance details

Defined in Web.Stripe.Event

StripeHasParam GetCustomers (EndingBefore CustomerId) Source # 
Instance details

Defined in Web.Stripe.Customer

StripeHasParam GetCoupons (EndingBefore CouponId) Source # 
Instance details

Defined in Web.Stripe.Coupon

StripeHasParam GetCharges (EndingBefore ChargeId) Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam GetRecipientCards (EndingBefore CardId) Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetCustomerCards (EndingBefore CardId) Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetBalanceTransactionHistory (EndingBefore TransactionId) Source # 
Instance details

Defined in Web.Stripe.Balance

StripeHasParam GetApplicationFeeRefunds (EndingBefore RefundId) Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund

StripeHasParam GetApplicationFees (EndingBefore ApplicationFeeId) Source # 
Instance details

Defined in Web.Stripe.ApplicationFee

Eq a => Eq (EndingBefore a) Source # 
Instance details

Defined in Web.Stripe.Types

Data a => Data (EndingBefore a) Source # 
Instance details

Defined in Web.Stripe.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EndingBefore a -> c (EndingBefore a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (EndingBefore a) #

toConstr :: EndingBefore a -> Constr #

dataTypeOf :: EndingBefore a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (EndingBefore a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (EndingBefore a)) #

gmapT :: (forall b. Data b => b -> b) -> EndingBefore a -> EndingBefore a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EndingBefore a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EndingBefore a -> r #

gmapQ :: (forall d. Data d => d -> u) -> EndingBefore a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> EndingBefore a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> EndingBefore a -> m (EndingBefore a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EndingBefore a -> m (EndingBefore a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EndingBefore a -> m (EndingBefore a) #

Ord a => Ord (EndingBefore a) Source # 
Instance details

Defined in Web.Stripe.Types

Read a => Read (EndingBefore a) Source # 
Instance details

Defined in Web.Stripe.Types

Show a => Show (EndingBefore a) Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam param => ToStripeParam (EndingBefore param) Source # 
Instance details

Defined in Web.Stripe.StripeRequest

newtype ExpandParams Source #

Type of Expansion Parameters for use on Stripe objects

Constructors

ExpandParams 

Fields

Instances
Eq ExpandParams Source # 
Instance details

Defined in Web.Stripe.Types

Data ExpandParams Source # 
Instance details

Defined in Web.Stripe.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExpandParams -> c ExpandParams #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExpandParams #

toConstr :: ExpandParams -> Constr #

dataTypeOf :: ExpandParams -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExpandParams) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExpandParams) #

gmapT :: (forall b. Data b => b -> b) -> ExpandParams -> ExpandParams #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExpandParams -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExpandParams -> r #

gmapQ :: (forall d. Data d => d -> u) -> ExpandParams -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExpandParams -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExpandParams -> m ExpandParams #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpandParams -> m ExpandParams #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpandParams -> m ExpandParams #

Ord ExpandParams Source # 
Instance details

Defined in Web.Stripe.Types

Read ExpandParams Source # 
Instance details

Defined in Web.Stripe.Types

Show ExpandParams Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam ExpandParams Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam GetTransfers ExpandParams Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam GetTransfer ExpandParams Source # 
Instance details

Defined in Web.Stripe.Transfer

StripeHasParam GetSubscriptionsByCustomerId ExpandParams Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam GetSubscriptions ExpandParams Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam GetSubscription ExpandParams Source # 
Instance details

Defined in Web.Stripe.Subscription

StripeHasParam GetRefunds ExpandParams Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam GetRefund ExpandParams Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam GetRecipients ExpandParams Source # 
Instance details

Defined in Web.Stripe.Recipient

StripeHasParam GetRecipient ExpandParams Source # 
Instance details

Defined in Web.Stripe.Recipient

StripeHasParam GetInvoiceItems ExpandParams Source # 
Instance details

Defined in Web.Stripe.InvoiceItem

StripeHasParam GetInvoiceItem ExpandParams Source # 
Instance details

Defined in Web.Stripe.InvoiceItem

StripeHasParam GetInvoices ExpandParams Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam GetInvoice ExpandParams Source # 
Instance details

Defined in Web.Stripe.Invoice

StripeHasParam GetCustomers ExpandParams Source # 
Instance details

Defined in Web.Stripe.Customer

StripeHasParam GetCustomer ExpandParams Source # 
Instance details

Defined in Web.Stripe.Customer

StripeHasParam GetCharges ExpandParams Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam GetCharge ExpandParams Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam CreateCharge ExpandParams Source # 
Instance details

Defined in Web.Stripe.Charge

StripeHasParam GetRecipientCards ExpandParams Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetCustomerCards ExpandParams Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetRecipientCard ExpandParams Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetCustomerCard ExpandParams Source # 
Instance details

Defined in Web.Stripe.Card

StripeHasParam GetBalanceTransaction ExpandParams Source # 
Instance details

Defined in Web.Stripe.Balance

StripeHasParam GetApplicationFeeRefunds ExpandParams Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund

StripeHasParam GetApplicationFeeRefund ExpandParams Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund

StripeHasParam GetApplicationFees ExpandParams Source # 
Instance details

Defined in Web.Stripe.ApplicationFee

StripeHasParam GetApplicationFee ExpandParams Source # 
Instance details

Defined in Web.Stripe.ApplicationFee

data Refund Source #

Refund Object

Instances
Eq Refund Source # 
Instance details

Defined in Web.Stripe.Types

Methods

(==) :: Refund -> Refund -> Bool #

(/=) :: Refund -> Refund -> Bool #

Data Refund Source # 
Instance details

Defined in Web.Stripe.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Refund -> c Refund #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Refund #

toConstr :: Refund -> Constr #

dataTypeOf :: Refund -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Refund) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Refund) #

gmapT :: (forall b. Data b => b -> b) -> Refund -> Refund #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Refund -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Refund -> r #

gmapQ :: (forall d. Data d => d -> u) -> Refund -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Refund -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Refund -> m Refund #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Refund -> m Refund #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Refund -> m Refund #

Ord Refund Source # 
Instance details

Defined in Web.Stripe.Types

Read Refund Source # 
Instance details

Defined in Web.Stripe.Types

Show Refund Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON Refund Source #

JSON Instance for Refund

Instance details

Defined in Web.Stripe.Types

newtype RefundApplicationFee Source #

Instances
Eq RefundApplicationFee Source # 
Instance details

Defined in Web.Stripe.Types

Data RefundApplicationFee Source # 
Instance details

Defined in Web.Stripe.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RefundApplicationFee -> c RefundApplicationFee #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RefundApplicationFee #

toConstr :: RefundApplicationFee -> Constr #

dataTypeOf :: RefundApplicationFee -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RefundApplicationFee) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RefundApplicationFee) #

gmapT :: (forall b. Data b => b -> b) -> RefundApplicationFee -> RefundApplicationFee #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RefundApplicationFee -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RefundApplicationFee -> r #

gmapQ :: (forall d. Data d => d -> u) -> RefundApplicationFee -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RefundApplicationFee -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RefundApplicationFee -> m RefundApplicationFee #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RefundApplicationFee -> m RefundApplicationFee #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RefundApplicationFee -> m RefundApplicationFee #

Ord RefundApplicationFee Source # 
Instance details

Defined in Web.Stripe.Types

Read RefundApplicationFee Source # 
Instance details

Defined in Web.Stripe.Types

Show RefundApplicationFee Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam RefundApplicationFee Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam CreateRefund RefundApplicationFee Source # 
Instance details

Defined in Web.Stripe.Refund

data RefundReason Source #

Instances
Eq RefundReason Source # 
Instance details

Defined in Web.Stripe.Types

Data RefundReason Source # 
Instance details

Defined in Web.Stripe.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RefundReason -> c RefundReason #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RefundReason #

toConstr :: RefundReason -> Constr #

dataTypeOf :: RefundReason -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RefundReason) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RefundReason) #

gmapT :: (forall b. Data b => b -> b) -> RefundReason -> RefundReason #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RefundReason -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RefundReason -> r #

gmapQ :: (forall d. Data d => d -> u) -> RefundReason -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RefundReason -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RefundReason -> m RefundReason #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RefundReason -> m RefundReason #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RefundReason -> m RefundReason #

Ord RefundReason Source # 
Instance details

Defined in Web.Stripe.Types

Read RefundReason Source # 
Instance details

Defined in Web.Stripe.Types

Show RefundReason Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam RefundReason Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam CreateRefund RefundReason Source # 
Instance details

Defined in Web.Stripe.Refund

newtype RefundId Source #

Constructors

RefundId Text 
Instances
Eq RefundId Source # 
Instance details

Defined in Web.Stripe.Types

Data RefundId Source # 
Instance details

Defined in Web.Stripe.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RefundId -> c RefundId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RefundId #

toConstr :: RefundId -> Constr #

dataTypeOf :: RefundId -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RefundId) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RefundId) #

gmapT :: (forall b. Data b => b -> b) -> RefundId -> RefundId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RefundId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RefundId -> r #

gmapQ :: (forall d. Data d => d -> u) -> RefundId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RefundId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RefundId -> m RefundId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RefundId -> m RefundId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RefundId -> m RefundId #

Ord RefundId Source # 
Instance details

Defined in Web.Stripe.Types

Read RefundId Source # 
Instance details

Defined in Web.Stripe.Types

Show RefundId Source # 
Instance details

Defined in Web.Stripe.Types

ToStripeParam RefundId Source # 
Instance details

Defined in Web.Stripe.StripeRequest

StripeHasParam GetRefunds (EndingBefore RefundId) Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam GetRefunds (StartingAfter RefundId) Source # 
Instance details

Defined in Web.Stripe.Refund

StripeHasParam GetApplicationFeeRefunds (EndingBefore RefundId) Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund

StripeHasParam GetApplicationFeeRefunds (StartingAfter RefundId) Source # 
Instance details

Defined in Web.Stripe.ApplicationFeeRefund

data StripeList a Source #

Generic handling of Stripe JSON arrays

Constructors

StripeList 

Fields

Instances
Eq a => Eq (StripeList a) Source # 
Instance details

Defined in Web.Stripe.Types

Methods

(==) :: StripeList a -> StripeList a -> Bool #

(/=) :: StripeList a -> StripeList a -> Bool #

Data a => Data (StripeList a) Source # 
Instance details

Defined in Web.Stripe.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StripeList a -> c (StripeList a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (StripeList a) #

toConstr :: StripeList a -> Constr #

dataTypeOf :: StripeList a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (StripeList a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (StripeList a)) #

gmapT :: (forall b. Data b => b -> b) -> StripeList a -> StripeList a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StripeList a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StripeList a -> r #

gmapQ :: (forall d. Data d => d -> u) -> StripeList a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StripeList a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StripeList a -> m (StripeList a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StripeList a -> m (StripeList a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StripeList a -> m (StripeList a) #

Ord a => Ord (StripeList a) Source # 
Instance details

Defined in Web.Stripe.Types

Read a => Read (StripeList a) Source # 
Instance details

Defined in Web.Stripe.Types

Show a => Show (StripeList a) Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON a => FromJSON (StripeList a) Source #

JSON Instance for StripeList

Instance details

Defined in Web.Stripe.Types