{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
module Web.Stripe.ApplicationFeeRefund
(
CreateApplicationFeeRefund
, createApplicationFeeRefund
, GetApplicationFeeRefund
, getApplicationFeeRefund
, UpdateApplicationFeeRefund
, updateApplicationFeeRefund
, GetApplicationFeeRefunds
, getApplicationFeeRefunds
, FeeId (..)
, RefundId (..)
, ApplicationFee (..)
, ApplicationFeeRefund (..)
, StripeList (..)
, EndingBefore (..)
, StartingAfter (..)
, Limit (..)
, ExpandParams (..)
, MetaData (..)
, Amount (..)
) where
import Web.Stripe.StripeRequest (Method (GET, POST), StripeHasParam,
StripeRequest (..), StripeReturn,
mkStripeRequest)
import Web.Stripe.Util ((</>))
import Web.Stripe.Types (Amount(..), ApplicationFee (..),
ApplicationFeeRefund (..),
EndingBefore(..), ExpandParams(..),
FeeId (..), Limit(..), MetaData(..),
RefundId (..), StartingAfter(..),
StripeList (..))
createApplicationFeeRefund
:: FeeId
-> StripeRequest CreateApplicationFeeRefund
createApplicationFeeRefund
(FeeId feeid)
= request
where request = mkStripeRequest POST url params
url = "application_fees" </> feeid </> "refunds"
params = []
data CreateApplicationFeeRefund
type instance StripeReturn CreateApplicationFeeRefund = ApplicationFeeRefund
instance StripeHasParam CreateApplicationFeeRefund Amount
instance StripeHasParam CreateApplicationFeeRefund MetaData
getApplicationFeeRefund
:: FeeId
-> RefundId
-> StripeRequest GetApplicationFeeRefund
getApplicationFeeRefund
(FeeId feeid)
(RefundId refundid)
= request
where request = mkStripeRequest GET url params
url = "application_fees" </> feeid </> "refunds" </> refundid
params = []
data GetApplicationFeeRefund
type instance StripeReturn GetApplicationFeeRefund = ApplicationFeeRefund
instance StripeHasParam GetApplicationFeeRefund ExpandParams
updateApplicationFeeRefund
:: FeeId
-> RefundId
-> StripeRequest UpdateApplicationFeeRefund
updateApplicationFeeRefund
(FeeId feeid)
(RefundId refundid)
= request
where
request = mkStripeRequest GET url params
url = "application_fees" </> feeid </> "refunds" </> refundid
params = []
data UpdateApplicationFeeRefund
type instance StripeReturn UpdateApplicationFeeRefund = ApplicationFeeRefund
instance StripeHasParam UpdateApplicationFeeRefund MetaData
getApplicationFeeRefunds
:: FeeId
-> StripeRequest GetApplicationFeeRefunds
getApplicationFeeRefunds
(FeeId feeid) = request
where
request = mkStripeRequest GET url params
url = "application_fees" </> feeid </> "refunds"
params = []
data GetApplicationFeeRefunds
type instance StripeReturn GetApplicationFeeRefunds = (StripeList ApplicationFeeRefund)
instance StripeHasParam GetApplicationFeeRefunds ExpandParams
instance StripeHasParam GetApplicationFeeRefunds (EndingBefore RefundId)
instance StripeHasParam GetApplicationFeeRefunds Limit
instance StripeHasParam GetApplicationFeeRefunds (StartingAfter RefundId)