module Web.Stripe.Client
( StripeConfig(..)
, SecretKey(..)
, StripeVersion(..)
, StripeResponseCode(..)
, StripeFailure(..)
, StripeError(..)
, StripeErrorCode(..)
, StripeRequest(..)
, Stripe
, StripeT(StripeT)
, defaultConfig
, runStripeT
, baseSReq
, query
, queryData
, query_
, StdMethod(..)
) where
import Control.Arrow ((***))
import Control.Exception as EX
import Control.Monad (MonadPlus, join, liftM, mzero)
import Control.Monad.Error (Error, ErrorT, MonadError, MonadIO,
noMsg, runErrorT, strMsg, throwError)
import Control.Monad.State (MonadState, StateT, get, runStateT)
import Control.Monad.Trans (liftIO)
import Data.Aeson (FromJSON (..), Value (..), decode',
eitherDecode', (.:), (.:?))
import Data.Aeson.Types (parseMaybe)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as C8
import qualified Data.ByteString.Lazy as BL
import Data.Char (toLower)
import qualified Data.HashMap.Lazy as HML
import Data.Text (Text)
import qualified Data.Text as T
import Network.HTTP.Conduit
import Network.HTTP.Types
import Web.Stripe.Utils (textToByteString)
data StripeConfig = StripeConfig
{ stripeSecretKey :: SecretKey
, stripeCAFile :: FilePath
, stripeVersion :: StripeVersion
} deriving Show
newtype SecretKey = SecretKey { unSecretKey :: T.Text } deriving Show
data StripeResponseCode = OK | Unknown Int deriving (Show, Eq)
data StripeFailure
= BadRequest (Maybe StripeError)
| Unauthorized (Maybe StripeError)
| NotFound (Maybe StripeError)
| PaymentRequired (Maybe StripeError)
| InternalServerError (Maybe StripeError)
| BadGateway (Maybe StripeError)
| ServiceUnavailable (Maybe StripeError)
| GatewayTimeout (Maybe StripeError)
| HttpFailure (Maybe Text)
| OtherFailure (Maybe Text)
deriving (Show, Eq)
data StripeError
= InvalidRequestError Text
| APIError Text
| CardError Text StripeErrorCode (Maybe Text)
| UnknownError Text Text
deriving (Show, Eq)
data StripeErrorCode
= InvalidNumber
| IncorrectNumber
| InvalidExpiryMonth
| InvalidExpiryYear
| InvalidCVC
| ExpiredCard
| InvalidAmount
| IncorrectCVC
| CardDeclined
| Missing
| DuplicateTransaction
| ProcessingError
| UnknownErrorCode Text
deriving (Show, Eq)
data StripeRequest = StripeRequest
{ sMethod :: StdMethod
, sDestination :: [Text]
, sData :: [(B.ByteString, B.ByteString)]
, sQString :: [(String, String)]
} deriving Show
data StripeVersion = V20110915d
| OtherVersion String
instance Show StripeVersion where
show V20110915d = "2011-09-15-d"
show (OtherVersion x) = x
type Stripe a = StripeT IO a
newtype StripeT m a = StripeT
{ unStripeT :: StateT StripeConfig (ErrorT StripeFailure m) a
} deriving ( Functor, Monad, MonadIO, MonadPlus
, MonadError StripeFailure
, MonadState StripeConfig
)
runStripeT :: MonadIO m => StripeConfig -> StripeT m a -> m (Either StripeFailure a)
runStripeT cfg m =
runErrorT . liftM fst . (`runStateT` cfg) . unStripeT $ m
defaultConfig :: SecretKey -> StripeConfig
defaultConfig k = StripeConfig k "" V20110915d
baseSReq :: StripeRequest
baseSReq = StripeRequest
{ sMethod = GET
, sDestination = []
, sData = []
, sQString = []
}
query' :: MonadIO m => StripeRequest -> StripeT m (StripeResponseCode, BL.ByteString)
query' sReq = do
cfg <- get
req' <- maybe (throwError $ strMsg "Error Prepating the Request") return (prepRq cfg sReq)
let req = req' {checkStatus = \_ _ _ -> Nothing, responseTimeout = Just 10000000}
rsp' <- liftIO (EX.catch (fmap Right $ withManager $ httpLbs req) (return . Left))
case rsp' of
Left err -> throwError (HttpFailure $ Just (T.pack (show (err :: HttpException))))
Right rsp -> do
code <- toCode (responseStatus rsp) (responseBody rsp)
return (code, responseBody rsp)
query :: (MonadIO m, FromJSON a) => StripeRequest -> StripeT m (StripeResponseCode, a)
query req = query' req >>= \(code, ans) ->
either (throwError . strMsg .
(\msg -> "JSON parse error: " ++ msg ++ ". json: " ++ show ans))
(return . (code, )) $ eitherDecode' ans
queryData :: (MonadIO m, FromJSON a) => StripeRequest -> StripeT m (StripeResponseCode, a)
queryData req = query' req >>= \(code, ans) -> do
val <- either (throwError . strMsg . ("JSON parse error: " ++)) return $ eitherDecode' ans
case val of
Object o -> do
objVal <- maybe (throwError $ strMsg "no data in json" ) return $
HML.lookup "data" o
obj <- maybe (throwError $ strMsg "parsed JSON didn't contain object") return $
parseMaybe parseJSON objVal
return (code, obj)
_ -> throwError $ strMsg "JSON was not object"
query_ :: MonadIO m => StripeRequest -> StripeT m ()
query_ req = query' req >> return ()
setUserAgent :: C8.ByteString -> Request -> Request
setUserAgent ua req = req { requestHeaders = ("User-Agent", ua) : filteredHeaders }
where
filteredHeaders = filter ((/= "User-Agent") . fst) $ requestHeaders req
prepRq :: StripeConfig -> StripeRequest -> Maybe Request
prepRq StripeConfig{..} StripeRequest{..} =
flip fmap mReq $ \req -> applyBasicAuth k p $ (addBodyUa req)
{ queryString = renderQuery False qs
, requestHeaders = [ ("Stripe-Version", C8.pack . show $ stripeVersion) ]
, method = renderStdMethod sMethod
}
where
k = textToByteString $ unSecretKey stripeSecretKey
p = textToByteString ""
addBodyUa = urlEncodedBody sData . setUserAgent "hs-string/0.2 http-conduit"
mReq = parseUrl . T.unpack $ T.concat [
"https://api.stripe.com:443/v1/"
, T.intercalate "/" sDestination ]
qs = map (C8.pack *** Just . C8.pack) sQString
toCode :: Monad m => Status -> BL.ByteString -> StripeT m StripeResponseCode
toCode c body = case statusCode c of
200 -> return OK
400 -> throwError $ BadRequest e
401 -> throwError $ Unauthorized e
404 -> throwError $ NotFound e
402 -> throwError $ PaymentRequired e
500 -> throwError $ InternalServerError e
502 -> throwError $ BadGateway e
503 -> throwError $ ServiceUnavailable e
504 -> throwError $ GatewayTimeout e
i -> return $ Unknown i
where e = errorMsg body
toCECode :: T.Text -> StripeErrorCode
toCECode c = case T.map toLower c of
"invalid_number" -> InvalidNumber
"incorrect_number" -> IncorrectNumber
"invalid_expiry_month" -> InvalidExpiryMonth
"invalid_expiry_year" -> InvalidExpiryYear
"invalid_cvc" -> InvalidCVC
"expired_card" -> ExpiredCard
"invalid_amount" -> InvalidAmount
"incorrect_cvc" -> IncorrectCVC
"card_declined" -> CardDeclined
"missing" -> Missing
"duplicate_transaction" -> DuplicateTransaction
"processing_error" -> ProcessingError
_ -> UnknownErrorCode c
errorMsg :: BL.ByteString -> Maybe StripeError
errorMsg bs = join . fmap getErrorVal $ decode' bs
where
getErrorVal (Object o) = maybe Nothing (parseMaybe parseJSON) (HML.lookup "error" o)
getErrorVal _ = Nothing
instance FromJSON StripeError where
parseJSON (Object err) = do
type_ <- err .: "type"
msg <- err .: "message"
case T.map toLower type_ of
"invalid_request_error" -> return $ InvalidRequestError msg
"api_error" -> return $ APIError msg
"card_error" -> do
code <- err .: "code"
param <- err .:? "param"
return $ CardError msg (toCECode code) param
_ -> return $ UnknownError type_ msg
parseJSON _ = mzero
instance Error StripeFailure where
noMsg = OtherFailure Nothing
strMsg = OtherFailure . Just . T.pack