Copyright | (c) David Johnson 2014 |
---|---|
Maintainer | djohnson.m@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Web.Stripe.ApplicationFeeRefund
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
- data CreateApplicationFeeRefund
- createApplicationFeeRefund :: FeeId -> StripeRequest CreateApplicationFeeRefund
- data GetApplicationFeeRefund
- getApplicationFeeRefund :: FeeId -> RefundId -> StripeRequest GetApplicationFeeRefund
- data UpdateApplicationFeeRefund
- updateApplicationFeeRefund :: FeeId -> RefundId -> StripeRequest UpdateApplicationFeeRefund
- data GetApplicationFeeRefunds
- getApplicationFeeRefunds :: FeeId -> StripeRequest GetApplicationFeeRefunds
- newtype FeeId = FeeId Text
- newtype RefundId = RefundId Text
- data ApplicationFee = ApplicationFee {
- applicationFeeId :: ApplicationFeeId
- applicationFeeObjecet :: Text
- applicationFeeCreated :: UTCTime
- applicationFeeLiveMode :: Bool
- applicationFeeAmount :: Int
- applicationFeeCurrency :: Currency
- applicationFeeRefunded :: Bool
- applicationFeeAmountRefunded :: Int
- applicationFeeRefunds :: StripeList Refund
- applicationFeeBalanceTransaction :: Expandable TransactionId
- applicationFeeAccountId :: Expandable AccountId
- applicationFeeApplicationId :: ApplicationId
- applicationFeeChargeId :: Expandable ChargeId
- applicationFeeMetaData :: MetaData
- data ApplicationFeeRefund = ApplicationFeeRefund {
- applicationFeeRefundId :: RefundId
- applicationFeeRefundAmount :: Int
- applicationFeeRefundCurrency :: Currency
- applicationFeeRefundCreated :: UTCTime
- applicationFeeRefundObject :: Text
- applicationFeeRefundBalanceTransaction :: Maybe (Expandable TransactionId)
- applicationFeeRefundFee :: FeeId
- applicationFeeRefundMetaData :: MetaData
- data StripeList a = StripeList {}
- newtype EndingBefore a = EndingBefore a
- newtype StartingAfter a = StartingAfter a
- newtype Limit = Limit Int
- newtype ExpandParams = ExpandParams {
- getExpandParams :: [Text]
- newtype MetaData = MetaData [(Text, Text)]
- newtype Amount = Amount {}
API
createApplicationFeeRefund Source #
Arguments
:: FeeId | The |
-> StripeRequest CreateApplicationFeeRefund |
Create a new ApplicationFeeRefund
data GetApplicationFeeRefund Source #
Instances
StripeHasParam GetApplicationFeeRefund ExpandParams Source # | |
Defined in Web.Stripe.ApplicationFeeRefund | |
type StripeReturn GetApplicationFeeRefund Source # | |
getApplicationFeeRefund Source #
Arguments
:: FeeId | The |
-> RefundId | The |
-> StripeRequest GetApplicationFeeRefund |
Retrieve an existing ApplicationFeeRefund
data UpdateApplicationFeeRefund Source #
Instances
StripeHasParam UpdateApplicationFeeRefund MetaData Source # | |
Defined in Web.Stripe.ApplicationFeeRefund | |
type StripeReturn UpdateApplicationFeeRefund Source # | |
updateApplicationFeeRefund Source #
Arguments
:: FeeId | The |
-> RefundId | The |
-> StripeRequest UpdateApplicationFeeRefund |
Update an ApplicationFeeRefund
for a given Application FeeId
and RefundId
data GetApplicationFeeRefunds Source #
Instances
getApplicationFeeRefunds Source #
Arguments
:: FeeId | The |
-> StripeRequest GetApplicationFeeRefunds |
Retrieve a list of all ApplicationFeeRefund
s for a given Application FeeId
Types
FeeId
for objects with Fees
Instances
Eq FeeId Source # | |
Data FeeId Source # | |
Defined in Web.Stripe.Types Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FeeId -> c FeeId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FeeId # dataTypeOf :: FeeId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FeeId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FeeId) # gmapT :: (forall b. Data b => b -> b) -> FeeId -> FeeId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FeeId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FeeId -> r # gmapQ :: (forall d. Data d => d -> u) -> FeeId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FeeId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FeeId -> m FeeId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FeeId -> m FeeId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FeeId -> m FeeId # | |
Ord FeeId Source # | |
Read FeeId Source # | |
Show FeeId Source # | |
Instances
data ApplicationFee Source #
ApplicationFee Object
Constructors
Instances
data ApplicationFeeRefund Source #
Application Fee Refunds
Constructors
Instances
data StripeList a Source #
Generic handling of Stripe JSON arrays
Constructors
StripeList | |
Instances
Eq a => Eq (StripeList a) Source # | |
Defined in Web.Stripe.Types | |
Data a => Data (StripeList a) Source # | |
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 # | |
Defined in Web.Stripe.Types Methods compare :: StripeList a -> StripeList a -> Ordering # (<) :: StripeList a -> StripeList a -> Bool # (<=) :: StripeList a -> StripeList a -> Bool # (>) :: StripeList a -> StripeList a -> Bool # (>=) :: StripeList a -> StripeList a -> Bool # max :: StripeList a -> StripeList a -> StripeList a # min :: StripeList a -> StripeList a -> StripeList a # | |
Read a => Read (StripeList a) Source # | |
Defined in Web.Stripe.Types Methods readsPrec :: Int -> ReadS (StripeList a) # readList :: ReadS [StripeList a] # readPrec :: ReadPrec (StripeList a) # readListPrec :: ReadPrec [StripeList a] # | |
Show a => Show (StripeList a) Source # | |
Defined in Web.Stripe.Types Methods showsPrec :: Int -> StripeList a -> ShowS # show :: StripeList a -> String # showList :: [StripeList a] -> ShowS # | |
FromJSON a => FromJSON (StripeList a) Source # | JSON Instance for |
Defined in Web.Stripe.Types Methods parseJSON :: Value -> Parser (StripeList a) # parseJSONList :: Value -> Parser [StripeList a] # |
newtype EndingBefore a Source #
Pagination Option for StripeList
Constructors
EndingBefore a |
Instances
newtype StartingAfter a Source #
Pagination Option for StripeList
Constructors
StartingAfter a |
Instances
Pagination Option for StripeList
Instances
newtype ExpandParams Source #
Type of Expansion Parameters for use on Stripe
objects
Constructors
ExpandParams | |
Fields
|
Instances
Type of MetaData for use on Stripe
objects
Instances
Amount representing a monetary value. Stripe represents pennies as whole numbers i.e. 100 = $1