Copyright | (c) David Johnson 2014 |
---|---|
Maintainer | djohnson.m@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- module Web.Stripe.StripeRequest
- module Web.Stripe.Error
- module Web.Stripe.Util
- handleStream :: (Value -> Result a) -> Int -> Result Value -> Either StripeError a
- parseFail :: String -> Either StripeError a
- attemptDecode :: Int -> Bool
- unknownCode :: Either StripeError a
- defaultEndpoint :: Endpoint
- data Endpoint = Endpoint {}
- data Protocol
- data StripeConfig = StripeConfig {}
- newtype StripeKey = StripeKey {}
- data APIVersion = V20141007
Documentation
module Web.Stripe.StripeRequest
module Web.Stripe.Error
module Web.Stripe.Util
:: (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.
:: String | error message |
-> Either StripeError a |
lift a parser error to be a StripeError
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.
Stripe endpoint, useful for mocking
Instances
Eq Endpoint Source # | |
Data Endpoint Source # | |
Defined in Web.Stripe.Client gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Endpoint -> c Endpoint # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Endpoint # toConstr :: Endpoint -> Constr # dataTypeOf :: Endpoint -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Endpoint) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Endpoint) # gmapT :: (forall b. Data b => b -> b) -> Endpoint -> Endpoint # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Endpoint -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Endpoint -> r # gmapQ :: (forall d. Data d => d -> u) -> Endpoint -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Endpoint -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Endpoint -> m Endpoint # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Endpoint -> m Endpoint # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Endpoint -> m Endpoint # | |
Ord Endpoint Source # | |
Defined in Web.Stripe.Client | |
Read Endpoint Source # | |
Show Endpoint Source # | |
Endpoint Protocol
Instances
Eq Protocol Source # | |
Data Protocol Source # | |
Defined in Web.Stripe.Client gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Protocol -> c Protocol # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Protocol # toConstr :: Protocol -> Constr # dataTypeOf :: Protocol -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Protocol) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Protocol) # gmapT :: (forall b. Data b => b -> b) -> Protocol -> Protocol # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Protocol -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Protocol -> r # gmapQ :: (forall d. Data d => d -> u) -> Protocol -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Protocol -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Protocol -> m Protocol # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Protocol -> m Protocol # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Protocol -> m Protocol # | |
Ord Protocol Source # | |
Defined in Web.Stripe.Client | |
Read Protocol Source # | |
Show Protocol Source # | |
data StripeConfig Source #
Stripe config
Instances
Stripe secret key
Instances
Eq StripeKey Source # | |
Data StripeKey Source # | |
Defined in Web.Stripe.Client 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 # | |
Defined in Web.Stripe.Client | |
Read StripeKey Source # | |
Show StripeKey Source # | |
data APIVersion Source #
API Version
V20141007 | Stripe API Version for this package release |