Copyright | (c) David Johnson 2014 |
---|---|
Maintainer | djohnson.m@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
https://stripe.com/docs/api#recipients
{-# LANGUAGE OverloadedStrings #-} import Web.Stripe import Web.Stripe.Recipient main :: IO () main = do let config = StripeConfig (StripeKey "secret_key") result <- stripe config $ createRecipient (Name "simon marlow") Individual case result of Right recipient -> print recipient Left stripeError -> print stripeError
Synopsis
- data CreateRecipient
- createRecipient :: Name -> RecipientType -> StripeRequest CreateRecipient
- data GetRecipient
- getRecipient :: RecipientId -> StripeRequest GetRecipient
- data UpdateRecipient
- updateRecipient :: RecipientId -> StripeRequest UpdateRecipient
- data DeleteRecipient
- deleteRecipient :: RecipientId -> StripeRequest DeleteRecipient
- data GetRecipients
- getRecipients :: StripeRequest GetRecipients
- newtype AccountNumber = AccountNumber Text
- newtype AddressCity = AddressCity Text
- newtype AddressCountry = AddressCountry Text
- newtype AddressLine1 = AddressLine1 Text
- newtype AddressLine2 = AddressLine2 Text
- newtype AddressState = AddressState Text
- newtype AddressZip = AddressZip Text
- data BankAccount = BankAccount {}
- newtype BankAccountId = BankAccountId Text
- data BankAccountStatus
- newtype CardNumber = CardNumber Text
- newtype Country = Country Text
- newtype CVC = CVC Text
- data DefaultCard = DefaultCard {}
- newtype Description = Description Text
- newtype ExpandParams = ExpandParams {
- getExpandParams :: [Text]
- newtype ExpMonth = ExpMonth Int
- newtype ExpYear = ExpYear Int
- newtype Email = Email Text
- newtype IsVerified = IsVerified {
- getVerified :: Bool
- newtype Limit = Limit Int
- newtype MetaData = MetaData [(Text, Text)]
- newtype Name = Name {}
- data NewBankAccount = NewBankAccount {}
- 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
- data Recipient
- = Recipient {
- recipientId :: RecipientId
- recipientObject :: Text
- recipientCreated :: UTCTime
- recipientLiveMode :: Bool
- recipientType :: RecipientType
- recipientDescription :: Maybe Description
- recipientEmail :: Maybe Email
- recipientName :: Name
- recipientVerified :: Bool
- recipientActiveAccount :: Maybe BankAccount
- recipientCards :: StripeList RecipientCard
- recipientDefaultCard :: Maybe (Expandable RecipientCardId)
- | DeletedRecipient { }
- = Recipient {
- newtype RecipientId = RecipientId Text
- data RecipientType
- newtype RoutingNumber = RoutingNumber Text
- data StripeDeleteResult = StripeDeleteResult {}
- newtype TaxID = TaxID {}
- newtype TokenId = TokenId Text
API
data CreateRecipient Source #
Instances
StripeHasParam CreateRecipient Email Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam CreateRecipient Description Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam CreateRecipient MetaData Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam CreateRecipient TokenId Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam CreateRecipient TaxID Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam CreateRecipient NewBankAccount Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam CreateRecipient NewCard Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam CreateRecipient CardId Source # | |
Defined in Web.Stripe.Recipient | |
type StripeReturn CreateRecipient Source # | |
Defined in Web.Stripe.Recipient |
Base Request for issues create Recipient
requests
data GetRecipient Source #
Instances
StripeHasParam GetRecipient ExpandParams Source # | |
Defined in Web.Stripe.Recipient | |
type StripeReturn GetRecipient Source # | |
Defined in Web.Stripe.Recipient |
:: RecipientId | The |
-> StripeRequest GetRecipient |
Retrieve a Recipient
data UpdateRecipient Source #
Instances
StripeHasParam UpdateRecipient Email Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam UpdateRecipient Description Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam UpdateRecipient Name Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam UpdateRecipient MetaData Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam UpdateRecipient TokenId Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam UpdateRecipient TaxID Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam UpdateRecipient NewBankAccount Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam UpdateRecipient DefaultCard Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam UpdateRecipient NewCard Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam UpdateRecipient CardId Source # | |
Defined in Web.Stripe.Recipient | |
type StripeReturn UpdateRecipient Source # | |
Defined in Web.Stripe.Recipient |
:: RecipientId |
|
-> StripeRequest UpdateRecipient |
Update Recipient
data DeleteRecipient Source #
Instances
type StripeReturn DeleteRecipient Source # | |
Defined in Web.Stripe.Recipient |
:: RecipientId |
|
-> StripeRequest DeleteRecipient |
Delete a Recipient
data GetRecipients Source #
Instances
StripeHasParam GetRecipients ExpandParams Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam GetRecipients Limit Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam GetRecipients IsVerified Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam GetRecipients (EndingBefore RecipientId) Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam GetRecipients (StartingAfter RecipientId) Source # | |
Defined in Web.Stripe.Recipient | |
type StripeReturn GetRecipients Source # | |
Defined in Web.Stripe.Recipient |
getRecipients :: StripeRequest GetRecipients Source #
Retrieve multiple Recipient
s
Types
newtype AccountNumber Source #
Account Number of a Bank Account
Instances
newtype AddressCity Source #
City address for a Card
Instances
newtype AddressCountry Source #
Country address for a Card
Instances
newtype AddressLine1 Source #
Address Line One for a Card
Instances
newtype AddressLine2 Source #
Address Line Two for a Card
Instances
newtype AddressState Source #
Address State for a Card
Instances
newtype AddressZip Source #
Address Zip Code for a Card
Instances
data BankAccount Source #
BankAccount
Object
Instances
newtype BankAccountId Source #
Instances
data BankAccountStatus Source #
BankAccountStatus
Object
Instances
newtype CardNumber Source #
Number associated with a Card
Instances
Country
Instances
Eq Country Source # | |
Data Country Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Country -> c Country # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Country # toConstr :: Country -> Constr # dataTypeOf :: Country -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Country) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Country) # gmapT :: (forall b. Data b => b -> b) -> Country -> Country # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Country -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Country -> r # gmapQ :: (forall d. Data d => d -> u) -> Country -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Country -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Country -> m Country # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Country -> m Country # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Country -> m Country # | |
Ord Country Source # | |
Read Country Source # | |
Show Country Source # | |
CVC for a Card
Instances
Eq CVC Source # | |
Data CVC Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CVC -> c CVC # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CVC # dataTypeOf :: CVC -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CVC) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CVC) # gmapT :: (forall b. Data b => b -> b) -> CVC -> CVC # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CVC -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CVC -> r # gmapQ :: (forall d. Data d => d -> u) -> CVC -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CVC -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CVC -> m CVC # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CVC -> m CVC # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CVC -> m CVC # | |
Ord CVC Source # | |
Read CVC Source # | |
Show CVC Source # | |
ToStripeParam CVC Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: CVC -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # |
data DefaultCard Source #
set the DefaultCard
Instances
newtype Description Source #
Generic Description for use in constructing API Calls
Instances
newtype ExpandParams Source #
Type of Expansion Parameters for use on Stripe
objects
Instances
Expiration Month for a Card
Instances
Eq ExpMonth Source # | |
Data ExpMonth Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExpMonth -> c ExpMonth # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExpMonth # toConstr :: ExpMonth -> Constr # dataTypeOf :: ExpMonth -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExpMonth) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExpMonth) # gmapT :: (forall b. Data b => b -> b) -> ExpMonth -> ExpMonth # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExpMonth -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExpMonth -> r # gmapQ :: (forall d. Data d => d -> u) -> ExpMonth -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExpMonth -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExpMonth -> m ExpMonth # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpMonth -> m ExpMonth # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpMonth -> m ExpMonth # | |
Ord ExpMonth Source # | |
Defined in Web.Stripe.Types | |
Read ExpMonth Source # | |
Show ExpMonth Source # | |
ToStripeParam ExpMonth Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: ExpMonth -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipientCard ExpMonth Source # | |
Defined in Web.Stripe.Card | |
StripeHasParam UpdateCustomerCard ExpMonth Source # | |
Defined in Web.Stripe.Card |
Expiration Year for a Card
Instances
Eq ExpYear Source # | |
Data ExpYear Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExpYear -> c ExpYear # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExpYear # toConstr :: ExpYear -> Constr # dataTypeOf :: ExpYear -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExpYear) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExpYear) # gmapT :: (forall b. Data b => b -> b) -> ExpYear -> ExpYear # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExpYear -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExpYear -> r # gmapQ :: (forall d. Data d => d -> u) -> ExpYear -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ExpYear -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExpYear -> m ExpYear # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpYear -> m ExpYear # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpYear -> m ExpYear # | |
Ord ExpYear Source # | |
Read ExpYear Source # | |
Show ExpYear Source # | |
ToStripeParam ExpYear Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: ExpYear -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipientCard ExpYear Source # | |
Defined in Web.Stripe.Card | |
StripeHasParam UpdateCustomerCard ExpYear Source # | |
Defined in Web.Stripe.Card |
Instances
Eq Email Source # | |
Data Email Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Email -> c Email # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Email # dataTypeOf :: Email -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Email) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Email) # gmapT :: (forall b. Data b => b -> b) -> Email -> Email # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Email -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Email -> r # gmapQ :: (forall d. Data d => d -> u) -> Email -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Email -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Email -> m Email # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Email -> m Email # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Email -> m Email # | |
Ord Email Source # | |
Read Email Source # | |
Show Email Source # | |
ToStripeParam Email Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Email -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipient Email Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam CreateRecipient Email Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam UpdateCustomer Email Source # | |
Defined in Web.Stripe.Customer | |
StripeHasParam CreateCustomer Email Source # | |
Defined in Web.Stripe.Customer |
newtype IsVerified Source #
IsVerified
Recipients
Instances
Pagination Option for StripeList
Instances
Type of MetaData for use on Stripe
objects
Instances
a cardholder's full name
Instances
Eq Name Source # | |
Data Name Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name # dataTypeOf :: Name -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) # gmapT :: (forall b. Data b => b -> b) -> Name -> Name # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # | |
Ord Name Source # | |
Read Name Source # | |
Show Name Source # | |
FromJSON Name Source # | |
ToStripeParam Name Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: Name -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipient Name Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam UpdateRecipientCard Name Source # | |
Defined in Web.Stripe.Card | |
StripeHasParam UpdateCustomerCard Name Source # | |
Defined in Web.Stripe.Card |
data NewBankAccount Source #
create a new BankAccount
Instances
Instances
Recipient Object
Instances
Eq Recipient Source # | |
Data Recipient Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Recipient -> c Recipient # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Recipient # toConstr :: Recipient -> Constr # dataTypeOf :: Recipient -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Recipient) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Recipient) # gmapT :: (forall b. Data b => b -> b) -> Recipient -> Recipient # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Recipient -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Recipient -> r # gmapQ :: (forall d. Data d => d -> u) -> Recipient -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Recipient -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Recipient -> m Recipient # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Recipient -> m Recipient # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Recipient -> m Recipient # | |
Ord Recipient Source # | |
Defined in Web.Stripe.Types | |
Read Recipient Source # | |
Show Recipient Source # | |
FromJSON Recipient Source # | JSON Instance for |
newtype RecipientId Source #
RecipientId
for a Recipient
Instances
data RecipientType Source #
Type of Recipient
Instances
newtype RoutingNumber Source #
Routing Number for Bank Account
Instances
data StripeDeleteResult Source #
JSON returned from a Stripe
deletion request
Instances
Instances
Eq TaxID Source # | |
Data TaxID Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TaxID -> c TaxID # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TaxID # dataTypeOf :: TaxID -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TaxID) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TaxID) # gmapT :: (forall b. Data b => b -> b) -> TaxID -> TaxID # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TaxID -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TaxID -> r # gmapQ :: (forall d. Data d => d -> u) -> TaxID -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TaxID -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TaxID -> m TaxID # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TaxID -> m TaxID # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TaxID -> m TaxID # | |
Ord TaxID Source # | |
Read TaxID Source # | |
Show TaxID Source # | |
ToStripeParam TaxID Source # | |
Defined in Web.Stripe.StripeRequest toStripeParam :: TaxID -> [(ByteString, ByteString)] -> [(ByteString, ByteString)] Source # | |
StripeHasParam UpdateRecipient TaxID Source # | |
Defined in Web.Stripe.Recipient | |
StripeHasParam CreateRecipient TaxID Source # | |
Defined in Web.Stripe.Recipient |