Copyright | (c) David Johnson 2014 |
---|---|
Maintainer | djohnson.m@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
https://stripe.com/docs/api#application_fees
{-# LANGUAGE OverloadedStrings #-} import Web.Stripe import Web.Stripe.ApplicationFee main :: IO () main = do let config = StripeConfig (StripeKey "secret_key") result <- stripe config $ getApplicationFee (FeeId "fee_4xtEGZhPNDEt3w") case result of Right applicationFee -> print applicationFee Left stripeError -> print stripeError
Synopsis
- data GetApplicationFee
- getApplicationFee :: FeeId -> StripeRequest GetApplicationFee
- data GetApplicationFees
- getApplicationFees :: StripeRequest GetApplicationFees
- newtype ApplicationId = ApplicationId 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
- newtype ApplicationFeeId = ApplicationFeeId Text
- newtype ChargeId = ChargeId Text
- data ConnectApp = ConnectApp {}
- newtype Created = Created UTCTime
- newtype EndingBefore a = EndingBefore a
- newtype FeeId = FeeId Text
- newtype Limit = Limit Int
- newtype StartingAfter a = StartingAfter a
- data StripeList a = StripeList {}
- newtype ExpandParams = ExpandParams {
- getExpandParams :: [Text]
API
data GetApplicationFee Source #
Instances
StripeHasParam GetApplicationFee ExpandParams Source # | |
Defined in Web.Stripe.ApplicationFee | |
type StripeReturn GetApplicationFee Source # | |
Defined in Web.Stripe.ApplicationFee |
:: FeeId | The |
-> StripeRequest GetApplicationFee |
ApplicationFee
retrieval
data GetApplicationFees Source #
Instances
getApplicationFees :: StripeRequest GetApplicationFees Source #
ApplicationFee
s retrieval
Types
newtype ApplicationId Source #
ApplicationId
object
Instances
data ApplicationFee Source #
ApplicationFee Object
Instances
newtype ApplicationFeeId Source #
Instances
Instances
data ConnectApp Source #
Connect Application
Instances
Instances
newtype EndingBefore a Source #
Pagination Option for StripeList
Instances
FeeId
for objects with Fees
Instances
Eq FeeId Source # | |
Data FeeId Source # | |
Defined in Web.Stripe.Types 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 # | |
Pagination Option for StripeList
Instances
newtype StartingAfter a Source #
Pagination Option for StripeList
Instances
data StripeList a Source #
Generic handling of Stripe JSON arrays
Instances
newtype ExpandParams Source #
Type of Expansion Parameters for use on Stripe
objects