2023-10-04 18:36:10 +03:00
|
|
|
{-# LANGUAGE DuplicateRecordFields #-}
|
|
|
|
{-# LANGUAGE LambdaCase #-}
|
|
|
|
{-# LANGUAGE NamedFieldPuns #-}
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
|
|
|
module RemoteTests where
|
|
|
|
|
2023-11-01 12:48:58 +02:00
|
|
|
import Simplex.Chat.Remote.RevHTTP
|
|
|
|
import qualified Simplex.RemoteControl.Discovery as Discovery
|
|
|
|
import Simplex.RemoteControl.Types
|
2023-10-04 18:36:10 +03:00
|
|
|
import ChatClient
|
|
|
|
import ChatTests.Utils
|
2023-10-22 11:42:19 +03:00
|
|
|
import Control.Logger.Simple
|
2023-10-29 19:06:32 +00:00
|
|
|
import qualified Data.Aeson as J
|
2023-10-11 11:45:05 +03:00
|
|
|
import qualified Data.ByteString as B
|
2023-10-29 19:06:32 +00:00
|
|
|
import qualified Data.ByteString.Lazy.Char8 as LB
|
2023-10-04 18:36:10 +03:00
|
|
|
import Data.List.NonEmpty (NonEmpty (..))
|
2023-10-11 11:45:05 +03:00
|
|
|
import qualified Data.Map.Strict as M
|
2023-10-30 16:00:54 +02:00
|
|
|
import Data.String (fromString)
|
2023-10-04 18:36:10 +03:00
|
|
|
import Network.HTTP.Types (ok200)
|
|
|
|
import qualified Network.HTTP2.Client as C
|
|
|
|
import qualified Network.HTTP2.Server as S
|
|
|
|
import qualified Network.Socket as N
|
|
|
|
import qualified Network.TLS as TLS
|
2023-10-29 19:06:32 +00:00
|
|
|
import Simplex.Chat.Archive (archiveFilesFolder)
|
|
|
|
import Simplex.Chat.Controller (ChatConfig (..), XFTPFileConfig (..))
|
2023-10-11 11:45:05 +03:00
|
|
|
import qualified Simplex.Chat.Controller as Controller
|
2023-10-29 19:06:32 +00:00
|
|
|
import Simplex.Chat.Mobile.File
|
2023-10-30 16:00:54 +02:00
|
|
|
import Simplex.Chat.Remote.Types
|
2023-10-04 18:36:10 +03:00
|
|
|
import qualified Simplex.Messaging.Crypto as C
|
2023-10-29 19:06:32 +00:00
|
|
|
import Simplex.Messaging.Crypto.File (CryptoFileArgs (..))
|
2023-10-30 16:00:54 +02:00
|
|
|
import Simplex.Messaging.Encoding (smpDecode)
|
|
|
|
import Simplex.Messaging.Encoding.String (strDecode, strEncode)
|
2023-10-04 18:36:10 +03:00
|
|
|
import Simplex.Messaging.Transport.Client (TransportHost (..))
|
|
|
|
import Simplex.Messaging.Transport.Credentials (genCredentials, tlsCredentials)
|
|
|
|
import Simplex.Messaging.Transport.HTTP2.Client (HTTP2Response (..), closeHTTP2Client, sendRequest)
|
|
|
|
import Simplex.Messaging.Transport.HTTP2.Server (HTTP2Request (..))
|
2023-10-22 11:42:19 +03:00
|
|
|
import Simplex.Messaging.Util
|
2023-10-29 19:06:32 +00:00
|
|
|
import System.FilePath ((</>))
|
2023-10-04 18:36:10 +03:00
|
|
|
import Test.Hspec
|
|
|
|
import UnliftIO
|
2023-10-22 11:42:19 +03:00
|
|
|
import UnliftIO.Concurrent
|
2023-10-11 11:45:05 +03:00
|
|
|
import UnliftIO.Directory
|
2023-10-04 18:36:10 +03:00
|
|
|
|
|
|
|
remoteTests :: SpecWith FilePath
|
2023-10-22 11:42:19 +03:00
|
|
|
remoteTests = describe "Remote" $ do
|
2023-11-01 12:48:58 +02:00
|
|
|
-- it "generates usable credentials" genCredentialsTest
|
|
|
|
-- it "OOB encoding, decoding, and signatures are correct" oobCodecTest
|
2023-10-04 18:36:10 +03:00
|
|
|
it "connects announcer with discoverer over reverse-http2" announceDiscoverHttp2Test
|
2023-10-22 11:42:19 +03:00
|
|
|
it "performs protocol handshake" remoteHandshakeTest
|
|
|
|
it "performs protocol handshake (again)" remoteHandshakeTest -- leaking servers regression check
|
|
|
|
it "sends messages" remoteMessageTest
|
2023-10-29 19:06:32 +00:00
|
|
|
describe "remote files" $ do
|
|
|
|
it "store/get/send/receive files" remoteStoreFileTest
|
|
|
|
it "should sends files from CLI wihtout /store" remoteCLIFileTest
|
2023-10-04 18:36:10 +03:00
|
|
|
|
|
|
|
-- * Low-level TLS with ephemeral credentials
|
|
|
|
|
2023-11-01 12:48:58 +02:00
|
|
|
-- -- XXX: extract
|
|
|
|
-- genCredentialsTest :: (HasCallStack) => FilePath -> IO ()
|
|
|
|
-- genCredentialsTest _tmp = do
|
|
|
|
-- (fingerprint, credentials) <- genTestCredentials
|
|
|
|
-- started <- newEmptyTMVarIO
|
|
|
|
-- bracket (startTLSServer started credentials serverHandler) cancel $ \_server -> do
|
|
|
|
-- ok <- atomically (readTMVar started)
|
|
|
|
-- port <- maybe (error "TLS server failed to start") pure ok
|
|
|
|
-- logNote $ "Assigned port: " <> tshow port
|
|
|
|
-- connectTLSClient ("127.0.0.1", fromIntegral port) fingerprint clientHandler
|
|
|
|
-- where
|
|
|
|
-- serverHandler serverTls = do
|
|
|
|
-- logNote "Sending from server"
|
|
|
|
-- Transport.putLn serverTls "hi client"
|
|
|
|
-- logNote "Reading from server"
|
|
|
|
-- Transport.getLn serverTls `shouldReturn` "hi server"
|
|
|
|
-- clientHandler clientTls = do
|
|
|
|
-- logNote "Sending from client"
|
|
|
|
-- Transport.putLn clientTls "hi server"
|
|
|
|
-- logNote "Reading from client"
|
|
|
|
-- Transport.getLn clientTls `shouldReturn` "hi client"
|
2023-10-04 18:36:10 +03:00
|
|
|
|
|
|
|
-- * UDP discovery and rever HTTP2
|
|
|
|
|
2023-11-01 12:48:58 +02:00
|
|
|
-- oobCodecTest :: (HasCallStack) => FilePath -> IO ()
|
|
|
|
-- oobCodecTest _tmp = do
|
|
|
|
-- subscribers <- newTMVarIO 0
|
|
|
|
-- localAddr <- Discovery.getLocalAddress subscribers >>= maybe (fail "unable to get local address") pure
|
|
|
|
-- (fingerprint, _credentials) <- genTestCredentials
|
|
|
|
-- (_dhKey, _sigKey, _ann, signedOOB@(SignedOOB oob _sig)) <- Discovery.startSession (Just "Desktop") (localAddr, read Discovery.DISCOVERY_PORT) fingerprint
|
|
|
|
-- verifySignedOOB signedOOB `shouldBe` True
|
|
|
|
-- strDecode (strEncode oob) `shouldBe` Right oob
|
|
|
|
-- strDecode (strEncode signedOOB) `shouldBe` Right signedOOB
|
2023-10-30 16:00:54 +02:00
|
|
|
|
2023-10-04 18:36:10 +03:00
|
|
|
announceDiscoverHttp2Test :: (HasCallStack) => FilePath -> IO ()
|
|
|
|
announceDiscoverHttp2Test _tmp = do
|
2023-10-30 16:00:54 +02:00
|
|
|
subscribers <- newTMVarIO 0
|
|
|
|
localAddr <- Discovery.getLocalAddress subscribers >>= maybe (fail "unable to get local address") pure
|
2023-10-04 18:36:10 +03:00
|
|
|
(fingerprint, credentials) <- genTestCredentials
|
2023-10-30 16:00:54 +02:00
|
|
|
(_dhKey, sigKey, ann, _oob) <- Discovery.startSession (Just "Desktop") (localAddr, read Discovery.DISCOVERY_PORT) fingerprint
|
2023-10-22 11:42:19 +03:00
|
|
|
tasks <- newTVarIO []
|
2023-10-04 18:36:10 +03:00
|
|
|
finished <- newEmptyMVar
|
2023-10-07 16:23:24 +03:00
|
|
|
controller <- async $ do
|
2023-10-22 11:42:19 +03:00
|
|
|
logNote "Controller: starting"
|
2023-10-07 16:23:24 +03:00
|
|
|
bracket
|
2023-11-01 12:48:58 +02:00
|
|
|
(announceRevHTTP2 tasks (sigKey, ann) credentials (putMVar finished ()) >>= either (fail . show) pure)
|
2023-10-07 16:23:24 +03:00
|
|
|
closeHTTP2Client
|
|
|
|
( \http -> do
|
2023-10-22 11:42:19 +03:00
|
|
|
logNote "Controller: got client"
|
2023-10-07 16:23:24 +03:00
|
|
|
sendRequest http (C.requestNoBody "GET" "/" []) (Just 10000000) >>= \case
|
|
|
|
Left err -> do
|
2023-10-22 11:42:19 +03:00
|
|
|
logNote "Controller: got error"
|
2023-10-07 16:23:24 +03:00
|
|
|
fail $ show err
|
|
|
|
Right HTTP2Response {} ->
|
2023-10-22 11:42:19 +03:00
|
|
|
logNote "Controller: got response"
|
2023-10-07 16:23:24 +03:00
|
|
|
)
|
2023-10-30 16:00:54 +02:00
|
|
|
host <- async $ Discovery.withListener subscribers $ \sock -> do
|
|
|
|
(N.SockAddrInet _port addr, sigAnn) <- Discovery.recvAnnounce sock
|
|
|
|
SignedAnnounce Announce {caFingerprint, serviceAddress=(hostAddr, port)} _sig <- either fail pure $ smpDecode sigAnn
|
|
|
|
caFingerprint `shouldBe` fingerprint
|
|
|
|
addr `shouldBe` hostAddr
|
|
|
|
let service = (THIPv4 $ N.hostAddressToTuple hostAddr, port)
|
|
|
|
logNote $ "Host: connecting to " <> tshow service
|
|
|
|
server <- async $ Discovery.connectTLSClient service fingerprint $ \tls -> do
|
2023-10-22 11:42:19 +03:00
|
|
|
logNote "Host: got tls"
|
2023-11-01 12:48:58 +02:00
|
|
|
flip attachHTTP2Server tls $ \HTTP2Request {sendResponse} -> do
|
2023-10-22 11:42:19 +03:00
|
|
|
logNote "Host: got request"
|
2023-10-04 18:36:10 +03:00
|
|
|
sendResponse $ S.responseNoBody ok200 []
|
2023-10-22 11:42:19 +03:00
|
|
|
logNote "Host: sent response"
|
2023-10-07 16:23:24 +03:00
|
|
|
takeMVar finished `finally` cancel server
|
2023-10-22 11:42:19 +03:00
|
|
|
logNote "Host: finished"
|
|
|
|
tasks `registerAsync` controller
|
|
|
|
tasks `registerAsync` host
|
|
|
|
(waitBoth host controller `shouldReturn` ((), ())) `finally` cancelTasks tasks
|
2023-10-04 18:36:10 +03:00
|
|
|
|
|
|
|
-- * Chat commands
|
|
|
|
|
2023-10-07 16:23:24 +03:00
|
|
|
remoteHandshakeTest :: (HasCallStack) => FilePath -> IO ()
|
2023-10-04 18:36:10 +03:00
|
|
|
remoteHandshakeTest = testChat2 aliceProfile bobProfile $ \desktop mobile -> do
|
|
|
|
desktop ##> "/list remote hosts"
|
|
|
|
desktop <## "No remote hosts"
|
|
|
|
|
2023-10-22 11:42:19 +03:00
|
|
|
startRemote mobile desktop
|
2023-10-04 18:36:10 +03:00
|
|
|
|
2023-10-22 11:42:19 +03:00
|
|
|
logNote "Session active"
|
2023-10-13 20:53:04 +03:00
|
|
|
|
|
|
|
desktop ##> "/list remote hosts"
|
|
|
|
desktop <## "Remote hosts:"
|
2023-10-22 11:42:19 +03:00
|
|
|
desktop <## "1. (active)"
|
2023-10-04 18:36:10 +03:00
|
|
|
mobile ##> "/list remote ctrls"
|
2023-10-13 20:53:04 +03:00
|
|
|
mobile <## "Remote controllers:"
|
2023-10-14 13:10:06 +01:00
|
|
|
mobile <## "1. My desktop (active)"
|
2023-10-04 18:36:10 +03:00
|
|
|
|
2023-10-22 11:42:19 +03:00
|
|
|
stopMobile mobile desktop `catchAny` (logError . tshow)
|
|
|
|
-- TODO: add a case for 'stopDesktop'
|
|
|
|
|
2023-10-04 18:36:10 +03:00
|
|
|
desktop ##> "/delete remote host 1"
|
2023-10-13 22:35:30 +01:00
|
|
|
desktop <## "ok"
|
2023-10-04 18:36:10 +03:00
|
|
|
desktop ##> "/list remote hosts"
|
|
|
|
desktop <## "No remote hosts"
|
|
|
|
|
2023-10-13 20:53:04 +03:00
|
|
|
mobile ##> "/delete remote ctrl 1"
|
2023-10-13 22:35:30 +01:00
|
|
|
mobile <## "ok"
|
2023-10-13 20:53:04 +03:00
|
|
|
mobile ##> "/list remote ctrls"
|
|
|
|
mobile <## "No remote controllers"
|
|
|
|
|
2023-10-22 11:42:19 +03:00
|
|
|
remoteMessageTest :: (HasCallStack) => FilePath -> IO ()
|
|
|
|
remoteMessageTest = testChat3 aliceProfile aliceDesktopProfile bobProfile $ \mobile desktop bob -> do
|
|
|
|
startRemote mobile desktop
|
|
|
|
contactBob desktop bob
|
|
|
|
|
|
|
|
logNote "sending messages"
|
|
|
|
desktop #> "@bob hello there 🙂"
|
|
|
|
bob <# "alice> hello there 🙂"
|
|
|
|
bob #> "@alice hi"
|
|
|
|
desktop <# "bob> hi"
|
|
|
|
|
|
|
|
logNote "post-remote checks"
|
|
|
|
stopMobile mobile desktop
|
|
|
|
|
|
|
|
mobile ##> "/contacts"
|
|
|
|
mobile <## "bob (Bob)"
|
|
|
|
|
|
|
|
bob ##> "/contacts"
|
|
|
|
bob <## "alice (Alice)"
|
|
|
|
|
|
|
|
desktop ##> "/contacts"
|
|
|
|
-- empty contact list on desktop-local
|
|
|
|
|
|
|
|
threadDelay 1000000
|
|
|
|
logNote "done"
|
|
|
|
|
2023-10-29 19:06:32 +00:00
|
|
|
remoteStoreFileTest :: HasCallStack => FilePath -> IO ()
|
|
|
|
remoteStoreFileTest =
|
|
|
|
testChatCfg3 cfg aliceProfile aliceDesktopProfile bobProfile $ \mobile desktop bob ->
|
|
|
|
withXFTPServer $ do
|
|
|
|
let mobileFiles = "./tests/tmp/mobile_files"
|
|
|
|
mobile ##> ("/_files_folder " <> mobileFiles)
|
|
|
|
mobile <## "ok"
|
|
|
|
let desktopFiles = "./tests/tmp/desktop_files"
|
|
|
|
desktop ##> ("/_files_folder " <> desktopFiles)
|
|
|
|
desktop <## "ok"
|
|
|
|
let desktopHostFiles = "./tests/tmp/remote_hosts_data"
|
|
|
|
desktop ##> ("/remote_hosts_folder " <> desktopHostFiles)
|
|
|
|
desktop <## "ok"
|
|
|
|
let bobFiles = "./tests/tmp/bob_files"
|
|
|
|
bob ##> ("/_files_folder " <> bobFiles)
|
|
|
|
bob <## "ok"
|
|
|
|
startRemote mobile desktop
|
|
|
|
contactBob desktop bob
|
|
|
|
rhs <- readTVarIO (Controller.remoteHostSessions $ chatController desktop)
|
|
|
|
desktopHostStore <- case M.lookup 1 rhs of
|
|
|
|
Just RemoteHostSession {storePath} -> pure $ desktopHostFiles </> storePath </> archiveFilesFolder
|
|
|
|
_ -> fail "Host session 1 should be started"
|
|
|
|
desktop ##> "/store remote file 1 tests/fixtures/test.pdf"
|
|
|
|
desktop <## "file test.pdf stored on remote host 1"
|
|
|
|
src <- B.readFile "tests/fixtures/test.pdf"
|
|
|
|
B.readFile (mobileFiles </> "test.pdf") `shouldReturn` src
|
|
|
|
B.readFile (desktopHostStore </> "test.pdf") `shouldReturn` src
|
|
|
|
desktop ##> "/store remote file 1 tests/fixtures/test.pdf"
|
|
|
|
desktop <## "file test_1.pdf stored on remote host 1"
|
|
|
|
B.readFile (mobileFiles </> "test_1.pdf") `shouldReturn` src
|
|
|
|
B.readFile (desktopHostStore </> "test_1.pdf") `shouldReturn` src
|
|
|
|
desktop ##> "/store remote file 1 encrypt=on tests/fixtures/test.pdf"
|
|
|
|
desktop <## "file test_2.pdf stored on remote host 1"
|
|
|
|
Just cfArgs@(CFArgs key nonce) <- J.decode . LB.pack <$> getTermLine desktop
|
|
|
|
chatReadFile (mobileFiles </> "test_2.pdf") (strEncode key) (strEncode nonce) `shouldReturn` Right (LB.fromStrict src)
|
|
|
|
chatReadFile (desktopHostStore </> "test_2.pdf") (strEncode key) (strEncode nonce) `shouldReturn` Right (LB.fromStrict src)
|
|
|
|
|
|
|
|
removeFile (desktopHostStore </> "test_1.pdf")
|
|
|
|
removeFile (desktopHostStore </> "test_2.pdf")
|
|
|
|
|
|
|
|
-- cannot get file before it is used
|
|
|
|
desktop ##> "/get remote file 1 {\"userId\": 1, \"fileId\": 1, \"sent\": true, \"fileSource\": {\"filePath\": \"test_1.pdf\"}}"
|
|
|
|
hostError desktop "SEFileNotFound"
|
|
|
|
-- send file not encrypted locally on mobile host
|
|
|
|
desktop ##> "/_send @2 json {\"filePath\": \"test_1.pdf\", \"msgContent\": {\"type\": \"file\", \"text\": \"sending a file\"}}"
|
|
|
|
desktop <# "@bob sending a file"
|
2023-10-30 16:00:54 +02:00
|
|
|
desktop <# "/f @bob test_1.pdf"
|
2023-10-29 19:06:32 +00:00
|
|
|
desktop <## "use /fc 1 to cancel sending"
|
|
|
|
bob <# "alice> sending a file"
|
|
|
|
bob <# "alice> sends file test_1.pdf (266.0 KiB / 272376 bytes)"
|
|
|
|
bob <## "use /fr 1 [<dir>/ | <path>] to receive it"
|
|
|
|
bob ##> "/fr 1"
|
|
|
|
concurrentlyN_
|
|
|
|
[ do
|
|
|
|
desktop <## "completed uploading file 1 (test_1.pdf) for bob",
|
|
|
|
do
|
|
|
|
bob <## "saving file 1 from alice to test_1.pdf"
|
|
|
|
bob <## "started receiving file 1 (test_1.pdf) from alice"
|
|
|
|
bob <## "completed receiving file 1 (test_1.pdf) from alice"
|
|
|
|
]
|
|
|
|
B.readFile (bobFiles </> "test_1.pdf") `shouldReturn` src
|
|
|
|
-- returns error for inactive user
|
|
|
|
desktop ##> "/get remote file 1 {\"userId\": 2, \"fileId\": 1, \"sent\": true, \"fileSource\": {\"filePath\": \"test_1.pdf\"}}"
|
|
|
|
hostError desktop "CEDifferentActiveUser"
|
|
|
|
-- returns error with incorrect file ID
|
|
|
|
desktop ##> "/get remote file 1 {\"userId\": 1, \"fileId\": 2, \"sent\": true, \"fileSource\": {\"filePath\": \"test_1.pdf\"}}"
|
|
|
|
hostError desktop "SEFileNotFound"
|
|
|
|
-- gets file
|
|
|
|
doesFileExist (desktopHostStore </> "test_1.pdf") `shouldReturn` False
|
|
|
|
desktop ##> "/get remote file 1 {\"userId\": 1, \"fileId\": 1, \"sent\": true, \"fileSource\": {\"filePath\": \"test_1.pdf\"}}"
|
|
|
|
desktop <## "ok"
|
|
|
|
B.readFile (desktopHostStore </> "test_1.pdf") `shouldReturn` src
|
|
|
|
|
|
|
|
-- send file encrypted locally on mobile host
|
|
|
|
desktop ##> ("/_send @2 json {\"fileSource\": {\"filePath\":\"test_2.pdf\", \"cryptoArgs\": " <> LB.unpack (J.encode cfArgs) <> "}, \"msgContent\": {\"type\": \"file\", \"text\": \"\"}}")
|
2023-10-30 16:00:54 +02:00
|
|
|
desktop <# "/f @bob test_2.pdf"
|
2023-10-29 19:06:32 +00:00
|
|
|
desktop <## "use /fc 2 to cancel sending"
|
|
|
|
bob <# "alice> sends file test_2.pdf (266.0 KiB / 272376 bytes)"
|
|
|
|
bob <## "use /fr 2 [<dir>/ | <path>] to receive it"
|
|
|
|
bob ##> "/fr 2"
|
|
|
|
concurrentlyN_
|
|
|
|
[ do
|
|
|
|
desktop <## "completed uploading file 2 (test_2.pdf) for bob",
|
|
|
|
do
|
|
|
|
bob <## "saving file 2 from alice to test_2.pdf"
|
|
|
|
bob <## "started receiving file 2 (test_2.pdf) from alice"
|
|
|
|
bob <## "completed receiving file 2 (test_2.pdf) from alice"
|
|
|
|
]
|
|
|
|
B.readFile (bobFiles </> "test_2.pdf") `shouldReturn` src
|
|
|
|
|
|
|
|
-- receive file via remote host
|
|
|
|
copyFile "./tests/fixtures/test.jpg" (bobFiles </> "test.jpg")
|
|
|
|
bob #> "/f @alice test.jpg"
|
|
|
|
bob <## "use /fc 3 to cancel sending"
|
|
|
|
desktop <# "bob> sends file test.jpg (136.5 KiB / 139737 bytes)"
|
|
|
|
desktop <## "use /fr 3 [<dir>/ | <path>] to receive it"
|
|
|
|
desktop ##> "/fr 3 encrypt=on"
|
|
|
|
concurrentlyN_
|
|
|
|
[ do
|
|
|
|
bob <## "completed uploading file 3 (test.jpg) for alice",
|
|
|
|
do
|
|
|
|
desktop <## "saving file 3 from bob to test.jpg"
|
|
|
|
desktop <## "started receiving file 3 (test.jpg) from bob"
|
|
|
|
desktop <## "completed receiving file 3 (test.jpg) from bob"
|
|
|
|
]
|
|
|
|
Just cfArgs'@(CFArgs key' nonce') <- J.decode . LB.pack <$> getTermLine desktop
|
|
|
|
desktop <## "File received to connected remote host 1"
|
|
|
|
desktop <## "To download to this device use:"
|
|
|
|
getCmd <- getTermLine desktop
|
|
|
|
getCmd `shouldBe` ("/get remote file 1 {\"userId\":1,\"fileId\":3,\"sent\":false,\"fileSource\":{\"filePath\":\"test.jpg\",\"cryptoArgs\":" <> LB.unpack (J.encode cfArgs') <> "}}")
|
|
|
|
src' <- B.readFile (bobFiles </> "test.jpg")
|
|
|
|
chatReadFile (mobileFiles </> "test.jpg") (strEncode key') (strEncode nonce') `shouldReturn` Right (LB.fromStrict src')
|
|
|
|
doesFileExist (desktopHostStore </> "test.jpg") `shouldReturn` False
|
|
|
|
-- returns error with incorrect key
|
|
|
|
desktop ##> "/get remote file 1 {\"userId\": 1, \"fileId\": 3, \"sent\": false, \"fileSource\": {\"filePath\": \"test.jpg\", \"cryptoArgs\": null}}"
|
|
|
|
hostError desktop "SEFileNotFound"
|
|
|
|
doesFileExist (desktopHostStore </> "test.jpg") `shouldReturn` False
|
|
|
|
desktop ##> getCmd
|
|
|
|
desktop <## "ok"
|
|
|
|
chatReadFile (desktopHostStore </> "test.jpg") (strEncode key') (strEncode nonce') `shouldReturn` Right (LB.fromStrict src')
|
|
|
|
|
|
|
|
stopMobile mobile desktop
|
|
|
|
where
|
|
|
|
cfg = testCfg {xftpFileConfig = Just $ XFTPFileConfig {minFileSize = 0}, tempDir = Just "./tests/tmp/tmp"}
|
|
|
|
hostError cc err = do
|
|
|
|
r <- getTermLine cc
|
|
|
|
r `shouldStartWith` "remote host 1 error"
|
|
|
|
r `shouldContain` err
|
|
|
|
|
|
|
|
remoteCLIFileTest :: (HasCallStack) => FilePath -> IO ()
|
|
|
|
remoteCLIFileTest = testChatCfg3 cfg aliceProfile aliceDesktopProfile bobProfile $ \mobile desktop bob -> withXFTPServer $ do
|
|
|
|
createDirectoryIfMissing True "./tests/tmp/tmp/"
|
2023-10-11 11:45:05 +03:00
|
|
|
let mobileFiles = "./tests/tmp/mobile_files"
|
|
|
|
mobile ##> ("/_files_folder " <> mobileFiles)
|
|
|
|
mobile <## "ok"
|
2023-10-29 19:06:32 +00:00
|
|
|
let bobFiles = "./tests/tmp/bob_files/"
|
|
|
|
createDirectoryIfMissing True bobFiles
|
|
|
|
let desktopHostFiles = "./tests/tmp/remote_hosts_data"
|
|
|
|
desktop ##> ("/remote_hosts_folder " <> desktopHostFiles)
|
2023-10-11 11:45:05 +03:00
|
|
|
desktop <## "ok"
|
|
|
|
|
2023-10-22 11:42:19 +03:00
|
|
|
startRemote mobile desktop
|
|
|
|
contactBob desktop bob
|
|
|
|
|
|
|
|
rhs <- readTVarIO (Controller.remoteHostSessions $ chatController desktop)
|
2023-10-29 19:06:32 +00:00
|
|
|
desktopHostStore <- case M.lookup 1 rhs of
|
|
|
|
Just RemoteHostSession {storePath} -> pure $ desktopHostFiles </> storePath </> archiveFilesFolder
|
2023-10-22 11:42:19 +03:00
|
|
|
_ -> fail "Host session 1 should be started"
|
|
|
|
|
|
|
|
mobileName <- userName mobile
|
|
|
|
|
2023-10-29 19:06:32 +00:00
|
|
|
bob #> ("/f @" <> mobileName <> " " <> "tests/fixtures/test.pdf")
|
2023-10-22 11:42:19 +03:00
|
|
|
bob <## "use /fc 1 to cancel sending"
|
|
|
|
|
|
|
|
desktop <# "bob> sends file test.pdf (266.0 KiB / 272376 bytes)"
|
|
|
|
desktop <## "use /fr 1 [<dir>/ | <path>] to receive it"
|
|
|
|
desktop ##> "/fr 1"
|
|
|
|
concurrentlyN_
|
|
|
|
[ do
|
2023-10-29 19:06:32 +00:00
|
|
|
bob <## "completed uploading file 1 (test.pdf) for alice",
|
2023-10-22 11:42:19 +03:00
|
|
|
do
|
|
|
|
desktop <## "saving file 1 from bob to test.pdf"
|
|
|
|
desktop <## "started receiving file 1 (test.pdf) from bob"
|
2023-10-29 19:06:32 +00:00
|
|
|
desktop <## "completed receiving file 1 (test.pdf) from bob"
|
2023-10-22 11:42:19 +03:00
|
|
|
]
|
2023-10-29 19:06:32 +00:00
|
|
|
|
|
|
|
desktop <## "File received to connected remote host 1"
|
|
|
|
desktop <## "To download to this device use:"
|
|
|
|
getCmd <- getTermLine desktop
|
|
|
|
src <- B.readFile "tests/fixtures/test.pdf"
|
|
|
|
B.readFile (mobileFiles </> "test.pdf") `shouldReturn` src
|
|
|
|
doesFileExist (desktopHostStore </> "test.pdf") `shouldReturn` False
|
|
|
|
desktop ##> getCmd
|
|
|
|
desktop <## "ok"
|
|
|
|
B.readFile (desktopHostStore </> "test.pdf") `shouldReturn` src
|
|
|
|
|
|
|
|
desktop `send` "/f @bob tests/fixtures/test.jpg"
|
|
|
|
desktop <# "/f @bob test.jpg"
|
2023-10-22 11:42:19 +03:00
|
|
|
desktop <## "use /fc 2 to cancel sending"
|
|
|
|
|
2023-10-29 19:06:32 +00:00
|
|
|
bob <# "alice> sends file test.jpg (136.5 KiB / 139737 bytes)"
|
2023-10-22 11:42:19 +03:00
|
|
|
bob <## "use /fr 2 [<dir>/ | <path>] to receive it"
|
2023-10-29 19:06:32 +00:00
|
|
|
bob ##> ("/fr 2 " <> bobFiles)
|
2023-10-22 11:42:19 +03:00
|
|
|
concurrentlyN_
|
|
|
|
[ do
|
2023-10-29 19:06:32 +00:00
|
|
|
desktop <## "completed uploading file 2 (test.jpg) for bob",
|
2023-10-22 11:42:19 +03:00
|
|
|
do
|
2023-10-29 19:06:32 +00:00
|
|
|
bob <## "saving file 2 from alice to ./tests/tmp/bob_files/test.jpg"
|
|
|
|
bob <## "started receiving file 2 (test.jpg) from alice"
|
|
|
|
bob <## "completed receiving file 2 (test.jpg) from alice"
|
2023-10-22 11:42:19 +03:00
|
|
|
]
|
|
|
|
|
2023-10-29 19:06:32 +00:00
|
|
|
src' <- B.readFile "tests/fixtures/test.jpg"
|
|
|
|
B.readFile (mobileFiles </> "test.jpg") `shouldReturn` src'
|
|
|
|
B.readFile (desktopHostStore </> "test.jpg") `shouldReturn` src'
|
|
|
|
B.readFile (bobFiles </> "test.jpg") `shouldReturn` src'
|
2023-10-22 11:42:19 +03:00
|
|
|
|
|
|
|
stopMobile mobile desktop
|
2023-10-29 19:06:32 +00:00
|
|
|
where
|
|
|
|
cfg = testCfg {xftpFileConfig = Just $ XFTPFileConfig {minFileSize = 0}, tempDir = Just "./tests/tmp/tmp"}
|
2023-10-22 11:42:19 +03:00
|
|
|
|
|
|
|
-- * Utils
|
|
|
|
|
|
|
|
startRemote :: TestCC -> TestCC -> IO ()
|
|
|
|
startRemote mobile desktop = do
|
2023-10-30 16:00:54 +02:00
|
|
|
desktop ##> "/set device name My desktop"
|
|
|
|
desktop <## "ok"
|
2023-10-07 16:23:24 +03:00
|
|
|
desktop ##> "/create remote host"
|
|
|
|
desktop <## "remote host 1 created"
|
2023-10-30 16:00:54 +02:00
|
|
|
-- A new host is started [automatically] by UI
|
2023-10-07 16:23:24 +03:00
|
|
|
desktop ##> "/start remote host 1"
|
2023-10-13 22:35:30 +01:00
|
|
|
desktop <## "ok"
|
2023-10-30 16:00:54 +02:00
|
|
|
desktop <## "remote host 1 started"
|
|
|
|
desktop <## "connection code:"
|
|
|
|
oobLink <- getTermLine desktop
|
|
|
|
OOB {caFingerprint = oobFingerprint} <- either (fail . mappend "OOB link failed: ") pure $ decodeOOBLink (fromString oobLink)
|
|
|
|
-- Desktop displays OOB QR code
|
2023-10-07 16:23:24 +03:00
|
|
|
|
2023-10-30 16:00:54 +02:00
|
|
|
mobile ##> "/set device name Mobile"
|
|
|
|
mobile <## "ok"
|
2023-10-07 16:23:24 +03:00
|
|
|
mobile ##> "/start remote ctrl"
|
2023-10-13 22:35:30 +01:00
|
|
|
mobile <## "ok"
|
2023-10-07 16:23:24 +03:00
|
|
|
mobile <## "remote controller announced"
|
|
|
|
mobile <## "connection code:"
|
2023-10-30 16:00:54 +02:00
|
|
|
annFingerprint <- getTermLine mobile
|
|
|
|
-- The user scans OOB QR code and confirms it matches the announced stuff
|
|
|
|
fromString annFingerprint `shouldBe` strEncode oobFingerprint
|
|
|
|
|
|
|
|
mobile ##> ("/register remote ctrl " <> oobLink)
|
2023-10-07 16:23:24 +03:00
|
|
|
mobile <## "remote controller 1 registered"
|
|
|
|
mobile ##> "/accept remote ctrl 1"
|
2023-10-13 22:35:30 +01:00
|
|
|
mobile <## "ok" -- alternative scenario: accepted before controller start
|
2023-10-14 13:10:06 +01:00
|
|
|
mobile <## "remote controller 1 connecting to My desktop"
|
|
|
|
mobile <## "remote controller 1 connected, My desktop"
|
2023-10-07 16:23:24 +03:00
|
|
|
desktop <## "remote host 1 connected"
|
|
|
|
|
2023-10-22 11:42:19 +03:00
|
|
|
contactBob :: TestCC -> TestCC -> IO ()
|
|
|
|
contactBob desktop bob = do
|
|
|
|
logNote "exchanging contacts"
|
2023-10-07 16:23:24 +03:00
|
|
|
bob ##> "/c"
|
|
|
|
inv' <- getInvitation bob
|
|
|
|
desktop ##> ("/c " <> inv')
|
|
|
|
desktop <## "confirmation sent!"
|
|
|
|
concurrently_
|
|
|
|
(desktop <## "bob (Bob): contact is connected")
|
|
|
|
(bob <## "alice (Alice): contact is connected")
|
|
|
|
|
2023-10-22 11:42:19 +03:00
|
|
|
genTestCredentials :: IO (C.KeyHash, TLS.Credentials)
|
|
|
|
genTestCredentials = do
|
|
|
|
caCreds <- liftIO $ genCredentials Nothing (0, 24) "CA"
|
|
|
|
sessionCreds <- liftIO $ genCredentials (Just caCreds) (0, 24) "Session"
|
|
|
|
pure . tlsCredentials $ sessionCreds :| [caCreds]
|
2023-10-11 11:45:05 +03:00
|
|
|
|
2023-10-22 11:42:19 +03:00
|
|
|
stopDesktop :: HasCallStack => TestCC -> TestCC -> IO ()
|
|
|
|
stopDesktop mobile desktop = do
|
|
|
|
logWarn "stopping via desktop"
|
|
|
|
desktop ##> "/stop remote host 1"
|
|
|
|
-- desktop <## "ok"
|
|
|
|
concurrently_
|
|
|
|
(desktop <## "remote host 1 stopped")
|
|
|
|
(eventually 3 $ mobile <## "remote controller stopped")
|
2023-10-11 11:45:05 +03:00
|
|
|
|
2023-10-22 11:42:19 +03:00
|
|
|
stopMobile :: HasCallStack => TestCC -> TestCC -> IO ()
|
|
|
|
stopMobile mobile desktop = do
|
|
|
|
logWarn "stopping via mobile"
|
2023-10-07 16:23:24 +03:00
|
|
|
mobile ##> "/stop remote ctrl"
|
|
|
|
mobile <## "ok"
|
|
|
|
concurrently_
|
|
|
|
(mobile <## "remote controller stopped")
|
2023-10-22 11:42:19 +03:00
|
|
|
(eventually 3 $ desktop <## "remote host 1 stopped")
|
|
|
|
|
|
|
|
-- | Run action with extended timeout
|
|
|
|
eventually :: Int -> IO a -> IO a
|
|
|
|
eventually retries action = tryAny action >>= \case -- TODO: only catch timeouts
|
|
|
|
Left err | retries == 0 -> throwIO err
|
|
|
|
Left _ -> eventually (retries - 1) action
|
|
|
|
Right r -> pure r
|