{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PostfixOperators #-} module ChatTests.Forward where import ChatClient import ChatTests.DBUtils import ChatTests.Utils import Control.Concurrent (threadDelay) import qualified Data.ByteString.Char8 as B import Data.List (intercalate) import qualified Data.Text as T import Simplex.Chat.Library.Commands (fixedImagePreview) import Simplex.Chat.Types (ImageData (..)) import System.Directory (copyFile, doesFileExist, removeFile) import Test.Hspec hiding (it) chatForwardTests :: SpecWith TestParams chatForwardTests = do describe "forward messages" $ do it "from contact to contact" testForwardContactToContact it "from contact to group" testForwardContactToGroup it "from contact to notes" testForwardContactToNotes it "from group to contact" testForwardGroupToContact it "from group to group" testForwardGroupToGroup it "from group to notes" testForwardGroupToNotes it "from notes to contact" testForwardNotesToContact it "from notes to group" testForwardNotesToGroup it "from notes to notes" testForwardNotesToNotes -- TODO forward between different folders when supported describe "interactions with forwarded messages" $ do it "preserve original forward info" testForwardPreserveInfo it "received forwarded message is saved with new forward info" testForwardRcvMsgNewInfo it "quoted message is not included" testForwardQuotedMsg it "editing is prohibited" testForwardEditProhibited it "delete for other" testForwardDeleteForOther describe "forward files" $ do it "from contact to contact" testForwardFileNoFilesFolder it "with relative paths: from contact to contact" testForwardFileContactToContact it "with relative paths: from group to notes" testForwardFileGroupToNotes it "with relative paths: from notes to group" testForwardFileNotesToGroup describe "multi forward api" $ do it "from contact to contact" testForwardContactToContactMulti it "from group to group" testForwardGroupToGroupMulti it "with relative paths: multiple files from contact to contact" testMultiForwardFiles testForwardContactToContact :: HasCallStack => TestParams -> IO () testForwardContactToContact = testChat3 aliceProfile bobProfile cathProfile $ \alice bob cath -> do connectUsers alice bob connectUsers alice cath connectUsers bob cath alice #> "@bob hi" bob <# "alice> hi" msgId <- lastItemId alice bob #> "@alice hey" alice <# "bob> hey" alice ##> ("/_forward @3 @2 " <> msgId) alice <# "@cath <- you @bob" alice <## " hi" cath <# "alice> -> forwarded" cath <## " hi" alice `send` "@cath <- @bob hey" alice <# "@cath <- @bob" alice <## " hey" cath <# "alice> -> forwarded" cath <## " hey" -- read chat alice ##> "/tail @cath 2" alice <# "@cath <- you @bob" alice <## " hi" alice <# "@cath <- @bob" alice <## " hey" cath ##> "/tail @alice 2" cath <# "alice> -> forwarded" cath <## " hi" cath <# "alice> -> forwarded" cath <## " hey" -- item info alice ##> "/item info @cath hey" alice <##. "sent at: " alice <## "message history:" alice .<## ": hey" alice <##. "forwarded from: @bob, chat item id:" testForwardContactToGroup :: HasCallStack => TestParams -> IO () testForwardContactToGroup = testChat3 aliceProfile bobProfile cathProfile $ \alice bob cath -> do connectUsers alice bob createGroup2 "team" alice cath alice #> "@bob hi" bob <# "alice> hi" bob #> "@alice hey" alice <# "bob> hey" alice `send` "#team <- @bob hi" alice <# "#team <- you @bob" alice <## " hi" cath <# "#team alice> -> forwarded" cath <## " hi" alice `send` "#team <- @bob hey" alice <# "#team <- @bob" alice <## " hey" cath <# "#team alice> -> forwarded" cath <## " hey" testForwardContactToNotes :: HasCallStack => TestParams -> IO () testForwardContactToNotes = testChat2 aliceProfile bobProfile $ \alice bob -> do createCCNoteFolder alice connectUsers alice bob alice #> "@bob hi" bob <# "alice> hi" bob #> "@alice hey" alice <# "bob> hey" alice `send` "* <- @bob hi" alice <# "* <- you @bob" alice <## " hi" alice `send` "* <- @bob hey" alice <# "* <- @bob" alice <## " hey" testForwardGroupToContact :: HasCallStack => TestParams -> IO () testForwardGroupToContact = testChat3 aliceProfile bobProfile cathProfile $ \alice bob cath -> do createGroup2 "team" alice bob connectUsers alice cath alice #> "#team hi" bob <# "#team alice> hi" bob #> "#team hey" alice <# "#team bob> hey" alice `send` "@cath <- #team hi" alice <# "@cath <- you #team" alice <## " hi" cath <# "alice> -> forwarded" cath <## " hi" alice `send` "@cath <- #team @bob hey" alice <# "@cath <- #team" alice <## " hey" cath <# "alice> -> forwarded" cath <## " hey" testForwardGroupToGroup :: HasCallStack => TestParams -> IO () testForwardGroupToGroup = testChat3 aliceProfile bobProfile cathProfile $ \alice bob cath -> do createGroup2 "team" alice bob createGroup2 "club" alice cath alice #> "#team hi" bob <# "#team alice> hi" bob #> "#team hey" alice <# "#team bob> hey" threadDelay 1000000 alice `send` "#club <- #team hi" alice <# "#club <- you #team" alice <## " hi" cath <# "#club alice> -> forwarded" cath <## " hi" threadDelay 1000000 alice `send` "#club <- #team hey" alice <# "#club <- #team" alice <## " hey" cath <# "#club alice> -> forwarded" cath <## " hey" -- read chat alice ##> "/tail #club 2" alice <# "#club <- you #team" alice <## " hi" alice <# "#club <- #team" alice <## " hey" cath ##> "/tail #club 2" cath <# "#club alice> -> forwarded" cath <## " hi" cath <# "#club alice> -> forwarded" cath <## " hey" testForwardGroupToNotes :: HasCallStack => TestParams -> IO () testForwardGroupToNotes = testChat2 aliceProfile bobProfile $ \alice bob -> do createCCNoteFolder alice createGroup2 "team" alice bob alice #> "#team hi" bob <# "#team alice> hi" bob #> "#team hey" alice <# "#team bob> hey" alice `send` "* <- #team hi" alice <# "* <- you #team" alice <## " hi" alice `send` "* <- #team hey" alice <# "* <- #team" alice <## " hey" testForwardNotesToContact :: HasCallStack => TestParams -> IO () testForwardNotesToContact = testChat2 aliceProfile cathProfile $ \alice cath -> do createCCNoteFolder alice connectUsers alice cath alice >* "hi" alice `send` "@cath <- * hi" alice <# "@cath hi" cath <# "alice> hi" testForwardNotesToGroup :: HasCallStack => TestParams -> IO () testForwardNotesToGroup = testChat2 aliceProfile cathProfile $ \alice cath -> do createCCNoteFolder alice createGroup2 "team" alice cath alice >* "hi" alice `send` "#team <- * hi" alice <# "#team hi" cath <# "#team alice> hi" testForwardNotesToNotes :: HasCallStack => TestParams -> IO () testForwardNotesToNotes ps = withNewTestChat ps "alice" aliceProfile $ \alice -> do createCCNoteFolder alice alice >* "hi" alice `send` "* <- * hi" alice <# "* hi" alice ##> "/tail * 2" alice <# "* hi" alice <# "* hi" testForwardPreserveInfo :: HasCallStack => TestParams -> IO () testForwardPreserveInfo = testChat4 aliceProfile bobProfile cathProfile danProfile $ \alice bob cath dan -> do createCCNoteFolder alice connectUsers alice bob connectUsers alice cath createGroup2 "team" alice dan bob #> "@alice hey" alice <# "bob> hey" alice `send` "* <- @bob hey" alice <# "* <- @bob" alice <## " hey" alice `send` "@cath <- * hey" alice <# "@cath <- @bob" alice <## " hey" cath <# "alice> -> forwarded" cath <## " hey" alice `send` "#team <- @cath hey" alice <# "#team <- @bob" alice <## " hey" dan <# "#team alice> -> forwarded" dan <## " hey" testForwardRcvMsgNewInfo :: HasCallStack => TestParams -> IO () testForwardRcvMsgNewInfo = testChat4 aliceProfile bobProfile cathProfile danProfile $ \alice bob cath dan -> do connectUsers bob dan createCCNoteFolder alice connectUsers alice bob connectUsers alice cath dan #> "@bob hey" bob <# "dan> hey" bob `send` "@alice <- @dan hey" bob <# "@alice <- @dan" bob <## " hey" alice <# "bob> -> forwarded" alice <## " hey" alice `send` "* <- @bob hey" alice <# "* <- @bob" alice <## " hey" alice `send` "@cath <- * hey" alice <# "@cath <- @bob" alice <## " hey" cath <# "alice> -> forwarded" cath <## " hey" testForwardQuotedMsg :: HasCallStack => TestParams -> IO () testForwardQuotedMsg = testChat3 aliceProfile bobProfile cathProfile $ \alice bob cath -> do connectUsers alice bob connectUsers alice cath alice #> "@bob hi" bob <# "alice> hi" bob `send` "> @alice (hi) hey" bob <# "@alice > hi" bob <## " hey" alice <# "bob> > hi" alice <## " hey" alice `send` "@cath <- @bob hey" alice <# "@cath <- @bob" alice <## " hey" cath <# "alice> -> forwarded" cath <## " hey" -- read chat alice ##> "/tail @cath 1" alice <# "@cath <- @bob" alice <## " hey" cath ##> "/tail @alice 1" cath <# "alice> -> forwarded" cath <## " hey" testForwardEditProhibited :: HasCallStack => TestParams -> IO () testForwardEditProhibited = testChat3 aliceProfile bobProfile cathProfile $ \alice bob cath -> do connectUsers alice bob connectUsers alice cath bob #> "@alice hey" alice <# "bob> hey" alice `send` "@cath <- @bob hey" alice <# "@cath <- @bob" alice <## " hey" cath <# "alice> -> forwarded" cath <## " hey" msgId <- lastItemId alice alice ##> ("/_update item @3 " <> msgId <> " text hey edited") alice <## "cannot update this item" testForwardDeleteForOther :: HasCallStack => TestParams -> IO () testForwardDeleteForOther = testChat3 aliceProfile bobProfile cathProfile $ \alice bob cath -> do connectUsers alice bob connectUsers alice cath bob #> "@alice hey" alice <# "bob> hey" alice `send` "@cath <- @bob hey" alice <# "@cath <- @bob" alice <## " hey" cath <# "alice> -> forwarded" cath <## " hey" msgId <- lastItemId alice alice ##> ("/_delete item @3 " <> msgId <> " broadcast") alice <## "message marked deleted" cath <# "alice> [marked deleted] hey" testForwardFileNoFilesFolder :: HasCallStack => TestParams -> IO () testForwardFileNoFilesFolder = testChat3 aliceProfile bobProfile cathProfile $ \alice bob cath -> withXFTPServer $ do connectUsers alice bob connectUsers bob cath -- send original file alice ##> "/_send @2 json [{\"filePath\": \"./tests/fixtures/test.pdf\", \"msgContent\": {\"type\": \"text\", \"text\": \"hi\"}}]" alice <# "@bob hi" alice <# "/f @bob ./tests/fixtures/test.pdf" alice <## "use /fc 1 to cancel sending" bob <# "alice> hi" bob <# "alice> sends file test.pdf (266.0 KiB / 272376 bytes)" bob <## "use /fr 1 [