{-# LANGUAGE TypeApplications #-} module Main where import Gargantext.Prelude hiding (isInfixOf) import Control.Concurrent (forkIO, killThread) import Control.Monad import Data.Text (isInfixOf) import Gargantext.Core.AsyncUpdates.CentralExchange qualified as CE import Gargantext.Core.AsyncUpdates.Dispatcher qualified as D import Gargantext.Core.AsyncUpdates.Dispatcher.Types qualified as DT import Shelly hiding (FilePath) import System.IO import System.Process import Test.Hspec import qualified Data.Text as T import qualified Test.API as API import qualified Test.Server.ReverseProxy as ReverseProxy import qualified Test.Database.Operations as DB startCoreNLPServer :: IO ProcessHandle startCoreNLPServer = do devNull <- openFile "/dev/null" WriteMode let p = proc "./startServer.sh" [] (_, _, _, hdl) <- (createProcess $ p { cwd = Just "devops/coreNLP/stanford-corenlp-current" , delegate_ctlc = True , 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 'startServer.sh' script. If this is the " <> "first time you are running the tests, you have to run " <> "cd devops/coreNLP && ./build.sh first. You have to run it only once, " <> "and then you are good to go for the time being." | otherwise -> throwIO e pure hdl stopCoreNLPServer :: ProcessHandle -> IO () stopCoreNLPServer = interruptProcessGroupOf startNotifications :: IO (ThreadId, DT.Dispatcher) startNotifications = do central_exchange <- forkIO CE.gServer dispatcher <- D.dispatcher pure (central_exchange, dispatcher) stopNotifications :: (ThreadId, DT.Dispatcher) -> IO () stopNotifications (central_exchange, dispatcher) = do killThread central_exchange killThread $ DT.d_ce_listener dispatcher -- 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 -- TODO Ideally remove start/stop notifications and use -- Test/API/Setup to initialize this in env bracket startNotifications stopNotifications $ \_ -> do bracket startCoreNLPServer stopCoreNLPServer $ \_ -> hspec $ do API.tests ReverseProxy.tests DB.tests DB.nodeStoryTests