stripe-core-2.4.1: Stripe API for Haskell - Pure Core

Copyright(c) David Johnson 2014
Maintainerdjohnson.m@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Web.Stripe.Account

Contents

Description

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

API

data GetAccountDetails Source #

Retrieve the object that represents your Stripe account

Types

data Account Source #

Account Object

Instances
Eq Account Source # 
Instance details

Defined in Web.Stripe.Types

Methods

(==) :: Account -> Account -> Bool #

(/=) :: Account -> Account -> Bool #

Data Account Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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 # 
Instance details

Defined in Web.Stripe.Types

Read Account Source # 
Instance details

Defined in Web.Stripe.Types

Show Account Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON Account Source #

JSON Instance for Account

Instance details

Defined in Web.Stripe.Types

newtype AccountId Source #

Constructors

AccountId Text 
Instances
Eq AccountId Source # 
Instance details

Defined in Web.Stripe.Types

Data AccountId Source # 
Instance details

Defined in Web.Stripe.Types

Methods

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 # 
Instance details

Defined in Web.Stripe.Types

Read AccountId Source # 
Instance details

Defined in Web.Stripe.Types

Show AccountId Source # 
Instance details

Defined in Web.Stripe.Types

FromJSON AccountId Source #

JSON Instance for AccountId

Instance details

Defined in Web.Stripe.Types

type ExpandsTo AccountId Source # 
Instance details

Defined in Web.Stripe.Types