Skip to content

Commit

Permalink
Use hspec-wai for api server test
Browse files Browse the repository at this point in the history
  • Loading branch information
v0d1ch committed Jul 25, 2023
1 parent 0faec99 commit a1c3aca
Show file tree
Hide file tree
Showing 3 changed files with 50 additions and 41 deletions.
1 change: 1 addition & 0 deletions hydra-node/hydra-node.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -336,6 +336,7 @@ test-suite tests
, hspec
, hspec-core
, hspec-golden-aeson
, hspec-wai
, HUnit
, hydra-cardano-api
, hydra-node
Expand Down
44 changes: 25 additions & 19 deletions hydra-node/src/Hydra/API/Server.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,7 @@ import Hydra.API.ServerOutput (
projectSnapshotUtxo,
snapshotUtxo,
)
import Hydra.Cardano.Api (ProtocolParameters)
import Hydra.Chain (
Chain (..),
IsChainState,
Expand All @@ -56,6 +57,7 @@ import Hydra.Party (Party)
import Hydra.Persistence (PersistenceIncremental (..))
import Network.HTTP.Types (Method, status200, status400, status500)
import Network.Wai (
Application,
Request (pathInfo),
Response,
ResponseReceived,
Expand Down Expand Up @@ -85,7 +87,6 @@ import Network.WebSockets (
import Test.QuickCheck (oneof)
import Text.URI hiding (ParseException)
import Text.URI.QQ (queryKey, queryValue)
import Hydra.Cardano.Api (ProtocolParameters)

data APIServerLog
= APIServerStarted {listeningPort :: PortNumber}
Expand Down Expand Up @@ -220,7 +221,7 @@ runAPIServer host port party tracer history chain callback headStatusP snapshotU
-- catch and rethrow with more context
handle onIOException $
runSettings serverSettings $
websocketsOr defaultConnectionOptions wsApp (httpApp chain protocolparams)
websocketsOr defaultConnectionOptions wsApp (httpApp tracer chain protocolparams)
where
serverSettings =
defaultSettings
Expand Down Expand Up @@ -251,23 +252,6 @@ runAPIServer host port party tracer history chain callback headStatusP snapshotU
withPingThread con 30 (pure ()) $
race_ (receiveInputs con) (sendOutputs chan con outConfig)

-- Hydra HTTP server
httpApp directChain pparams' req respond =
case (requestMethod req, pathInfo req) of
("POST", ["commit"]) -> do
body <- consumeRequestBodyStrict req
handleDraftCommitUtxo directChain tracer body (requestMethod req) (pathInfo req) respond
("GET", ["protocol-parameters"]) ->
respond $ responseLBS status200 [] (Aeson.encode pparams')
_ -> do
traceWith tracer $
APIRestInputReceived
{ method = decodeUtf8 $ requestMethod req
, paths = pathInfo req
, requestInputBody = Nothing
}
respond $ responseLBS status400 [] "Resource not found"

-- NOTE: We will add a 'Greetings' message on each API server start. This is
-- important to make sure the latest configured 'party' is reaching the
-- client.
Expand Down Expand Up @@ -365,6 +349,28 @@ data RunServerException = RunServerException

instance Exception RunServerException

-- | Hydra HTTP server
httpApp ::
Tracer IO APIServerLog ->
Chain tx IO ->
ProtocolParameters ->
Application
httpApp tracer directChain pparams req respond =
case (requestMethod req, pathInfo req) of
("POST", ["commit"]) -> do
body <- consumeRequestBodyStrict req
handleDraftCommitUtxo directChain tracer body (requestMethod req) (pathInfo req) respond
("GET", ["protocol-parameters"]) ->
respond $ responseLBS status200 [] (Aeson.encode pparams)
_ -> do
traceWith tracer $
APIRestInputReceived
{ method = decodeUtf8 $ requestMethod req
, paths = pathInfo req
, requestInputBody = Nothing
}
respond $ responseLBS status400 [] "Resource not found"

-- Handle user requests to obtain a draft commit tx
handleDraftCommitUtxo ::
Chain tx IO ->
Expand Down
46 changes: 24 additions & 22 deletions hydra-node/test/Hydra/API/RestServerSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,21 +2,20 @@

module Hydra.API.RestServerSpec where

import Hydra.Prelude
import Hydra.Prelude hiding (get)
import Test.Hydra.Prelude

import Data.Aeson (encode)
import Data.Aeson.Lens (key)
import Hydra.API.RestServer (DraftCommitTxRequest, DraftCommitTxResponse)
import Hydra.API.ServerSpec (mockPersistence, withTestAPIServer)
import Hydra.API.Server (httpApp)
import Hydra.API.ServerSpec (dummyChainHandle)
import Hydra.Chain.Direct.Fixture (defaultPParams)
import Hydra.Chain.Direct.State ()
import Hydra.JSONSchema (prop_validateJSONSchema)
import Hydra.Logging (showLogsOnFailure)
import Network.HTTP.Req (GET (GET), NoReqBody (NoReqBody), defaultHttpConfig, http, lbsResponse, port, req, responseBody, responseStatusCode, runReq, (/:))
import Hydra.Logging (nullTracer)
import Test.Aeson.GenericSpecs (roundtripAndGoldenSpecs)
import Test.Hydra.Fixture (alice)
import Test.Network.Ports (withFreePort)
import Test.Hspec.Wai (MatchBody (..), ResponseMatcher (matchBody), get, shouldRespondWith, with)
import Test.QuickCheck.Property (property, withMaxSuccess)

spec :: Spec
Expand All @@ -37,19 +36,22 @@ spec = do
prop_validateJSONSchema @DraftCommitTxResponse "api.json" $
key "components" . key "messages" . key "DraftCommitTxResponse" . key "payload"

describe "REST API endpoints" $
it "GET /protocol-parameters returns 200" $
showLogsOnFailure $ \tracer -> failAfter 5 $
withFreePort $ \port' ->
withTestAPIServer port' alice mockPersistence tracer $ \_ -> do
r <-
runReq defaultHttpConfig $
req
GET
(http "127.0.0.1" /: "protocol-parameters")
NoReqBody
lbsResponse
(port $ fromIntegral port')

responseBody r `shouldBe` encode defaultPParams
responseStatusCode r `shouldBe` 200
apiServerSpec

-- REVIEW: we should add more tests for other routes here (eg. /commit)
apiServerSpec :: Spec
apiServerSpec = do
let webServer = httpApp nullTracer dummyChainHandle defaultPParams
with (return webServer) $ do
describe "API should respond correctly" $
it "GET /protocol-parameters works" $
get "/protocol-parameters"
`shouldRespondWith` 200
{ matchBody =
MatchBody
( \_ actualBody ->
if actualBody /= encode defaultPParams
then Just "Request body missmatch"
else Nothing
)
}

0 comments on commit a1c3aca

Please sign in to comment.