{-# LANGUAGE TypeApplications #-}

module Main where

import Control.Monad
import Data.Text (isInfixOf)
import Data.Text qualified as T
import Gargantext.Prelude hiding (isInfixOf)
import System.IO
import System.Process
import System.Posix.Process
import System.Posix.Signals
import Test.API qualified as API
import Test.Database.Operations qualified as DB
import Test.Hspec
import Test.Server.ReverseProxy qualified as ReverseProxy


startCoreNLPServer :: IO ProcessHandle
startCoreNLPServer = do
  putText "calling start core nlp"
  devNull <- openFile "/dev/null" WriteMode
  let p = proc "startCoreNLPServer.sh" []
  (_, _, _, hdl) <- (createProcess $ p { cwd = Nothing
                    -- NOTE(adn) Issue #451, this one has to stay disabled, because if we
                    -- turn it on, despite the confusing documentation on the `process` library
                    -- it will cause the Haskell RTS to completely ignore the Ctrl^c and instead
                    -- delegate it exclusively to the process here, which means that our CoreNLP
                    -- server will shut down correctly, but the test running will stop responding
                    -- to Ctrl^C requests.
                    , delegate_ctlc = False
                    , create_group = True
                    , std_out = UseHandle devNull
                    , std_err = UseHandle devNull
                    }) `catch` \e -> case e of
                                           _ | True <- "does not exist" `isInfixOf` (T.pack . show @SomeException $ e)
                                             -> fail $ "Cannot execute the 'startCoreNLPServer.sh' script. Make sure you are in a nix environment."
                                             | otherwise -> throwIO e
  pure hdl

killProcessTree :: ProcessHandle -> IO ()
killProcessTree ph = do
  pid <- getPid ph
  case pid of
    Nothing -> putText "Process already terminated"
    Just p -> do
      pgid <- getProcessGroupIDOf p
      signalProcessGroup keyboardSignal pgid

-- It's especially important to use Hspec for DB tests, because,
-- unlike 'tasty', 'Hspec' has explicit control over parallelism,
-- and it's important that DB tests are run according to a very
-- precise order, as they are not independent from each other.
-- Unfortunately it's not possibly to use the 'tasty-hspec' adapter
-- because by the time we get a 'TestTree' out of the adapter library,
-- the information about parallelism is lost.
--
-- /IMPORTANT/: For these tests to run correctly, you have to run
-- ./devops/coreNLP/build.sh first. You have to run it only /once/,
-- and then you are good to go for the time being.
main :: IO ()
main = do
  hSetBuffering stdout NoBuffering
  bracket startCoreNLPServer killProcessTree (const run_tests)
  where
    run_tests = hspec $ sequential $ do
      API.tests
      ReverseProxy.tests
      DB.tests
      DB.nodeStoryTests
      runIO $ putText "tests finished"