| Copyright | (c) David Johnson 2014 |
|---|---|
| Maintainer | djohnson.m@gmail.com |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
Web.Stripe.Token
Description
https://stripe.com/docs/api#tokens
{-# LANGUAGE OverloadedStrings #-}
import Web.Stripe
import Web.Stripe.Token
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 $ createCardToken (Just cardinfo)
case result of
Right token -> print token
Left stripeError -> print stripeError
- data CreateCardToken
- createCardToken :: Maybe NewCard -> StripeRequest CreateCardToken
- data CreateBankAccountToken
- createBankAccountToken :: Maybe NewBankAccount -> StripeRequest CreateBankAccountToken
- data GetCardToken
- getCardToken :: TokenId -> StripeRequest GetCardToken
- data GetBankAccountToken
- getBankAccountToken :: TokenId -> StripeRequest GetBankAccountToken
- data Account = Account {
- accountId :: AccountId
- accountEmail :: Email
- accountStatementDescriptor :: Maybe Description
- accountDisplayName :: Maybe Text
- accountTimeZone :: Text
- accountDetailsSubmitted :: Bool
- accountChargeEnabled :: Bool
- accountTransferEnabled :: Bool
- accountCurrenciesSupported :: [Currency]
- accountDefaultCurrency :: Currency
- accountCountry :: Text
- accountObject :: Text
- accountBusinessName :: Maybe Text
- accountBusinessURL :: Maybe Text
- accountBusinessLogo :: Maybe Text
- accountSupportPhone :: Maybe Text
- newtype AccountNumber = AccountNumber Text
- data BankAccount = BankAccount {}
- data Card = Card {
- cardId :: CardId
- cardObject :: Text
- cardLastFour :: Text
- cardBrand :: Brand
- cardFunding :: Text
- cardExpMonth :: ExpMonth
- cardExpYear :: ExpYear
- cardFingerprint :: Text
- cardCountry :: Text
- cardName :: Maybe Name
- cardAddressLine1 :: Maybe AddressLine1
- cardAddressLine2 :: Maybe AddressLine2
- cardAddressCity :: Maybe AddressCity
- cardAddressState :: Maybe AddressState
- cardAddressZip :: Maybe AddressZip
- cardAddressCountry :: Maybe AddressCountry
- cardCVCCheck :: Maybe Text
- cardAddressLine1Check :: Maybe Text
- cardAddressZipCheck :: Maybe Text
- cardCustomerId :: Maybe (Expandable CustomerId)
- newtype CardNumber = CardNumber Text
- newtype Country = Country Text
- newtype CustomerId = CustomerId Text
- newtype CVC = CVC Text
- newtype ExpMonth = ExpMonth Int
- newtype ExpYear = ExpYear Int
- data NewBankAccount = NewBankAccount {}
- mkNewCard :: CardNumber -> ExpMonth -> ExpYear -> NewCard
- data NewCard = NewCard {
- newCardCardNumber :: CardNumber
- newCardExpMonth :: ExpMonth
- newCardExpYear :: ExpYear
- newCardCVC :: Maybe CVC
- newCardName :: Maybe Name
- newCardAddressLine1 :: Maybe AddressLine1
- newCardAddressLine2 :: Maybe AddressLine2
- newCardAddressCity :: Maybe AddressCity
- newCardAddressZip :: Maybe AddressZip
- newCardAddressState :: Maybe AddressState
- newCardAddressCountry :: Maybe AddressCountry
- newtype RoutingNumber = RoutingNumber Text
- data Token a = Token {
- tokenId :: TokenId
- tokenLiveMode :: Bool
- tokenCreated :: UTCTime
- tokenUsed :: Bool
- tokenObject :: Text
- tokenType :: TokenType
- tokenData :: a
- newtype TokenId = TokenId Text
- data TokenType
API
data CreateCardToken Source #
Instances
Arguments
| :: Maybe NewCard | optional |
| -> StripeRequest CreateCardToken |
data CreateBankAccountToken Source #
Instances
createBankAccountToken Source #
Arguments
| :: Maybe NewBankAccount | option |
| -> StripeRequest CreateBankAccountToken |
Create a Token for a specific BankAccount
data GetCardToken Source #
Instances
| type StripeReturn GetCardToken Source # | |
Arguments
| :: TokenId | |
| -> StripeRequest GetCardToken |
data GetBankAccountToken Source #
Instances
Arguments
| :: TokenId | The |
| -> StripeRequest GetBankAccountToken |
Types
Account Object
Constructors
data BankAccount Source #
BankAccount Object
Constructors
| BankAccount | |
Instances
| Eq BankAccount Source # | |
| Data BankAccount Source # | |
| Ord BankAccount Source # | |
| Read BankAccount Source # | |
| Show BankAccount Source # | |
| FromJSON BankAccount Source # |
|
Card Object
Constructors
| Card | |
Fields
| |
Country
newtype CustomerId Source #
CustomerId for a Customer
Constructors
| CustomerId Text |
Instances
CVC for a Card
Expiration Month for a Card
Expiration Year for a Card
mkNewCard :: CardNumber -> ExpMonth -> ExpYear -> NewCard Source #
create a NewCard with only the required fields
Constructors
Instances
Token Object
Constructors
| Token | |
Fields
| |
Instances