less clients per test

This commit is contained in:
Efim Poberezkin 2022-02-17 12:45:26 +04:00
parent e31fc87691
commit 9d35e100d9
4 changed files with 55 additions and 14 deletions

View File

@ -1,11 +1,13 @@
module Main where
import Simplex.StressTest
import System.Directory (createDirectoryIfMissing, removeDirectoryRecursive)
import System.Directory
import Test.Hspec
import Control.Monad
main :: IO ()
main = do
createDirectoryIfMissing False "tests/tmp"
dirExists <- doesDirectoryExist "test"
when dirExists $ removeDirectoryRecursive "test"
createDirectoryIfMissing True "test"
hspec $ describe "SimpleX chat client" chatTests
removeDirectoryRecursive "tests/tmp"

View File

@ -0,0 +1,36 @@
#!/bin/bash
# Log all stdout output to stackscript.log
exec &> >(tee -i /var/log/stackscript.log)
# Uncomment next line to enable debugging features
# set -xeo pipefail
cd $HOME
# Download stress test binary
binary="$HOME/simplex-stress-test"
curl -L -o binary https://github.com/simplex-chat/simplex-chat/releases/download/v1.2.1/simplex-stress-test
chmod +x binary
# / Create systemd service
cat <<EOT >> /etc/systemd/system/simplex-stress-test.service
[Unit]
Description=SMP server stress test
[Service]
Type=simple
ExecStart=/bin/sh -c "$binary start"
Restart=always
RestartSec=3
[Install]
WantedBy=multi-user.target
EOT
# Create systemd service /
# Start systemd service
chmod 644 /etc/systemd/system/simplex-stress-test.service
sudo systemctl enable simplex-stress-test
sudo systemctl start simplex-stress-test

View File

@ -111,34 +111,37 @@ testStressServer :: IO ()
testStressServer =
withTmpFiles $ do
sentTVar <- newTVarIO (0 :: Int)
connectedTVar <- newTVarIO (0 :: Int)
tcpConnectionsTVar <- newTVarIO (0 :: Int)
userConnectionsTVar <- newTVarIO (0 :: Int)
concurrentlyN_ $
forever
( do
threadDelay 5000000
sent <- readTVarIO sentTVar
connected <- readTVarIO connectedTVar
print $ "connected: " <> show connected <> " -- sent: " <> show sent
tcpConnections <- readTVarIO tcpConnectionsTVar
userConnections <- readTVarIO userConnectionsTVar
print $ "tcpConnections: " <> show tcpConnections <> " -- userConnections: " <> show userConnections <> " -- sent: " <> show sent
) :
map
( \i ->
testChat2' (i * 2 -1, aliceProfile) (i * 2, bobProfile) $
\alice bob -> do
print $ show i <> " - connected +2"
atomically $ modifyTVar connectedTVar (+ 2)
print $ show i <> " - tcpConnections +2"
atomically $ modifyTVar tcpConnectionsTVar (+ 2)
connectUsers alice bob
print $ show i <> " - userConnections +2"
atomically $ modifyTVar userConnectionsTVar (+ 2)
loop i alice bob sentTVar 1
)
(take 100 ([1 ..] :: [Int]))
(take 25 ([1 ..] :: [Int]))
where
loop :: Int -> TestCC -> TestCC -> TVar Int -> Int -> IO ()
loop i alice bob sentTVar k = do
alice `send` "@bob hi"
bob `send` "@alice hi"
alice <##> bob
when (k `mod` 100 == 0) $ do
print $ show i <> " - +200"
print $ show i <> " - sent +200"
atomically $ modifyTVar sentTVar (+ 200)
threadDelay 500000
threadDelay 1000000
loop i alice bob sentTVar $ k + 1
startFileTransfer :: TestCC -> TestCC -> IO ()

View File

@ -36,7 +36,7 @@ import System.Timeout (timeout)
import Test.Hspec (Expectation, shouldReturn)
testDBPrefix :: FilePath
testDBPrefix = "tests/tmp/test"
testDBPrefix = "test/test"
serverPort :: ServiceName
serverPort = "5001"