{-# LANGUAGE QuasiQuotes      #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies     #-}
{-# OPTIONS_GHC -Wno-orphans  #-}

module Test.API.GraphQL (
    tests
  ) where

import Gargantext.API.Admin.Auth.Types (authRes_token, authRes_tree_id, authRes_user_id)
import Gargantext.Core.Types.Individu
import Gargantext.Database.Admin.Types.Node (UserId(..))
import Gargantext.Prelude
import Servant.Auth.Client ()
import Test.API.Setup (withTestDBAndPort, dbEnvSetup, SpecContext (..))
import Test.Hspec
import Test.Hspec.Wai.Internal (withApplication)
import Test.Hspec.Wai.JSON (json)
import Test.Utils (protected, protectedNewError, shouldRespondWithFragment, shouldRespondWithFragmentCustomStatus, withValidLogin, withValidLoginA)
import Text.RawString.QQ (r)

tests :: Spec
tests = sequential $ aroundAll withTestDBAndPort $ beforeAllWith dbEnvSetup $ do
  describe "GraphQL" $ do
    describe "get_user_infos" $ do
      it "allows 'alice' to see her own info" $ \SpecContext{..} -> do
        withApplication _sctx_app $ do
          withValidLoginA _sctx_port "alice" (GargPassword "alice") $ \_clientEnv authRes -> do
            liftIO $ (authRes ^. authRes_user_id) `shouldBe` (UnsafeMkUserId 2)
            let query = [r| { "query": "{ user_infos(user_id: 2) { ui_id, ui_email } }" } |]
            let expected = [json| {data: {user_infos: [{ui_id: 2, ui_email: "alice@gargan.text" }] } } |]
            protected (authRes ^. authRes_token) "POST" "/gql" query `shouldRespondWithFragment` expected

    describe "get_users" $ do
      it "allows 'alice' to see her user info" $ \SpecContext{..} -> do
        withApplication _sctx_app $ do
          withValidLoginA _sctx_port "alice" (GargPassword "alice") $ \_clientEnv authRes -> do
            -- epo_api_user is a renamed field, we check if it's correctly un-prefixed
            liftIO $ (authRes ^. authRes_tree_id) `shouldBe` 8
            let query = [r| { "query": "{ users(user_id: 8) { u_username, u_hyperdata { epo_api_user, public { pseudo }, private { lang } } } }" } |]
            let expected = [json| {data: {users: [{u_username: "alice", u_hyperdata: {epo_api_user: null, public: { pseudo: "pseudo" }, private: { lang: "EN" } } }] } } |]
            protected (authRes ^. authRes_token) "POST" "/gql" query `shouldRespondWithFragment` expected

    describe "nodes" $ do
      it "returns node_type" $ \(SpecContext _testEnv port app _) -> do
        withApplication app $ do
          withValidLogin port "gargantua" (GargPassword "secret_key") $ \_clientEnv token -> do
            let query = [r| { "query": "{ nodes(node_id: 2) { node_type } }" } |]
            let expected = [json| {data: {nodes: [{node_type: "NodeFolderPrivate" }]}} |]
            protected token "POST" "/gql" query `shouldRespondWithFragment` expected

    describe "check error format" $ do
      it "returns the new error if header X-Garg-Error-Scheme: new is passed" $ \(SpecContext _testEnv port app _) -> do
        withApplication app $ do
          withValidLogin port "gargantua" (GargPassword "secret_key") $ \_clientEnv token -> do
            let query = [r| { "query": "{ languages(id:5) { lt_lang } }" } |]
            let expected = [json| {"errors": [{"locations":[{"column":13,"line":1}],"message":"Unknown Argument \"id\" on Field \"languages\"."}] } |]
            protectedNewError token "POST" "/gql" query `shouldRespondWithFragment` expected

      it "returns the old error (though this is deprecated)" $ \(SpecContext _testEnv port app _) -> do
        withApplication app $ do
          withValidLogin port "gargantua" (GargPassword "secret_key") $ \_clientEnv token -> do
            let query = [r| { "query": "{ languages(id:5) { lt_lang } }" } |]
            let expected = [json| {"errors": [{"locations":[{"column":13,"line":1}],"message":"Unknown Argument \"id\" on Field \"languages\"."}] } |]
            protected token "POST" "/gql" query `shouldRespondWithFragment` expected

      it "check new errors with 'type'" $ \(SpecContext _testEnv port app _) -> do
        withApplication app $ do
          withValidLogin port "gargantua" (GargPassword "secret_key") $ \_clientEnv token -> do
            let query = [r| { "query": "mutation { delete_team_membership(shared_folder_id:1, team_node_id:1, token:\"abc\") }" } |]
            let expected = [json| {"errors":[{"extensions":{"data":{"msg":"This user is not team owner","user_id":1},"diagnostic":"User not authorized. ","type":"EC_403__user_not_authorized"},"message":"User not authorized. "}]} |]
            shouldRespondWithFragmentCustomStatus 403
              (protectedNewError token "POST" "/gql" query)
              expected