Copyright | (c) David Johnson 2014 |
---|---|
Maintainer | djohnson.m@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
https://stripe.com/docs/api#account
{-# LANGUAGE OverloadedStrings #-} import Web.Stripe import Web.Stripe.Account main :: IO () main = do let config = StripeConfig (StripeKey "secret_key") result <- stripe config getAccountDetails case result of Right account -> print account Left stripeError -> print stripeError
Synopsis
- data GetAccountDetails
- getAccountDetails :: StripeRequest GetAccountDetails
- 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 AccountId = AccountId Text
API
data GetAccountDetails Source #
Retrieve the object that represents your Stripe account
Instances
type StripeReturn GetAccountDetails Source # | |
Defined in Web.Stripe.Account |
Types
Account
Object
Instances
Eq Account Source # | |
Data Account Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Account -> c Account # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Account # toConstr :: Account -> Constr # dataTypeOf :: Account -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Account) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Account) # gmapT :: (forall b. Data b => b -> b) -> Account -> Account # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Account -> r # gmapQ :: (forall d. Data d => d -> u) -> Account -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Account -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Account -> m Account # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Account -> m Account # | |
Ord Account Source # | |
Read Account Source # | |
Show Account Source # | |
FromJSON Account Source # | JSON Instance for |
Instances
Eq AccountId Source # | |
Data AccountId Source # | |
Defined in Web.Stripe.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AccountId -> c AccountId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AccountId # toConstr :: AccountId -> Constr # dataTypeOf :: AccountId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AccountId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AccountId) # gmapT :: (forall b. Data b => b -> b) -> AccountId -> AccountId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AccountId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AccountId -> r # gmapQ :: (forall d. Data d => d -> u) -> AccountId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AccountId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AccountId -> m AccountId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountId -> m AccountId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AccountId -> m AccountId # | |
Ord AccountId Source # | |
Defined in Web.Stripe.Types | |
Read AccountId Source # | |
Show AccountId Source # | |
FromJSON AccountId Source # | JSON Instance for |
type ExpandsTo AccountId Source # | |
Defined in Web.Stripe.Types |