Skip to content

Commit d39100f

Browse files
committed
Merge branch 'master' into ab/tls-2
2 parents ca6790a + 017469b commit d39100f

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

43 files changed

+2519
-1239
lines changed

CHANGELOG.md

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,13 @@
1+
# 5.8.2
2+
3+
Agent:
4+
- fast handshake support (disabled).
5+
- new statistics api.
6+
7+
SMP server:
8+
- fast handshake support (SKEY command).
9+
- minor changes to reduce memory usage.
10+
111
# 5.8.1
212

313
Agent:

package.yaml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
name: simplexmq
2-
version: 5.8.1.0
2+
version: 6.0.0.0
33
synopsis: SimpleXMQ message broker
44
description: |
55
This package includes <./docs/Simplex-Messaging-Server.html server>,

rfcs/2024-06-14-fast-connection.md

Lines changed: 42 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,42 @@
1+
# Faster connection establishment
2+
3+
## Problem
4+
5+
SMP protocol is unidirectional, and to create a connection users have to agree two messaging queues.
6+
7+
V1 of handshake protocol required 5 messages and multiple HELLO sent between the users, which consumed a lot of traffic.
8+
9+
V2 of handshake protocol was optimized to remove multiple HELLO and also REPLY message, thanks to including queue address together with the key to secure this queue into the confirmation message.
10+
11+
This eliminated unnecessary traffic from repeated HELLOs, but still requires 4 messages in total and 2 times of each client being online. It is perceived by the users as "it didn't work" (because they see "connecting" after using the link) or "we have to be online at the same time" (and even in this case it is slow on bad network). This hurts usability and creates churn of the new users, as unless people are onboarded by the friends who know how the app works, they cannot figure out how to connect.
12+
13+
Ideally, we want to have handshake protocol design when an accepting user can send messages straight after using the link (their client says "connected") and the initiating client can send messages as soon as it received confirmation message with the profile.
14+
15+
This RFC proposes modifications to SMP and SMP Agent protocols to reduce the number of required messages to 2 and allows accepting client to send messages straight after using the link (and sending the confirmation), before receiving the profile of the initiating client in the second message, and the initiating client can send the messages straight after processing the confirmation and sending its own confirmation.
16+
17+
## Solution
18+
19+
The current protocol design allows additional confirmation step where the initiating client can confirm the connection having received the profile of the sender. We don't use it in the UI - this confirmation is done automatically and unconditionally.
20+
21+
Instead of requiring the initiating client to secure its queue with sender's key, we can allow the accepting client to secure it with the additional SKEY command. This would avoid "connecting" state but would introduce "Profile unknown" state where the accepting client does not yet have the profile of the initiating client. In this case we could also use the non-optional alias created during the connection (or have something like "Add alias to be able to send messages immediately" and show warning if the user proceeds without it).
22+
23+
The additional advantage here is that if the queue of the initiating client was removed, the connection will not procede to create additional queue, failing faster.
24+
25+
These are the proposed changes:
26+
27+
1. Modify NEW command to add flag allowing sender to secure the queue (it should not be allowed if queue is created for the contact address).
28+
2. Include flag into the invitation link URI and in reply address encoding that queue(s) can be secured by the sender (to avoid coupling with the protocol version and preserve the possibility of the longer handshakes).
29+
3. Add SKEY command to SMP protocol to allow the sender securing the message queue.
30+
4. This command has to be supported by SMP proxy as well, so that the sender does not connect to the recipient's server directly.
31+
5. Accepting client will secure the messaging queue before sending the confirmation to it.
32+
6. Initiating client will secure the messaging queue before sending the confirmation.
33+
34+
See [this sequence diagram](../protocol/diagrams/duplex-messaging/duplex-creating-v6.mmd) for the updated handshake protocol.
35+
36+
Changes to threat model: the attacker who compromised TLS and knows the queue address can block the connection, as the protocol no longer requires the recipient to decrypt the confirmation to secure the queue.
37+
38+
Possibly, "fast connection" should be an option in Privacy & security settings.
39+
40+
## Implementation questions
41+
42+
Currently we store received confirmations in the database, so that the client can confirm them. This becomes unnecessary.

simplexmq.cabal

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ cabal-version: 1.12
55
-- see: https://github.com/sol/hpack
66

77
name: simplexmq
8-
version: 5.8.1.0
8+
version: 6.0.0.0
99
synopsis: SimpleXMQ message broker
1010
description: This package includes <./docs/Simplex-Messaging-Server.html server>,
1111
<./docs/Simplex-Messaging-Client.html client> and
@@ -95,6 +95,7 @@ library
9595
Simplex.Messaging.Agent.Protocol
9696
Simplex.Messaging.Agent.QueryString
9797
Simplex.Messaging.Agent.RetryInterval
98+
Simplex.Messaging.Agent.Stats
9899
Simplex.Messaging.Agent.Store
99100
Simplex.Messaging.Agent.Store.SQLite
100101
Simplex.Messaging.Agent.Store.SQLite.Common
@@ -132,6 +133,8 @@ library
132133
Simplex.Messaging.Agent.Store.SQLite.Migrations.M20240223_connections_wait_delivery
133134
Simplex.Messaging.Agent.Store.SQLite.Migrations.M20240225_ratchet_kem
134135
Simplex.Messaging.Agent.Store.SQLite.Migrations.M20240417_rcv_files_approved_relays
136+
Simplex.Messaging.Agent.Store.SQLite.Migrations.M20240624_snd_secure
137+
Simplex.Messaging.Agent.Store.SQLite.Migrations.M20240702_servers_stats
135138
Simplex.Messaging.Agent.TRcvQueues
136139
Simplex.Messaging.Client
137140
Simplex.Messaging.Client.Agent

src/Simplex/FileTransfer/Agent.hs

Lines changed: 24 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -49,6 +49,7 @@ import qualified Data.Set as S
4949
import Data.Text (Text)
5050
import Data.Time.Clock (getCurrentTime)
5151
import Data.Time.Format (defaultTimeLocale, formatTime)
52+
import Simplex.FileTransfer.Chunks (toKB)
5253
import Simplex.FileTransfer.Client (XFTPChunkSpec (..))
5354
import Simplex.FileTransfer.Client.Main
5455
import Simplex.FileTransfer.Crypto
@@ -63,6 +64,7 @@ import Simplex.Messaging.Agent.Client
6364
import Simplex.Messaging.Agent.Env.SQLite
6465
import Simplex.Messaging.Agent.Protocol
6566
import Simplex.Messaging.Agent.RetryInterval
67+
import Simplex.Messaging.Agent.Stats
6668
import Simplex.Messaging.Agent.Store.SQLite
6769
import qualified Simplex.Messaging.Agent.Store.SQLite.DB as DB
6870
import qualified Simplex.Messaging.Crypto as C
@@ -184,6 +186,7 @@ runXFTPRcvWorker c srv Worker {doWork} = do
184186
let ri' = maybe ri (\d -> ri {initialInterval = d, increaseAfter = 0}) delay
185187
withRetryIntervalLimit xftpConsecutiveRetries ri' $ \delay' loop -> do
186188
liftIO $ waitForUserNetwork c
189+
atomically $ incXFTPServerStat c userId srv downloadAttempts
187190
downloadFileChunk fc replica approvedRelays
188191
`catchAgentError` \e -> retryOnError "XFTP rcv worker" (retryLoop loop e delay') (retryDone e) e
189192
where
@@ -194,13 +197,18 @@ runXFTPRcvWorker c srv Worker {doWork} = do
194197
withStore' c $ \db -> updateRcvChunkReplicaDelay db rcvChunkReplicaId replicaDelay
195198
atomically $ assertAgentForeground c
196199
loop
197-
retryDone = rcvWorkerInternalError c rcvFileId rcvFileEntityId (Just fileTmpPath)
200+
retryDone e = do
201+
atomically . incXFTPServerStat c userId srv $ case e of
202+
XFTP _ XFTP.AUTH -> downloadAuthErrs
203+
_ -> downloadErrs
204+
rcvWorkerInternalError c rcvFileId rcvFileEntityId (Just fileTmpPath) e
198205
downloadFileChunk :: RcvFileChunk -> RcvFileChunkReplica -> Bool -> AM ()
199206
downloadFileChunk RcvFileChunk {userId, rcvFileId, rcvFileEntityId, rcvChunkId, chunkNo, chunkSize, digest, fileTmpPath} replica approvedRelays = do
200207
unlessM ((approvedRelays ||) <$> ipAddressProtected') $ throwE $ FILE NOT_APPROVED
201208
fsFileTmpPath <- lift $ toFSFilePath fileTmpPath
202209
chunkPath <- uniqueCombine fsFileTmpPath $ show chunkNo
203-
let chunkSpec = XFTPRcvChunkSpec chunkPath (unFileSize chunkSize) (unFileDigest digest)
210+
let chSize = unFileSize chunkSize
211+
chunkSpec = XFTPRcvChunkSpec chunkPath chSize (unFileDigest digest)
204212
relChunkPath = fileTmpPath </> takeFileName chunkPath
205213
agentXFTPDownloadChunk c userId digest replica chunkSpec
206214
atomically $ waitUntilForeground c
@@ -214,6 +222,8 @@ runXFTPRcvWorker c srv Worker {doWork} = do
214222
Just RcvFileRedirect {redirectFileInfo = RedirectFileInfo {size = FileSize finalSize}, redirectEntityId} -> (redirectEntityId, finalSize)
215223
liftIO . when complete $ updateRcvFileStatus db rcvFileId RFSReceived
216224
pure (entityId, complete, RFPROG rcvd total)
225+
atomically $ incXFTPServerStat c userId srv downloads
226+
atomically $ incXFTPServerSizeStat c userId srv downloadsSize (fromIntegral $ toKB chSize)
217227
notify c entityId progress
218228
when complete . lift . void $
219229
getXFTPRcvWorker True c Nothing
@@ -484,6 +494,7 @@ runXFTPSndWorker c srv Worker {doWork} = do
484494
let ri' = maybe ri (\d -> ri {initialInterval = d, increaseAfter = 0}) delay
485495
withRetryIntervalLimit xftpConsecutiveRetries ri' $ \delay' loop -> do
486496
liftIO $ waitForUserNetwork c
497+
atomically $ incXFTPServerStat c userId srv uploadAttempts
487498
uploadFileChunk cfg fc replica
488499
`catchAgentError` \e -> retryOnError "XFTP snd worker" (retryLoop loop e delay') (retryDone e) e
489500
where
@@ -494,9 +505,11 @@ runXFTPSndWorker c srv Worker {doWork} = do
494505
withStore' c $ \db -> updateSndChunkReplicaDelay db sndChunkReplicaId replicaDelay
495506
atomically $ assertAgentForeground c
496507
loop
497-
retryDone = sndWorkerInternalError c sndFileId sndFileEntityId (Just filePrefixPath)
508+
retryDone e = do
509+
atomically $ incXFTPServerStat c userId srv uploadErrs
510+
sndWorkerInternalError c sndFileId sndFileEntityId (Just filePrefixPath) e
498511
uploadFileChunk :: AgentConfig -> SndFileChunk -> SndFileChunkReplica -> AM ()
499-
uploadFileChunk AgentConfig {xftpMaxRecipientsPerRequest = maxRecipients} sndFileChunk@SndFileChunk {sndFileId, userId, chunkSpec = chunkSpec@XFTPChunkSpec {filePath}, digest = chunkDigest} replica = do
512+
uploadFileChunk AgentConfig {xftpMaxRecipientsPerRequest = maxRecipients} sndFileChunk@SndFileChunk {sndFileId, userId, chunkSpec = chunkSpec@XFTPChunkSpec {filePath, chunkSize = chSize}, digest = chunkDigest} replica = do
500513
replica'@SndFileChunkReplica {sndChunkReplicaId} <- addRecipients sndFileChunk replica
501514
fsFilePath <- lift $ toFSFilePath filePath
502515
unlessM (doesFileExist fsFilePath) $ throwE $ FILE NO_FILE
@@ -510,6 +523,8 @@ runXFTPSndWorker c srv Worker {doWork} = do
510523
let uploaded = uploadedSize chunks
511524
total = totalSize chunks
512525
complete = all chunkUploaded chunks
526+
atomically $ incXFTPServerStat c userId srv uploads
527+
atomically $ incXFTPServerSizeStat c userId srv uploadsSize (fromIntegral $ toKB chSize)
513528
notify c sndFileEntityId $ SFPROG uploaded total
514529
when complete $ do
515530
(sndDescr, rcvDescrs) <- sndFileToDescrs sf
@@ -651,6 +666,7 @@ runXFTPDelWorker c srv Worker {doWork} = do
651666
let ri' = maybe ri (\d -> ri {initialInterval = d, increaseAfter = 0}) delay
652667
withRetryIntervalLimit xftpConsecutiveRetries ri' $ \delay' loop -> do
653668
liftIO $ waitForUserNetwork c
669+
atomically $ incXFTPServerStat c userId srv deleteAttempts
654670
deleteChunkReplica
655671
`catchAgentError` \e -> retryOnError "XFTP del worker" (retryLoop loop e delay') (retryDone e) e
656672
where
@@ -661,10 +677,13 @@ runXFTPDelWorker c srv Worker {doWork} = do
661677
withStore' c $ \db -> updateDeletedSndChunkReplicaDelay db deletedSndChunkReplicaId replicaDelay
662678
atomically $ assertAgentForeground c
663679
loop
664-
retryDone = delWorkerInternalError c deletedSndChunkReplicaId
680+
retryDone e = do
681+
atomically $ incXFTPServerStat c userId srv deleteErrs
682+
delWorkerInternalError c deletedSndChunkReplicaId e
665683
deleteChunkReplica = do
666684
agentXFTPDeleteChunk c userId replica
667685
withStore' c $ \db -> deleteDeletedSndChunkReplica db deletedSndChunkReplicaId
686+
atomically $ incXFTPServerStat c userId srv deletions
668687

669688
delWorkerInternalError :: AgentClient -> Int64 -> AgentErrorType -> AM ()
670689
delWorkerInternalError c deletedSndChunkReplicaId e = do

src/Simplex/FileTransfer/Chunks.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,10 @@ kb :: Integral a => a -> a
2626
kb n = 1024 * n
2727
{-# INLINE kb #-}
2828

29+
toKB :: Integral a => a -> a
30+
toKB n = n `div` 1024
31+
{-# INLINE toKB #-}
32+
2933
mb :: Integral a => a -> a
3034
mb n = 1024 * kb n
3135
{-# INLINE mb #-}

src/Simplex/FileTransfer/Client.hs

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,6 @@ import Data.ByteString.Char8 (ByteString)
2222
import qualified Data.ByteString.Char8 as B
2323
import Data.Int (Int64)
2424
import Data.List.NonEmpty (NonEmpty (..))
25-
import Data.Time (UTCTime)
2625
import Data.Word (Word32)
2726
import qualified Data.X509 as X
2827
import qualified Data.X509.Validation as XV
@@ -168,9 +167,6 @@ xftpClientServer = B.unpack . strEncode . snd3 . transportSession
168167
xftpTransportHost :: XFTPClient -> TransportHost
169168
xftpTransportHost XFTPClient {http2Client = HTTP2Client {client_ = HClient {host}}} = host
170169

171-
xftpSessionTs :: XFTPClient -> UTCTime
172-
xftpSessionTs = sessionTs . http2Client
173-
174170
xftpHTTP2Config :: TransportClientConfig -> XFTPClientConfig -> HTTP2ClientConfig
175171
xftpHTTP2Config transportConfig XFTPClientConfig {xftpNetworkConfig = NetworkConfig {tcpConnectTimeout}} =
176172
defaultHTTP2ClientConfig

0 commit comments

Comments
 (0)