Skip to content
Snippets Groups Projects
Commit cc317a83 authored by Jean-Paul Calderone's avatar Jean-Paul Calderone
Browse files

Most basic implementation of the redeem API

parent 1c7455cd
Branches
No related tags found
1 merge request!8HTTP API for Voucher redemption
...@@ -15,7 +15,9 @@ module PaymentServer.Redemption ...@@ -15,7 +15,9 @@ module PaymentServer.Redemption
import GHC.Generics import GHC.Generics
( Generic ( Generic
) )
import Control.Monad.IO.Class
( liftIO
)
import Data.Text import Data.Text
( Text ( Text
) )
...@@ -30,6 +32,7 @@ import Data.Aeson ...@@ -30,6 +32,7 @@ import Data.Aeson
) )
import Servant import Servant
( Server ( Server
, Handler
, ServerError(errBody, errHeaders) , ServerError(errBody, errHeaders)
, err400 , err400
, throwError , throwError
...@@ -41,12 +44,14 @@ import Servant.API ...@@ -41,12 +44,14 @@ import Servant.API
, (:>) , (:>)
) )
import PaymentServer.Persistence import PaymentServer.Persistence
( VoucherDatabase ( VoucherDatabase(redeemVoucher)
, Fingerprint
, Voucher , Voucher
) )
data Result data Result
= Failed = Failed
| Succeeded
deriving (Show, Eq) deriving (Show, Eq)
-- | A blinded token is presented along with a voucher to be signed and the -- | A blinded token is presented along with a voucher to be signed and the
...@@ -64,6 +69,7 @@ instance ToJSON Redeem where ...@@ -64,6 +69,7 @@ instance ToJSON Redeem where
instance ToJSON Result where instance ToJSON Result where
toJSON Failed = object [ "success" .= False ] toJSON Failed = object [ "success" .= False ]
toJSON Succeeded = object [ "success" .= True ]
type RedemptionAPI = ReqBody '[JSON] Redeem :> Post '[JSON] Result type RedemptionAPI = ReqBody '[JSON] Redeem :> Post '[JSON] Result
...@@ -73,6 +79,15 @@ jsonErr400 = err400 ...@@ -73,6 +79,15 @@ jsonErr400 = err400
} }
redemptionServer :: VoucherDatabase d => d -> Server RedemptionAPI redemptionServer :: VoucherDatabase d => d -> Server RedemptionAPI
redemptionServer _ = redeem redemptionServer = redeem
redeem :: VoucherDatabase d => d -> Redeem -> Handler Result
redeem database (Redeem voucher tokens) = do
let fingerprint = fingerprintFromTokens tokens
result <- liftIO $ PaymentServer.Persistence.redeemVoucher database voucher fingerprint
case result of
Left err -> return Failed
Right () -> return Succeeded
redeem request = return Failed -- throwError jsonErr400 fingerprintFromTokens :: [BlindedToken] -> Fingerprint
fingerprintFromTokens _ = "fingerprint"
...@@ -28,18 +28,21 @@ import Test.Hspec ...@@ -28,18 +28,21 @@ import Test.Hspec
, around , around
, shouldReturn , shouldReturn
, shouldBe , shouldBe
, runIO
) )
import Test.Hspec.Wai import Test.Hspec.Wai
( with ( with
, post
, shouldRespondWith , shouldRespondWith
, liftIO , liftIO
) )
import Test.Hspec.Wai.QuickCheck import Test.Hspec.Wai.QuickCheck
( property ( property
) )
import Test.QuickCheck
( (==>)
)
import Test.QuickCheck.Monadic import Test.QuickCheck.Monadic
( assert ( pre
) )
import Test.QuickCheck.Instances.Text () import Test.QuickCheck.Instances.Text ()
import Util.Spec import Util.Spec
...@@ -47,6 +50,9 @@ import Util.Spec ...@@ -47,6 +50,9 @@ import Util.Spec
, nonJSONUnsupportedMediaType , nonJSONUnsupportedMediaType
, wrongJSONInvalidRequest , wrongJSONInvalidRequest
) )
import Util.WAI
( postJSON
)
import PaymentServer.Redemption import PaymentServer.Redemption
( RedemptionAPI ( RedemptionAPI
, BlindedToken , BlindedToken
...@@ -80,19 +86,37 @@ withConnection :: VoucherDatabase d => IO d -> ((d -> IO ()) -> IO ()) ...@@ -80,19 +86,37 @@ withConnection :: VoucherDatabase d => IO d -> ((d -> IO ()) -> IO ())
withConnection getDB = bracket getDB (\db -> return ()) withConnection getDB = bracket getDB (\db -> return ())
make_spec_db :: VoucherDatabase d => IO d -> Spec make_spec_db :: VoucherDatabase d => IO d -> Spec
make_spec_db getDatabase = make_spec_db getDatabase = do
before (getDatabase >>= return . app) $ -- Create the database so we can interact with it directly in the tests
describe "redemptionServer" $ -- below.
do database <- runIO getDatabase
it "responds to redemption of an unpaid voucher with 400 (Invalid Request)" $ before (return $ app database) $
describe "redemption attempts on the server" $ do
it "receive 400 (Invalid Request) when the voucher is unpaid" $
property $ \(voucher :: Voucher) (tokens :: [BlindedToken]) ->
postJSON path (encode $ Redeem voucher tokens) `shouldRespondWith` 400
it "receive 200 (OK) when the voucher is paid" $
property $ \(voucher :: Voucher) (tokens :: [BlindedToken]) -> property $ \(voucher :: Voucher) (tokens :: [BlindedToken]) ->
post path (encode $ Redeem voucher tokens) `shouldRespondWith` 400 do
liftIO $ payForVoucher database voucher
postJSON path (encode $ Redeem voucher tokens) `shouldRespondWith` 200
it "responds to redemption of a paid voucher with 200 (OK)" $ it "receive 200 (OK) when the voucher is paid and previously redeemed with the same tokens" $
property $ \(voucher :: Voucher) (tokens :: [BlindedToken]) -> property $ \(voucher :: Voucher) (tokens :: [BlindedToken]) ->
do do
payForVoucher database voucher liftIO $ payForVoucher database voucher
post path (encode $ Redeem voucher tokens) `shouldRespondWith` 200 postJSON path (encode $ Redeem voucher tokens) `shouldRespondWith` 200
postJSON path (encode $ Redeem voucher tokens) `shouldRespondWith` 200
it "receive 400 (OK) when the voucher is paid and previously redeemed with different tokens" $
property $ \(voucher :: Voucher) (firstTokens :: [BlindedToken]) (secondTokens :: [BlindedToken]) ->
do
liftIO $ payForVoucher database voucher
postJSON path (encode $ Redeem voucher firstTokens) `shouldRespondWith` 200
postJSON path (encode $ Redeem voucher secondTokens) `shouldRespondWith` 400
spec_memory_db :: Spec spec_memory_db :: Spec
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment