Commit f1d668a0 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Add old error format test

parent 3763d0dc
Pipeline #5335 passed with stages
in 68 minutes and 26 seconds
...@@ -1003,6 +1003,7 @@ test-suite garg-test-hspec ...@@ -1003,6 +1003,7 @@ test-suite garg-test-hspec
other-modules: other-modules:
Test.API Test.API
Test.API.Authentication Test.API.Authentication
Test.API.Errors
Test.API.GraphQL Test.API.GraphQL
Test.API.Private Test.API.Private
Test.API.Setup Test.API.Setup
......
...@@ -6,9 +6,11 @@ import Test.Hspec ...@@ -6,9 +6,11 @@ import Test.Hspec
import qualified Test.API.Authentication as Auth import qualified Test.API.Authentication as Auth
import qualified Test.API.Private as Private import qualified Test.API.Private as Private
import qualified Test.API.GraphQL as GraphQL import qualified Test.API.GraphQL as GraphQL
import qualified Test.API.Errors as Errors
tests :: Spec tests :: Spec
tests = describe "API" $ do tests = describe "API" $ do
Auth.tests Auth.tests
Private.tests Private.tests
GraphQL.tests GraphQL.tests
Errors.tests
{-# LANGUAGE QuasiQuotes #-}
module Test.API.Errors (tests) where
import Gargantext.API.Routes
import Gargantext.Core.Types.Individu
import Gargantext.Prelude hiding (get)
import Network.HTTP.Client hiding (Proxy)
import Network.HTTP.Types
import Network.Wai.Test
import Servant
import Servant.Auth.Client ()
import Servant.Client
import Test.API.Private (protected, withValidLogin)
import Test.API.Setup (withTestDBAndPort, setupEnvironment, mkUrl, createAliceAndBob)
import Test.Hspec
import Test.Hspec.Wai.Internal (withApplication)
import Text.RawString.QQ (r)
import qualified Servant.Auth.Client as SA
tests :: Spec
tests = sequential $ aroundAll withTestDBAndPort $ do
describe "Errors API" $ do
describe "Prelude" $ do
it "setup DB triggers and users" $ \((testEnv, port), _) -> do
setupEnvironment testEnv
baseUrl <- parseBaseUrl "http://localhost"
manager <- newManager defaultManagerSettings
let clientEnv prt = mkClientEnv manager (baseUrl { baseUrlPort = prt })
createAliceAndBob testEnv
let ( roots_api :<|> _nodes_api
) = client (Proxy :: Proxy (MkProtectedAPI GargAdminAPI)) (SA.Token "bogus")
let ( admin_user_api_get :<|> _) = roots_api
result <- runClientM admin_user_api_get (clientEnv port)
length result `shouldBe` 0
describe "GET /api/v1.0/node" $ do
it "returns the old error by default" $ \((_testEnv, port), app) -> do
withApplication app $ do
withValidLogin port "gargantua" (GargPassword "secret_key") $ \token -> do
res <- protected token "GET" (mkUrl port "/node/99") ""
case res of
SResponse{..}
| Status{..} <- simpleStatus
->liftIO $ do
statusCode `shouldBe` 404
simpleBody `shouldBe` [r|{"error":"Node does not exist (nodeId-99)"}|]
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment