{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE OverloadedStrings #-}
module Web.Stripe.Client
( module Web.Stripe.StripeRequest
, module Web.Stripe.Error
, module Web.Stripe.Util
, handleStream
, parseFail
, attemptDecode
, unknownCode
, defaultEndpoint
, Endpoint (..)
, Protocol (..)
, StripeConfig (..)
, StripeKey (..)
, APIVersion (..)
) where
import Data.Aeson (Value, Result(..), fromJSON)
import Data.ByteString (ByteString)
import Data.Data (Data, Typeable)
import Data.Monoid (mempty)
import Data.Text as T
import Text.Read (lexP, pfail)
import qualified Text.Read as R
import Web.Stripe.StripeRequest
import Web.Stripe.Error
import Web.Stripe.Util
newtype StripeKey = StripeKey
{ getStripeKey :: ByteString
} deriving (Read, Show, Eq, Ord, Data, Typeable)
data Protocol = HTTP | HTTPS
deriving (Read, Show, Eq, Ord, Data, Typeable)
data StripeConfig = StripeConfig
{ secretKey :: StripeKey
, stripeEndpoint :: Maybe Endpoint
} deriving (Read, Show, Eq, Ord, Data, Typeable)
data Endpoint
= Endpoint
{ endpointUrl :: ByteString
, endpointProtocol :: Protocol
, endpointPort :: Int
} deriving (Show, Eq, Read, Ord, Data)
defaultEndpoint :: Endpoint
defaultEndpoint = Endpoint "api.stripe.com" HTTPS 443
data APIVersion =
V20141007
deriving (Eq, Ord, Data, Typeable)
instance Show APIVersion where
show V20141007 = "2014-10-07"
instance Read APIVersion where
readPrec =
do (R.String s) <- lexP
case s of
"2014-10-07" -> return V20141007
_ -> pfail
handleStream
:: (Value -> Result a)
-> Int
-> Result Value
-> Either StripeError a
handleStream decodeValue statusCode r =
case statusCode of
200 -> case r of
Error message -> parseFail message
(Success value) ->
case decodeValue value of
(Error message) -> parseFail message
(Success a) -> (Right a)
code | code >= 400 ->
case r of
Error message -> parseFail message
(Success value) ->
case fromJSON value of
(Error message) -> parseFail message
(Success stripeError) ->
Left $ setErrorHTTP code stripeError
_ -> unknownCode
attemptDecode
:: Int
-> Bool
attemptDecode code = code == 200 || code >= 400
parseFail
:: String
-> Either StripeError a
parseFail errorMessage =
Left $ StripeError ParseFailure (T.pack errorMessage) Nothing Nothing Nothing
unknownCode :: Either StripeError a
unknownCode =
Left $ StripeError UnknownErrorType mempty Nothing Nothing Nothing
setErrorHTTP
:: Int
-> StripeError
-> StripeError
setErrorHTTP statusCode stripeError =
case statusCode of
400 -> stripeError { errorHTTP = Just BadRequest }
401 -> stripeError { errorHTTP = Just UnAuthorized }
402 -> stripeError { errorHTTP = Just RequestFailed }
404 -> stripeError { errorHTTP = Just NotFound }
500 -> stripeError { errorHTTP = Just StripeServerError }
502 -> stripeError { errorHTTP = Just StripeServerError }
503 -> stripeError { errorHTTP = Just StripeServerError }
504 -> stripeError { errorHTTP = Just StripeServerError }
_ -> stripeError { errorHTTP = Just UnknownHTTPCode }