2021-07-07 22:46:38 +01:00
|
|
|
{-# LANGUAGE DuplicateRecordFields #-}
|
2021-08-05 20:51:48 +01:00
|
|
|
{-# LANGUAGE LambdaCase #-}
|
2021-07-07 22:46:38 +01:00
|
|
|
{-# LANGUAGE NamedFieldPuns #-}
|
2022-04-21 20:04:22 +01:00
|
|
|
{-# LANGUAGE NumericUnderscores #-}
|
2021-07-07 22:46:38 +01:00
|
|
|
{-# LANGUAGE OverloadedLists #-}
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2021-08-05 20:51:48 +01:00
|
|
|
{-# LANGUAGE TypeApplications #-}
|
2021-07-07 22:46:38 +01:00
|
|
|
|
|
|
|
module ChatClient where
|
|
|
|
|
2021-08-05 20:51:48 +01:00
|
|
|
import Control.Concurrent (ThreadId, forkIOWithUnmask, killThread)
|
2021-07-07 22:46:38 +01:00
|
|
|
import Control.Concurrent.Async
|
2021-08-05 20:51:48 +01:00
|
|
|
import Control.Concurrent.STM
|
|
|
|
import Control.Exception (bracket, bracket_)
|
2021-07-07 22:46:38 +01:00
|
|
|
import Control.Monad.Except
|
2021-08-05 20:51:48 +01:00
|
|
|
import Data.List (dropWhileEnd)
|
2022-03-13 19:34:03 +00:00
|
|
|
import Data.Maybe (fromJust)
|
|
|
|
import qualified Data.Text as T
|
2021-08-05 20:51:48 +01:00
|
|
|
import Network.Socket
|
2021-07-07 22:46:38 +01:00
|
|
|
import Simplex.Chat
|
2021-09-04 07:32:56 +01:00
|
|
|
import Simplex.Chat.Controller (ChatConfig (..), ChatController (..))
|
2022-04-10 17:13:06 +01:00
|
|
|
import Simplex.Chat.Core
|
2021-07-07 22:46:38 +01:00
|
|
|
import Simplex.Chat.Options
|
|
|
|
import Simplex.Chat.Store
|
2022-01-21 11:09:33 +00:00
|
|
|
import Simplex.Chat.Terminal
|
|
|
|
import Simplex.Chat.Terminal.Output (newChatTerminal)
|
2022-03-13 19:34:03 +00:00
|
|
|
import Simplex.Chat.Types (Profile, User (..))
|
2021-08-02 20:10:24 +01:00
|
|
|
import Simplex.Messaging.Agent.Env.SQLite
|
2021-08-14 21:04:51 +01:00
|
|
|
import Simplex.Messaging.Agent.RetryInterval
|
2021-08-05 20:51:48 +01:00
|
|
|
import Simplex.Messaging.Server (runSMPServerBlocking)
|
|
|
|
import Simplex.Messaging.Server.Env.STM
|
|
|
|
import Simplex.Messaging.Transport
|
2021-07-16 07:40:55 +01:00
|
|
|
import System.Directory (createDirectoryIfMissing, removeDirectoryRecursive)
|
2021-07-07 22:46:38 +01:00
|
|
|
import qualified System.Terminal as C
|
2021-08-05 20:51:48 +01:00
|
|
|
import System.Terminal.Internal (VirtualTerminal (..), VirtualTerminalSettings (..), withVirtualTerminal)
|
|
|
|
import System.Timeout (timeout)
|
2022-02-02 23:50:43 +04:00
|
|
|
import Test.Hspec (Expectation, shouldReturn)
|
2021-07-07 22:46:38 +01:00
|
|
|
|
2021-07-24 10:26:28 +01:00
|
|
|
testDBPrefix :: FilePath
|
|
|
|
testDBPrefix = "tests/tmp/test"
|
2021-07-07 22:46:38 +01:00
|
|
|
|
2021-08-05 20:51:48 +01:00
|
|
|
serverPort :: ServiceName
|
2021-12-27 15:15:35 +04:00
|
|
|
serverPort = "5001"
|
2021-08-05 20:51:48 +01:00
|
|
|
|
2021-07-07 22:46:38 +01:00
|
|
|
opts :: ChatOpts
|
|
|
|
opts =
|
|
|
|
ChatOpts
|
2022-01-21 11:09:33 +00:00
|
|
|
{ dbFilePrefix = undefined,
|
2022-01-20 20:23:21 +00:00
|
|
|
smpServers = ["smp://LcJUMfVhwD8yxjAiSaDzzGF3-kLG4Uh0Fl_ZIjrRwjI=@localhost:5001"],
|
2022-02-25 16:29:36 +04:00
|
|
|
logConnections = False,
|
2022-04-10 17:13:06 +01:00
|
|
|
logAgent = False,
|
|
|
|
chatCmd = "",
|
|
|
|
chatCmdDelay = 3
|
2021-07-07 22:46:38 +01:00
|
|
|
}
|
|
|
|
|
|
|
|
termSettings :: VirtualTerminalSettings
|
|
|
|
termSettings =
|
|
|
|
VirtualTerminalSettings
|
|
|
|
{ virtualType = "xterm",
|
|
|
|
virtualWindowSize = pure C.Size {height = 24, width = 1000},
|
|
|
|
virtualEvent = retry,
|
|
|
|
virtualInterrupt = retry
|
|
|
|
}
|
|
|
|
|
2021-08-05 20:51:48 +01:00
|
|
|
data TestCC = TestCC
|
|
|
|
{ chatController :: ChatController,
|
|
|
|
virtualTerminal :: VirtualTerminal,
|
|
|
|
chatAsync :: Async (),
|
|
|
|
termAsync :: Async (),
|
|
|
|
termQ :: TQueue String
|
|
|
|
}
|
2021-07-07 22:46:38 +01:00
|
|
|
|
2021-08-02 20:10:24 +01:00
|
|
|
aCfg :: AgentConfig
|
|
|
|
aCfg = agentConfig defaultChatConfig
|
|
|
|
|
|
|
|
cfg :: ChatConfig
|
|
|
|
cfg =
|
|
|
|
defaultChatConfig
|
|
|
|
{ agentConfig =
|
2022-02-09 20:58:02 +04:00
|
|
|
aCfg {reconnectInterval = (reconnectInterval aCfg) {initialInterval = 50000}},
|
|
|
|
testView = True
|
2021-08-02 20:10:24 +01:00
|
|
|
}
|
|
|
|
|
2021-07-07 22:46:38 +01:00
|
|
|
virtualSimplexChat :: FilePath -> Profile -> IO TestCC
|
2022-01-21 11:09:33 +00:00
|
|
|
virtualSimplexChat dbFilePrefix profile = do
|
2022-02-07 15:19:34 +04:00
|
|
|
st <- createStore (dbFilePrefix <> "_chat.db") 1 False
|
2022-01-21 11:09:33 +00:00
|
|
|
Right user <- runExceptT $ createUser st profile True
|
2021-07-07 22:46:38 +01:00
|
|
|
t <- withVirtualTerminal termSettings pure
|
2022-01-21 11:09:33 +00:00
|
|
|
ct <- newChatTerminal t
|
2022-04-10 17:13:06 +01:00
|
|
|
cc <- newChatController st (Just user) cfg opts {dbFilePrefix} Nothing -- no notifications
|
|
|
|
chatAsync <- async . runSimplexChat user cc . const $ runChatTerminal ct
|
2021-08-05 20:51:48 +01:00
|
|
|
termQ <- newTQueueIO
|
|
|
|
termAsync <- async $ readTerminalOutput t termQ
|
|
|
|
pure TestCC {chatController = cc, virtualTerminal = t, chatAsync, termAsync, termQ}
|
|
|
|
|
|
|
|
readTerminalOutput :: VirtualTerminal -> TQueue String -> IO ()
|
|
|
|
readTerminalOutput t termQ = do
|
|
|
|
let w = virtualWindow t
|
|
|
|
winVar <- atomically $ newTVar . init =<< readTVar w
|
|
|
|
forever . atomically $ do
|
|
|
|
win <- readTVar winVar
|
|
|
|
win' <- init <$> readTVar w
|
|
|
|
if win' == win
|
|
|
|
then retry
|
|
|
|
else do
|
|
|
|
let diff = getDiff win' win
|
|
|
|
forM_ diff $ writeTQueue termQ
|
|
|
|
writeTVar winVar win'
|
|
|
|
where
|
|
|
|
getDiff :: [String] -> [String] -> [String]
|
|
|
|
getDiff win win' = getDiff_ 1 (length win) win win'
|
|
|
|
getDiff_ :: Int -> Int -> [String] -> [String] -> [String]
|
|
|
|
getDiff_ n len win' win =
|
|
|
|
let diff = drop (len - n) win'
|
|
|
|
in if drop n win <> diff == win'
|
|
|
|
then map (dropWhileEnd (== ' ')) diff
|
|
|
|
else getDiff_ (n + 1) len win' win
|
2021-07-07 22:46:38 +01:00
|
|
|
|
2022-02-06 16:18:01 +00:00
|
|
|
withTmpFiles :: IO () -> IO ()
|
|
|
|
withTmpFiles =
|
2021-07-24 10:26:28 +01:00
|
|
|
bracket_
|
|
|
|
(createDirectoryIfMissing False "tests/tmp")
|
|
|
|
(removeDirectoryRecursive "tests/tmp")
|
2022-02-06 16:18:01 +00:00
|
|
|
|
|
|
|
testChatN :: [Profile] -> ([TestCC] -> IO ()) -> IO ()
|
|
|
|
testChatN ps test = withTmpFiles $ do
|
|
|
|
let envs = zip ps $ map ((testDBPrefix <>) . show) [(1 :: Int) ..]
|
|
|
|
tcs <- getTestCCs envs []
|
|
|
|
test tcs
|
|
|
|
concurrentlyN_ $ map (<// 100000) tcs
|
2021-07-24 10:26:28 +01:00
|
|
|
where
|
2022-04-10 13:30:58 +04:00
|
|
|
getTestCCs :: [(Profile, FilePath)] -> [TestCC] -> IO [TestCC]
|
2021-07-24 10:26:28 +01:00
|
|
|
getTestCCs [] tcs = pure tcs
|
|
|
|
getTestCCs ((p, db) : envs') tcs = (:) <$> virtualSimplexChat db p <*> getTestCCs envs' tcs
|
|
|
|
|
2022-02-02 23:50:43 +04:00
|
|
|
(<//) :: TestCC -> Int -> Expectation
|
|
|
|
(<//) cc t = timeout t (getTermLine cc) `shouldReturn` Nothing
|
|
|
|
|
|
|
|
getTermLine :: TestCC -> IO String
|
|
|
|
getTermLine = atomically . readTQueue . termQ
|
|
|
|
|
2022-03-13 19:34:03 +00:00
|
|
|
-- Use code below to echo virtual terminal
|
2022-04-05 10:01:08 +04:00
|
|
|
-- getTermLine :: TestCC -> IO String
|
2022-03-10 15:45:40 +04:00
|
|
|
-- getTermLine cc = do
|
|
|
|
-- s <- atomically . readTQueue $ termQ cc
|
2022-03-13 19:34:03 +00:00
|
|
|
-- name <- userName cc
|
|
|
|
-- putStrLn $ name <> ": " <> s
|
2022-03-10 15:45:40 +04:00
|
|
|
-- pure s
|
|
|
|
|
2022-03-13 19:34:03 +00:00
|
|
|
userName :: TestCC -> IO [Char]
|
|
|
|
userName (TestCC ChatController {currentUser} _ _ _ _) = T.unpack . localDisplayName . fromJust <$> readTVarIO currentUser
|
|
|
|
|
2021-07-07 22:46:38 +01:00
|
|
|
testChat2 :: Profile -> Profile -> (TestCC -> TestCC -> IO ()) -> IO ()
|
2021-07-24 10:26:28 +01:00
|
|
|
testChat2 p1 p2 test = testChatN [p1, p2] test_
|
|
|
|
where
|
|
|
|
test_ :: [TestCC] -> IO ()
|
|
|
|
test_ [tc1, tc2] = test tc1 tc2
|
|
|
|
test_ _ = error "expected 2 chat clients"
|
|
|
|
|
|
|
|
testChat3 :: Profile -> Profile -> Profile -> (TestCC -> TestCC -> TestCC -> IO ()) -> IO ()
|
|
|
|
testChat3 p1 p2 p3 test = testChatN [p1, p2, p3] test_
|
|
|
|
where
|
|
|
|
test_ :: [TestCC] -> IO ()
|
|
|
|
test_ [tc1, tc2, tc3] = test tc1 tc2 tc3
|
|
|
|
test_ _ = error "expected 3 chat clients"
|
|
|
|
|
|
|
|
testChat4 :: Profile -> Profile -> Profile -> Profile -> (TestCC -> TestCC -> TestCC -> TestCC -> IO ()) -> IO ()
|
|
|
|
testChat4 p1 p2 p3 p4 test = testChatN [p1, p2, p3, p4] test_
|
|
|
|
where
|
|
|
|
test_ :: [TestCC] -> IO ()
|
|
|
|
test_ [tc1, tc2, tc3, tc4] = test tc1 tc2 tc3 tc4
|
|
|
|
test_ _ = error "expected 4 chat clients"
|
|
|
|
|
|
|
|
concurrentlyN_ :: [IO a] -> IO ()
|
|
|
|
concurrentlyN_ = mapConcurrently_ id
|
2021-08-05 20:51:48 +01:00
|
|
|
|
|
|
|
serverCfg :: ServerConfig
|
|
|
|
serverCfg =
|
|
|
|
ServerConfig
|
2022-01-11 08:50:44 +00:00
|
|
|
{ transports = [(serverPort, transport @TLS)],
|
2021-08-05 20:51:48 +01:00
|
|
|
tbqSize = 1,
|
2022-01-06 16:03:45 +00:00
|
|
|
serverTbqSize = 1,
|
2021-09-04 07:32:56 +01:00
|
|
|
msgQueueQuota = 4,
|
2021-08-05 20:51:48 +01:00
|
|
|
queueIdBytes = 12,
|
|
|
|
msgIdBytes = 6,
|
2022-04-21 20:04:22 +01:00
|
|
|
storeLogFile = Nothing,
|
|
|
|
allowNewQueues = True,
|
|
|
|
messageTTL = Just $ 7 * 86400, -- 7 days
|
|
|
|
expireMessagesInterval = Just 21600_000000, -- microseconds, 6 hours
|
2022-01-11 08:50:44 +00:00
|
|
|
caCertificateFile = "tests/fixtures/tls/ca.crt",
|
|
|
|
privateKeyFile = "tests/fixtures/tls/server.key",
|
|
|
|
certificateFile = "tests/fixtures/tls/server.crt"
|
2021-08-05 20:51:48 +01:00
|
|
|
}
|
|
|
|
|
|
|
|
withSmpServer :: IO a -> IO a
|
|
|
|
withSmpServer = serverBracket (`runSMPServerBlocking` serverCfg) (pure ()) . const
|
|
|
|
|
|
|
|
serverBracket :: (TMVar Bool -> IO ()) -> IO () -> (ThreadId -> IO a) -> IO a
|
|
|
|
serverBracket process afterProcess f = do
|
|
|
|
started <- newEmptyTMVarIO
|
|
|
|
bracket
|
|
|
|
(forkIOWithUnmask ($ process started))
|
|
|
|
(\t -> killThread t >> afterProcess >> waitFor started "stop")
|
|
|
|
(\t -> waitFor started "start" >> f t)
|
|
|
|
where
|
|
|
|
waitFor started s =
|
|
|
|
5000000 `timeout` atomically (takeTMVar started) >>= \case
|
|
|
|
Nothing -> error $ "server did not " <> s
|
|
|
|
_ -> pure ()
|