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

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

Web.Stripe.Client

Description

 
Synopsis

Documentation

handleStream Source #

Arguments

:: (Value -> Result a)

function to decode JSON value

-> Int

HTTP response code

-> Result Value

result of attempting to decode body

-> Either StripeError a 

handleStream

This function is used by the backends such as stripe-http-client to decode the results of an API request.

parseFail Source #

Arguments

:: String

error message

-> Either StripeError a 

lift a parser error to be a StripeError

attemptDecode Source #

Arguments

:: Int

HTTP status code

-> Bool 

check the HTTP status code and see if it is one we can deal with or not

unknownCode :: Either StripeError a Source #

StripeError to return when we don't know what to do with the received HTTP status code.

data StripeConfig Source #

Stripe config

Constructors

StripeConfig 

Fields

Instances
Eq StripeConfig Source # 
Instance details

Defined in Web.Stripe.Client

Data StripeConfig Source # 
Instance details

Defined in Web.Stripe.Client

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StripeConfig -> c StripeConfig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StripeConfig #

toConstr :: StripeConfig -> Constr #

dataTypeOf :: StripeConfig -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StripeConfig) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StripeConfig) #

gmapT :: (forall b. Data b => b -> b) -> StripeConfig -> StripeConfig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StripeConfig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StripeConfig -> r #

gmapQ :: (forall d. Data d => d -> u) -> StripeConfig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StripeConfig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StripeConfig -> m StripeConfig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StripeConfig -> m StripeConfig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StripeConfig -> m StripeConfig #

Ord StripeConfig Source # 
Instance details

Defined in Web.Stripe.Client

Read StripeConfig Source # 
Instance details

Defined in Web.Stripe.Client

Show StripeConfig Source # 
Instance details

Defined in Web.Stripe.Client

newtype StripeKey Source #

Stripe secret key

Constructors

StripeKey 
Instances
Eq StripeKey Source # 
Instance details

Defined in Web.Stripe.Client

Data StripeKey Source # 
Instance details

Defined in Web.Stripe.Client

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StripeKey -> c StripeKey #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StripeKey #

toConstr :: StripeKey -> Constr #

dataTypeOf :: StripeKey -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StripeKey) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StripeKey) #

gmapT :: (forall b. Data b => b -> b) -> StripeKey -> StripeKey #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StripeKey -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StripeKey -> r #

gmapQ :: (forall d. Data d => d -> u) -> StripeKey -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StripeKey -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StripeKey -> m StripeKey #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StripeKey -> m StripeKey #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StripeKey -> m StripeKey #

Ord StripeKey Source # 
Instance details

Defined in Web.Stripe.Client

Read StripeKey Source # 
Instance details

Defined in Web.Stripe.Client

Show StripeKey Source # 
Instance details

Defined in Web.Stripe.Client

data APIVersion Source #

API Version

Constructors

V20141007

Stripe API Version for this package release

Instances
Eq APIVersion Source # 
Instance details

Defined in Web.Stripe.Client

Data APIVersion Source # 
Instance details

Defined in Web.Stripe.Client

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> APIVersion -> c APIVersion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c APIVersion #

toConstr :: APIVersion -> Constr #

dataTypeOf :: APIVersion -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c APIVersion) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c APIVersion) #

gmapT :: (forall b. Data b => b -> b) -> APIVersion -> APIVersion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> APIVersion -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> APIVersion -> r #

gmapQ :: (forall d. Data d => d -> u) -> APIVersion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> APIVersion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> APIVersion -> m APIVersion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> APIVersion -> m APIVersion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> APIVersion -> m APIVersion #

Ord APIVersion Source # 
Instance details

Defined in Web.Stripe.Client

Read APIVersion Source # 
Instance details

Defined in Web.Stripe.Client

Show APIVersion Source # 
Instance details

Defined in Web.Stripe.Client