{-# LANGUAGE TemplateHaskell #-} module PayPal.Adaptive.Core.PayResponse ( module Export , module PayPal.Adaptive.Core.PayResponse ) where import Data.Maybe (isJust) import Import import PayPal.Adaptive.Core.PayResponse.PayKey as Export import PayPal.Adaptive.Core.PayResponse.PaymentInfo as Export import PayPal.Adaptive.Core.PayResponse.PayStatus as Export -- | Used for forgiving attempts to parse PayPal responses. For instance, -- this library never expects more than one PaymentInfo. We still try to -- parse them as a list here so we can still sucessfully parse a PayResp -- to use in an 'AdaptiveError' if for some reason more than one 'PaymentInfo' -- is returned. -- -- data PayResponse = PayResponse { _prPayError :: Maybe Text -- ^ payErrorList (string) -- Information about why a payment failed. , _prPayStatus :: PayStatus , _prPayKey :: PayKey , _prPaymentInfos :: [PaymentInfo] } deriving (Eq, Show) instance FromJSON PayResponse where parseJSON = withObject "PayResp" $ \o -> do e <- o .:? "payErrorList" k <- o .: "payKey" s <- o .:? "paymentExecStatus" s' <- o .:? "status" status <- maybe (fail "no paymentExecStatus or status") return (if isJust s then s else s') a <- o .:? "paymentInfoList" case a of Nothing -> return $ PayResponse e status k mempty Just v -> do infos <- v .:? "paymentInfo" .!= mempty return $ PayResponse e status k infos $(makeLenses ''PayResponse)