simplex-chat/tests/ChatTests/Local.hs
Alexander Bondarenko daf67c0456
core: add direct xftp upload/download commands (#3781)
* chat: add direct xftp upload/download commands

* adapt to FileDescriptionURI record

* bump simplexmq

* add description uploading

* filter URIs by size

* cleanup

* add file meta to events

* remove focus

* auto-redirect when no URI fits

* send "upload complete" event with the original file id

* remove description upload command

* add index

* refactor

* update simplexmq

* Apply suggestions from code review

Co-authored-by: spaced4ndy <8711996+spaced4ndy@users.noreply.github.com>

* fix /fc command for non-chat uploads

* fix

* rename (tests fail)

* num recipients

* update messages

* split "file complete" events for chats and standalone

* restore xftpSndFileRedirect

* remove unused store error

* add send/cancel test

* untangle standalone views

* fix confused id

* fix /fc and /fs

* resolve comments

* misc fixes

* bump simplexmq

* fix build

* handle redirect errors independently

* fix missing file status in tests

---------

Co-authored-by: spaced4ndy <8711996+spaced4ndy@users.noreply.github.com>
Co-authored-by: Evgeny Poberezkin <evgeny@poberezkin.com>
2024-02-19 10:21:32 +00:00

190 lines
6.9 KiB
Haskell

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PostfixOperators #-}
module ChatTests.Local where
import ChatClient
import ChatTests.ChatList (getChats_)
import ChatTests.Utils
import Data.Time (getCurrentTime)
import Data.Time.Format.ISO8601 (iso8601Show)
import Simplex.Chat.Controller (ChatConfig (..), InlineFilesConfig (..), defaultInlineFilesConfig)
import System.Directory (copyFile, doesFileExist)
import System.FilePath ((</>))
import Test.Hspec hiding (it)
import UnliftIO.Async (concurrently_)
chatLocalChatsTests :: SpecWith FilePath
chatLocalChatsTests = do
describe "note folders" $ do
it "create folders, add notes, read, search" testNotes
it "switch users" testUserNotes
it "preview pagination for notes" testPreviewsPagination
it "chat pagination" testChatPagination
it "stores files" testFiles
it "deleting files does not interfere with other chat types" testOtherFiles
testNotes :: FilePath -> IO ()
testNotes tmp = withNewTestChat tmp "alice" aliceProfile $ \alice -> do
createCCNoteFolder alice
alice ##> "/contacts"
-- not a contact
alice /* "keep in mind"
alice ##> "/tail"
alice <# "* keep in mind"
alice ##> "/chats"
alice <# "* keep in mind"
alice ##> "/? keep"
alice <# "* keep in mind"
alice #$> ("/_read chat *1 from=1 to=100", id, "ok")
alice ##> "/_unread chat *1 on"
alice <## "ok"
alice ##> "/_delete item *1 1 internal"
alice <## "message deleted"
alice ##> "/tail"
alice ##> "/chats"
alice /* "ahoy!"
alice ##> "/_update item *1 1 text Greetings."
alice ##> "/tail *"
alice <# "* Greetings."
testUserNotes :: FilePath -> IO ()
testUserNotes tmp = withNewTestChat tmp "alice" aliceProfile $ \alice -> do
createCCNoteFolder alice
alice /* "keep in mind"
alice ##> "/tail"
alice <# "* keep in mind"
alice ##> "/create user secret"
alice <## "user profile: secret"
alice <## "use /p <display name> to change it"
alice <## "(the updated profile will be sent to all your contacts)"
alice ##> "/tail"
alice ##> "/_delete item *1 1 internal"
alice <## "chat db error: SENoteFolderNotFound {noteFolderId = 1}"
testPreviewsPagination :: FilePath -> IO ()
testPreviewsPagination tmp = withNewTestChat tmp "alice" aliceProfile $ \alice -> do
createCCNoteFolder alice
tsS <- iso8601Show <$> getCurrentTime
alice /* "first"
tsM <- iso8601Show <$> getCurrentTime
alice /* "last"
tsE <- iso8601Show <$> getCurrentTime
-- there's only one folder that got updated after tsM and before tsE
getChats_ alice "count=3" [("*", "last")]
getChats_ alice ("after=" <> tsE <> " count=10") []
getChats_ alice ("after=" <> tsS <> " count=10") [("*", "last")]
getChats_ alice ("before=" <> tsM <> " count=10") []
getChats_ alice ("before=" <> tsE <> " count=10") [("*", "last")]
getChats_ alice ("before=" <> tsS <> " count=10") []
testChatPagination :: FilePath -> IO ()
testChatPagination tmp = withNewTestChat tmp "alice" aliceProfile $ \alice -> do
createCCNoteFolder alice
alice /* "hello world"
alice /* "memento mori"
alice /* "knock-knock"
alice /* "who's there?"
alice #$> ("/_get chat *1 count=100", chat, [(1, "hello world"), (1, "memento mori"), (1, "knock-knock"), (1, "who's there?")])
alice #$> ("/_get chat *1 count=1", chat, [(1, "who's there?")])
alice #$> ("/_get chat *1 after=2 count=10", chat, [(1, "knock-knock"), (1, "who's there?")])
alice #$> ("/_get chat *1 after=2 count=2", chat, [(1, "knock-knock"), (1, "who's there?")])
alice #$> ("/_get chat *1 after=1 count=2", chat, [(1, "memento mori"), (1, "knock-knock")])
alice #$> ("/_get chat *1 before=3 count=10", chat, [(1, "hello world"), (1, "memento mori")])
alice #$> ("/_get chat *1 before=3 count=2", chat, [(1, "hello world"), (1, "memento mori")])
alice #$> ("/_get chat *1 before=4 count=2", chat, [(1, "memento mori"), (1, "knock-knock")])
alice #$> ("/_get chat *1 count=10 search=k-k", chat, [(1, "knock-knock")])
testFiles :: FilePath -> IO ()
testFiles tmp = withNewTestChat tmp "alice" aliceProfile $ \alice -> do
-- setup
createCCNoteFolder alice
let files = "./tests/tmp/app_files"
alice ##> ("/_files_folder " <> files)
alice <## "ok"
-- ui-like upload
let source = "./tests/fixtures/test.jpg"
let stored = files </> "test.jpg"
copyFile source stored
alice ##> "/_create *1 json {\"filePath\": \"test.jpg\", \"msgContent\": {\"text\":\"hi myself\",\"type\":\"image\",\"image\":\"data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAgAAAAIAQMAAAD+wSzIAAAABlBMVEX///+/v7+jQ3Y5AAAADklEQVQI12P4AIX8EAgALgAD/aNpbtEAAAAASUVORK5CYII=\"}}"
alice <# "* hi myself"
alice <# "* file 1 (test.jpg)"
alice ##> "/tail"
alice <# "* hi myself"
alice <# "* file 1 (test.jpg)"
alice ##> "/_get chat *1 count=100"
r <- chatF <$> getTermLine alice
r `shouldBe` [((1, "hi myself"), Just "test.jpg")]
alice ##> "/fs 1"
alice <## "bad chat command: not supported for local files"
alice ##> "/fc 1"
alice <## "chat db error: SELocalFileNoTransfer {fileId = 1}"
-- one more file
let stored2 = files </> "another_test.jpg"
copyFile source stored2
alice ##> "/_create *1 json {\"filePath\": \"another_test.jpg\", \"msgContent\": {\"text\":\"\",\"type\":\"image\",\"image\":\"data:image/png;base64,iVBORw0KGgoAAAANSUhEUgAAAAgAAAAIAQMAAAD+wSzIAAAABlBMVEX///+/v7+jQ3Y5AAAADklEQVQI12P4AIX8EAgALgAD/aNpbtEAAAAASUVORK5CYII=\"}}"
alice <# "* file 2 (another_test.jpg)"
alice ##> "/_delete item *1 2 internal"
alice <## "message deleted"
doesFileExist stored2 `shouldReturn` False
doesFileExist stored `shouldReturn` True
alice ##> "/clear *"
alice ##> "/fs 1"
alice <## "file 1 not found"
alice ##> "/tail"
doesFileExist stored `shouldReturn` False
testOtherFiles :: FilePath -> IO ()
testOtherFiles =
testChatCfg2 cfg aliceProfile bobProfile $ \alice bob -> do
connectUsers alice bob
createCCNoteFolder bob
bob ##> "/_files_folder ./tests/tmp/"
bob <## "ok"
alice ##> "/_send @2 json {\"msgContent\":{\"type\":\"voice\", \"duration\":10, \"text\":\"\"}, \"filePath\":\"./tests/fixtures/test.jpg\"}"
alice <# "@bob voice message (00:10)"
alice <# "/f @bob ./tests/fixtures/test.jpg"
-- below is not shown in "sent" mode
-- alice <## "use /fc 1 to cancel sending"
bob <# "alice> voice message (00:10)"
bob <# "alice> sends file test.jpg (136.5 KiB / 139737 bytes)"
-- below is not shown in "sent" mode
-- bob <## "use /fr 1 [<dir>/ | <path>] to receive it"
bob <## "started receiving file 1 (test.jpg) from alice"
concurrently_
(alice <## "completed sending file 1 (test.jpg) to bob")
(bob <## "completed receiving file 1 (test.jpg) from alice")
bob /* "test"
bob ##> "/tail *"
bob <# "* test"
bob ##> "/clear *"
bob ##> "/tail *"
bob ##> "/fs 1"
bob <## "receiving file 1 (test.jpg) complete, path: test.jpg"
doesFileExist "./tests/tmp/test.jpg" `shouldReturn` True
where
cfg = testCfg {inlineFiles = defaultInlineFilesConfig {offerChunks = 100, sendChunks = 100, receiveChunks = 100}}