| Copyright | (c) David Johnson, 2014 |
|---|---|
| Maintainer | djohnson.m@gmail.com |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
Web.Stripe.ApplicationFee
Description
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
- 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
Arguments
| :: FeeId | The |
| -> StripeRequest GetApplicationFee |
ApplicationFee retrieval
data GetApplicationFees Source #
Instances
getApplicationFees :: StripeRequest GetApplicationFees Source #
ApplicationFees retrieval
Types
data ApplicationFee Source #
ApplicationFee Object
Constructors
Instances
newtype ApplicationFeeId Source #
Constructors
| ApplicationFeeId Text |
Instances
Instances
data ConnectApp Source #
Connect Application
Constructors
| ConnectApp | |
Fields
| |
Instances
| Eq ConnectApp Source # | |
| Data ConnectApp Source # | |
| Ord ConnectApp Source # | |
| Read ConnectApp Source # | |
| Show ConnectApp Source # | |
| FromJSON ConnectApp Source # | Connect Application JSON instance |
Instances
newtype EndingBefore a Source #
Pagination Option for StripeList
Constructors
| EndingBefore a |
Instances
FeeId for objects with Fees
Pagination Option for StripeList
Instances
newtype StartingAfter a Source #
Pagination Option for StripeList
Constructors
| StartingAfter a |
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 |
newtype ExpandParams Source #
Type of Expansion Parameters for use on Stripe objects
Constructors
| ExpandParams | |
Fields
| |
Instances