{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}

module Test.API.Private.Share (
    tests
  ) where

import Control.Lens
import Data.ByteString.Lazy.Char8 qualified as CL8
import Data.Text qualified as T
import Gargantext.API.Errors
import Gargantext.API.Routes.Named
import Gargantext.API.Routes.Named.Private
import Gargantext.API.Routes.Named.Share
import Gargantext.Core.Types
import Gargantext.Core.Types.Individu
import Gargantext.Prelude
import Prelude (fail)
import Servant.Auth.Client qualified as SC
import Servant.Client.Streaming
import Test.API.Prelude (newCorpusForUser)
import Test.API.Routes
import Test.API.Setup (SpecContext(..), dbEnvSetup, withTestDBAndPort)
import Test.Hspec
import Test.Hspec.Wai.Internal (withApplication)
import Test.Utils

shareURL :: SC.Token -> Maybe NodeType -> Maybe NodeId -> ClientM ShareLink
shareURL token =
  clientRoutes & apiWithCustomErrorScheme
               & ($ GES_new)
               & backendAPI
               & backendAPI'
               & mkBackEndAPI
               & gargAPIVersion
               & gargPrivateAPI
               & mkPrivateAPI
               & ($ token)
               & shareUrlAPI
               & shareUrlEp

tests :: Spec
tests = sequential $ aroundAll withTestDBAndPort $ beforeAllWith dbEnvSetup $ do
  describe "Prelude" $ do
    it "should fail if no node type is specified" $ \(SpecContext _testEnv serverPort app _) -> do
      withApplication app $ do
        withValidLogin serverPort "alice" (GargPassword "alice") $ \clientEnv token -> do
          url <- liftIO $ runClientM (shareURL (toServantToken token) Nothing Nothing) clientEnv
          case url of
            Left (FailureResponse _req res)
              -> liftIO $ (CL8.unpack $ responseBody res) `shouldSatisfy` (T.isInfixOf "Invalid node Type" . T.pack)
            _ -> fail "Test did not fail as expected!"

    it "should fail if no node ID is specified" $ \(SpecContext _testEnv serverPort app _) -> do
      withApplication app $ do
        withValidLogin serverPort "alice" (GargPassword "alice") $ \clientEnv token -> do
          url <- liftIO $ runClientM (shareURL (toServantToken token) (Just NodeCorpus) Nothing) clientEnv
          case url of
            Left (FailureResponse _req res)
              -> liftIO $ (CL8.unpack $ responseBody res) `shouldSatisfy` (T.isInfixOf "Invalid node ID" . T.pack)
            _ -> fail "Test did not fail as expected!"

    it "should return a valid URL" $ \(SpecContext testEnv serverPort app _) -> do
      withApplication app $ do
        withValidLogin serverPort "alice" (GargPassword "alice") $ \clientEnv token -> do
          cId <- liftIO $ newCorpusForUser testEnv "alice"
          url <- liftIO $ runClientM (shareURL (toServantToken token) (Just NodeCorpus) (Just cId)) clientEnv
          case url of
            Left err
              -> fail (show err)
            Right (ShareLink _)
              -> pure ()

    it "should include the port if needed (like localhost)" $ \(SpecContext testEnv serverPort app _) -> do
      withApplication app $ do
        withValidLogin serverPort "alice" (GargPassword "alice") $ \clientEnv token -> do
          cId <- liftIO $ newCorpusForUser testEnv "alice"
          url <- liftIO $ runClientM (shareURL (toServantToken token) (Just NodeCorpus) (Just cId)) clientEnv
          case url of
            Left err
              -> fail (show err)
            Right (ShareLink uri)
              -> liftIO $ "localhost:80" `T.isInfixOf` T.pack (show uri) `shouldBe` True