{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TypeApplications #-} module Test.API.Errors (tests) where import Gargantext.API.Routes.Named.Node import Gargantext.API.Routes.Named.Private import Gargantext.Core.Types (Node) import Gargantext.Core.Types.Individu import Gargantext.Database.Admin.Types.Hyperdata (HyperdataUser) import Gargantext.Prelude hiding (get) import Network.HTTP.Client hiding (Proxy) import Network.HTTP.Types import Network.Wai.Test import Servant.Auth.Client () import Servant.Client import Servant.Client.Generic (genericClient) import Test.API.Routes (mkUrl) import Test.API.Setup (withTestDBAndPort, setupEnvironment, createAliceAndBob) import Test.Hspec import Test.Hspec.Wai.Internal (withApplication) import Test.Utils (protected, withValidLogin, protectedNewError) import Text.RawString.QQ (r) 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 gargAdminClient = (genericClient :: GargAdminAPI (AsClientT ClientM)) roots = (getRootsEp . rootsEp $ gargAdminClient :: ClientM [Node HyperdataUser]) result <- liftIO $ runClientM roots (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","node":99}|] it "returns the new error if header X-Garg-Error-Scheme: new is passed" $ \((_testEnv, port), app) -> do withApplication app $ do withValidLogin port "gargantua" (GargPassword "secret_key") $ \token -> do res <- protectedNewError token "GET" (mkUrl port "/node/99") "" case res of SResponse{..} | Status{..} <- simpleStatus ->liftIO $ do statusCode `shouldBe` 404 simpleBody `shouldBe` [r|{"data":{"node_id":99},"diagnostic":"FE_node_lookup_failed_not_found {nenf_node_id = nodeId-99}","type":"EC_404__node_lookup_failed_not_found"}|]