Skip to content

Commit ce6777b

Browse files
authored
newtype for server entity IDs, fix TRcvQueues (#1290)
* put DRG state to IORef, split STM transaction of sending notification (#1288) * put DRG state to IORef, split STM transaction of sending notification * remove comment * remove comment * add comment * revert version * newtype for server entity IDs, fix TRcvQueues * Revert "put DRG state to IORef, split STM transaction of sending notification (#1288)" This reverts commit 517933d. * logServer
1 parent 655e7ad commit ce6777b

34 files changed

+280
-227
lines changed

src/Simplex/FileTransfer/Agent.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -74,7 +74,7 @@ import qualified Simplex.Messaging.Crypto.File as CF
7474
import qualified Simplex.Messaging.Crypto.Lazy as LC
7575
import Simplex.Messaging.Encoding
7676
import Simplex.Messaging.Encoding.String (strDecode, strEncode)
77-
import Simplex.Messaging.Protocol (EntityId, ProtocolServer, ProtocolType (..), XFTPServer)
77+
import Simplex.Messaging.Protocol (ProtocolServer, ProtocolType (..), XFTPServer)
7878
import qualified Simplex.Messaging.TMap as TM
7979
import Simplex.Messaging.Util (catchAll_, liftError, tshow, unlessM, whenM)
8080
import System.FilePath (takeFileName, (</>))
@@ -346,7 +346,7 @@ xftpDeleteRcvFiles' c rcvFileEntityIds = do
346346
batchFiles :: (DB.Connection -> DBRcvFileId -> IO a) -> [RcvFile] -> AM' [Either AgentErrorType a]
347347
batchFiles f rcvFiles = withStoreBatch' c $ \db -> map (\RcvFile {rcvFileId} -> f db rcvFileId) rcvFiles
348348

349-
notify :: forall m e. (MonadIO m, AEntityI e) => AgentClient -> EntityId -> AEvent e -> m ()
349+
notify :: forall m e. (MonadIO m, AEntityI e) => AgentClient -> AEntityId -> AEvent e -> m ()
350350
notify c entId cmd = atomically $ writeTBQueue (subQ c) ("", entId, AEvt (sAEntity @e) cmd)
351351

352352
xftpSendFile' :: AgentClient -> UserId -> CryptoFile -> Int -> AM SndFileId

src/Simplex/FileTransfer/Client.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -50,6 +50,7 @@ import Simplex.Messaging.Protocol
5050
ProtocolServer (..),
5151
RecipientId,
5252
SenderId,
53+
pattern NoEntity,
5354
)
5455
import Simplex.Messaging.Transport (ALPN, HandshakeError (..), THandleAuth (..), THandleParams (..), TransportError (..), TransportPeer (..), supportedParameters)
5556
import Simplex.Messaging.Transport.Client (TransportClientConfig, TransportHost, alpn)
@@ -222,7 +223,7 @@ createXFTPChunk ::
222223
Maybe BasicAuth ->
223224
ExceptT XFTPClientError IO (SenderId, NonEmpty RecipientId)
224225
createXFTPChunk c spKey file rcps auth_ =
225-
sendXFTPCommand c spKey "" (FNEW file rcps auth_) Nothing >>= \case
226+
sendXFTPCommand c spKey NoEntity (FNEW file rcps auth_) Nothing >>= \case
226227
(FRSndIds sId rIds, body) -> noFile body (sId, rIds)
227228
(r, _) -> throwE $ unexpectedResponse r
228229

@@ -278,7 +279,7 @@ pingXFTP :: XFTPClient -> ExceptT XFTPClientError IO ()
278279
pingXFTP c@XFTPClient {thParams} = do
279280
t <-
280281
liftEither . first PCETransportError $
281-
xftpEncodeTransmission thParams ("", "", FileCmd SFRecipient PING)
282+
xftpEncodeTransmission thParams ("", NoEntity, FileCmd SFRecipient PING)
282283
(r, _) <- sendXFTPTransmission c t Nothing
283284
case r of
284285
FRPong -> pure ()

src/Simplex/FileTransfer/Description.hs

Lines changed: 4 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,9 @@
11
{-# LANGUAGE DataKinds #-}
22
{-# LANGUAGE DeriveAnyClass #-}
3+
{-# LANGUAGE DerivingStrategies #-}
34
{-# LANGUAGE DuplicateRecordFields #-}
45
{-# LANGUAGE GADTs #-}
6+
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
57
{-# LANGUAGE KindSignatures #-}
68
{-# LANGUAGE NamedFieldPuns #-}
79
{-# LANGUAGE OverloadedStrings #-}
@@ -139,12 +141,9 @@ data FileChunkReplica = FileChunkReplica
139141
}
140142
deriving (Eq, Show)
141143

142-
newtype ChunkReplicaId = ChunkReplicaId {unChunkReplicaId :: ByteString}
144+
newtype ChunkReplicaId = ChunkReplicaId {unChunkReplicaId :: XFTPFileId}
143145
deriving (Eq, Show)
144-
145-
instance StrEncoding ChunkReplicaId where
146-
strEncode (ChunkReplicaId fid) = strEncode fid
147-
strP = ChunkReplicaId <$> strP
146+
deriving newtype (StrEncoding)
148147

149148
instance FromJSON ChunkReplicaId where
150149
parseJSON = strParseJSON "ChunkReplicaId"
@@ -153,10 +152,6 @@ instance ToJSON ChunkReplicaId where
153152
toJSON = strToJSON
154153
toEncoding = strToJEncoding
155154

156-
instance FromField ChunkReplicaId where fromField f = ChunkReplicaId <$> fromField f
157-
158-
instance ToField ChunkReplicaId where toField (ChunkReplicaId s) = toField s
159-
160155
data YAMLFileDescription = YAMLFileDescription
161156
{ party :: FileParty,
162157
size :: String,

src/Simplex/FileTransfer/Protocol.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,7 @@ import Simplex.Messaging.Protocol
4141
ProtocolType (..),
4242
RcvPublicAuthKey,
4343
RcvPublicDhKey,
44+
EntityId (..),
4445
RecipientId,
4546
SenderId,
4647
SentRawTransmission,
@@ -170,7 +171,7 @@ data FileInfo = FileInfo
170171
}
171172
deriving (Show)
172173

173-
type XFTPFileId = ByteString
174+
type XFTPFileId = EntityId
174175

175176
instance FilePartyI p => ProtocolEncoding XFTPVersion XFTPErrorType (FileCommand p) where
176177
type Tag (FileCommand p) = FileCommandTag p
@@ -191,7 +192,7 @@ instance FilePartyI p => ProtocolEncoding XFTPVersion XFTPErrorType (FileCommand
191192
fromProtocolError = fromProtocolError @XFTPVersion @XFTPErrorType @FileResponse
192193
{-# INLINE fromProtocolError #-}
193194

194-
checkCredentials (auth, _, fileId, _) cmd = case cmd of
195+
checkCredentials (auth, _, EntityId fileId, _) cmd = case cmd of
195196
-- FNEW must not have signature and chunk ID
196197
FNEW {}
197198
| isNothing auth -> Left $ CMD NO_AUTH
@@ -301,7 +302,7 @@ instance ProtocolEncoding XFTPVersion XFTPErrorType FileResponse where
301302
PEBlock -> BLOCK
302303
{-# INLINE fromProtocolError #-}
303304

304-
checkCredentials (_, _, entId, _) cmd = case cmd of
305+
checkCredentials (_, _, EntityId entId, _) cmd = case cmd of
305306
FRSndIds {} -> noEntity
306307
-- ERR response does not always have entity ID
307308
FRErr _ -> Right cmd

src/Simplex/FileTransfer/Server.hs

Lines changed: 6 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@
99
{-# LANGUAGE NumericUnderscores #-}
1010
{-# LANGUAGE OverloadedLists #-}
1111
{-# LANGUAGE OverloadedStrings #-}
12+
{-# LANGUAGE PatternSynonyms #-}
1213
{-# LANGUAGE ScopedTypeVariables #-}
1314
{-# LANGUAGE TupleSections #-}
1415

@@ -53,7 +54,7 @@ import qualified Simplex.Messaging.Crypto as C
5354
import qualified Simplex.Messaging.Crypto.Lazy as LC
5455
import Simplex.Messaging.Encoding
5556
import Simplex.Messaging.Encoding.String
56-
import Simplex.Messaging.Protocol (CorrId (..), RcvPublicAuthKey, RcvPublicDhKey, RecipientId, TransmissionAuth)
57+
import Simplex.Messaging.Protocol (CorrId (..), EntityId (..), RcvPublicAuthKey, RcvPublicDhKey, RecipientId, TransmissionAuth, pattern NoEntity)
5758
import Simplex.Messaging.Server (dummyVerifyCmd, verifyCmdAuthorization)
5859
import Simplex.Messaging.Server.Expiration
5960
import Simplex.Messaging.Server.Stats
@@ -310,7 +311,7 @@ data ServerFile = ServerFile
310311

311312
processRequest :: XFTPTransportRequest -> M ()
312313
processRequest XFTPTransportRequest {thParams, reqBody = body@HTTP2Body {bodyHead}, sendResponse}
313-
| B.length bodyHead /= xftpBlockSize = sendXFTPResponse ("", "", FRErr BLOCK) Nothing
314+
| B.length bodyHead /= xftpBlockSize = sendXFTPResponse ("", NoEntity, FRErr BLOCK) Nothing
314315
| otherwise = do
315316
case xftpDecodeTransmission thParams bodyHead of
316317
Right (sig_, signed, (corrId, fId, cmdOrErr)) ->
@@ -323,7 +324,7 @@ processRequest XFTPTransportRequest {thParams, reqBody = body@HTTP2Body {bodyHea
323324
Left e -> send (FRErr e) Nothing
324325
where
325326
send resp = sendXFTPResponse (corrId, fId, resp)
326-
Left e -> sendXFTPResponse ("", "", FRErr e) Nothing
327+
Left e -> sendXFTPResponse ("", NoEntity, FRErr e) Nothing
327328
where
328329
sendXFTPResponse (corrId, fId, resp) serverFile_ = do
329330
let t_ = xftpEncodeTransmission thParams (corrId, fId, resp)
@@ -464,7 +465,7 @@ processXFTPRequest HTTP2Body {bodyPart} = \case
464465
\used -> let used' = used + fromIntegral size in if used' <= quota then (True, used') else (False, used)
465466
receive = do
466467
path <- asks $ filesPath . config
467-
let fPath = path </> B.unpack (B64.encode senderId)
468+
let fPath = path </> B.unpack (B64.encode $ unEntityId senderId)
468469
receiveChunk (XFTPRcvChunkSpec fPath size digest) >>= \case
469470
Right () -> do
470471
stats <- asks serverStats
@@ -560,9 +561,7 @@ randomId :: Int -> M ByteString
560561
randomId n = atomically . C.randomBytes n =<< asks random
561562

562563
getFileId :: M XFTPFileId
563-
getFileId = do
564-
size <- asks (fileIdSize . config)
565-
atomically . C.randomBytes size =<< asks random
564+
getFileId = fmap EntityId . randomId =<< asks (fileIdSize . config)
566565

567566
withFileLog :: (StoreLog 'WriteMode -> IO a) -> M ()
568567
withFileLog action = liftIO . mapM_ action =<< asks storeLog

src/Simplex/FileTransfer/Server/Control.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@
44
module Simplex.FileTransfer.Server.Control where
55

66
import qualified Data.Attoparsec.ByteString.Char8 as A
7-
import Data.ByteString (ByteString)
7+
import Simplex.FileTransfer.Protocol (XFTPFileId)
88
import Simplex.Messaging.Encoding.String
99
import Simplex.Messaging.Protocol (BasicAuth)
1010

@@ -13,7 +13,7 @@ data CPClientRole = CPRNone | CPRUser | CPRAdmin
1313
data ControlProtocol
1414
= CPAuth BasicAuth
1515
| CPStatsRTS
16-
| CPDelete ByteString
16+
| CPDelete XFTPFileId
1717
| CPHelp
1818
| CPQuit
1919
| CPSkip

src/Simplex/FileTransfer/Types.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -25,9 +25,9 @@ import Simplex.Messaging.Parsers
2525
import Simplex.Messaging.Protocol (XFTPServer)
2626
import System.FilePath ((</>))
2727

28-
type RcvFileId = ByteString
28+
type RcvFileId = ByteString -- Agent entity ID
2929

30-
type SndFileId = ByteString
30+
type SndFileId = ByteString -- Agent entity ID
3131

3232
authTagSize :: Int64
3333
authTagSize = fromIntegral C.authTagSize

src/Simplex/Messaging/Agent.hs

Lines changed: 14 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -177,7 +177,7 @@ import Simplex.Messaging.Notifications.Protocol (DeviceToken, NtfRegCode (NtfReg
177177
import Simplex.Messaging.Notifications.Server.Push.APNS (PNMessageData (..))
178178
import Simplex.Messaging.Notifications.Types
179179
import Simplex.Messaging.Parsers (parse)
180-
import Simplex.Messaging.Protocol (BrokerMsg, Cmd (..), EntityId, ErrorType (AUTH), MsgBody, MsgFlags (..), NtfServer, ProtoServerWithAuth, ProtocolType (..), ProtocolTypeI (..), SMPMsgMeta, SParty (..), SProtocolType (..), SndPublicAuthKey, SubscriptionMode (..), UserProtocol, VersionSMPC, sndAuthKeySMPClientVersion)
180+
import Simplex.Messaging.Protocol (BrokerMsg, Cmd (..), ErrorType (AUTH), MsgBody, MsgFlags (..), NtfServer, ProtoServerWithAuth, ProtocolType (..), ProtocolTypeI (..), SMPMsgMeta, SParty (..), SProtocolType (..), SndPublicAuthKey, SubscriptionMode (..), UserProtocol, VersionSMPC, sndAuthKeySMPClientVersion)
181181
import qualified Simplex.Messaging.Protocol as SMP
182182
import Simplex.Messaging.ServiceScheme (ServiceScheme (..))
183183
import qualified Simplex.Messaging.TMap as TM
@@ -891,7 +891,7 @@ joinConnSrv c userId connId hasNewConn enableNtfs cReqUri@CRContactUri {} cInfo
891891
lift (compatibleContactUri cReqUri) >>= \case
892892
Just (qInfo, vrsn) -> do
893893
(connId', cReq) <- newConnSrv c userId connId hasNewConn enableNtfs SCMInvitation Nothing (CR.IKNoPQ pqSup) subMode srv
894-
void $ sendInvitation c userId qInfo vrsn cReq cInfo
894+
void $ sendInvitation c userId connId' qInfo vrsn cReq cInfo
895895
pure (connId', False)
896896
Nothing -> throwE $ AGENT A_VERSION
897897

@@ -2208,7 +2208,7 @@ cleanupManager c@AgentClient {subQ} = do
22082208
deleteExpiredReplicasForDeletion = do
22092209
rcvFilesTTL <- asks $ rcvFilesTTL . config
22102210
withStore' c (`deleteDeletedSndChunkReplicasExpired` rcvFilesTTL)
2211-
notify :: forall e. AEntityI e => EntityId -> AEvent e -> AM ()
2211+
notify :: forall e. AEntityI e => AEntityId -> AEvent e -> AM ()
22122212
notify entId cmd = atomically $ writeTBQueue subQ ("", entId, AEvt (sAEntity @e) cmd)
22132213

22142214
data ACKd = ACKd | ACKPending
@@ -2345,7 +2345,7 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(userId, srv, _), _v, sessId
23452345
HELLO -> helloMsg srvMsgId msgMeta conn'' >> ackDel msgId
23462346
-- note that there is no ACK sent for A_MSG, it is sent with agent's user ACK command
23472347
A_MSG body -> do
2348-
logServer "<--" c srv rId $ "MSG <MSG>:" <> logSecret srvMsgId
2348+
logServer "<--" c srv rId $ "MSG <MSG>:" <> logSecret' srvMsgId
23492349
notify $ MSG msgMeta msgFlags body
23502350
pure ACKPending
23512351
A_RCVD rcpts -> qDuplex conn'' "RCVD" $ messagesRcvd rcpts msgMeta
@@ -2355,7 +2355,7 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(userId, srv, _), _v, sessId
23552355
QUSE qs -> qDuplexAckDel conn'' "QUSE" $ qUseMsg srvMsgId qs
23562356
-- no action needed for QTEST
23572357
-- any message in the new queue will mark it active and trigger deletion of the old queue
2358-
QTEST _ -> logServer "<--" c srv rId ("MSG <QTEST>:" <> logSecret srvMsgId) >> ackDel msgId
2358+
QTEST _ -> logServer "<--" c srv rId ("MSG <QTEST>:" <> logSecret' srvMsgId) >> ackDel msgId
23592359
EREADY _ -> qDuplexAckDel conn'' "EREADY" $ ereadyMsg rcPrev
23602360
where
23612361
qDuplexAckDel :: Connection c -> String -> (Connection 'CDuplex -> AM ()) -> AM ACKd
@@ -2378,7 +2378,7 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(userId, srv, _), _v, sessId
23782378
| otherwise ->
23792379
liftEither (parse smpP (AGENT A_MESSAGE) agentMsgBody) >>= \case
23802380
AgentMessage _ (A_MSG body) -> do
2381-
logServer "<--" c srv rId $ "MSG <MSG>:" <> logSecret srvMsgId
2381+
logServer "<--" c srv rId $ "MSG <MSG>:" <> logSecret' srvMsgId
23822382
notify $ MSG msgMeta msgFlags body
23832383
pure ACKPending
23842384
_ -> ack
@@ -2500,7 +2500,7 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(userId, srv, _), _v, sessId
25002500

25012501
smpConfirmation :: SMP.MsgId -> Connection c -> Maybe C.APublicAuthKey -> C.PublicKeyX25519 -> Maybe (CR.SndE2ERatchetParams 'C.X448) -> ByteString -> VersionSMPC -> VersionSMPA -> AM ()
25022502
smpConfirmation srvMsgId conn' senderKey e2ePubKey e2eEncryption encConnInfo smpClientVersion agentVersion = do
2503-
logServer "<--" c srv rId $ "MSG <CONF>:" <> logSecret srvMsgId
2503+
logServer "<--" c srv rId $ "MSG <CONF>:" <> logSecret' srvMsgId
25042504
AgentConfig {smpClientVRange, smpAgentVRange, e2eEncryptVRange} <- asks config
25052505
let ConnData {pqSupport} = toConnData conn'
25062506
unless
@@ -2569,7 +2569,7 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(userId, srv, _), _v, sessId
25692569

25702570
helloMsg :: SMP.MsgId -> MsgMeta -> Connection c -> AM ()
25712571
helloMsg srvMsgId MsgMeta {pqEncryption} conn' = do
2572-
logServer "<--" c srv rId $ "MSG <HELLO>:" <> logSecret srvMsgId
2572+
logServer "<--" c srv rId $ "MSG <HELLO>:" <> logSecret' srvMsgId
25732573
case status of
25742574
Active -> prohibited "hello: active"
25752575
_ ->
@@ -2593,7 +2593,7 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(userId, srv, _), _v, sessId
25932593
continueSending srvMsgId addr (DuplexConnection _ _ sqs) =
25942594
case findQ addr sqs of
25952595
Just sq -> do
2596-
logServer "<--" c srv rId $ "MSG <QCONT>:" <> logSecret srvMsgId
2596+
logServer "<--" c srv rId $ "MSG <QCONT>:" <> logSecret' srvMsgId
25972597
atomically $
25982598
TM.lookup (qAddress sq) (smpDeliveryWorkers c)
25992599
>>= mapM_ (\(_, retryLock) -> tryPutTMVar retryLock ())
@@ -2602,7 +2602,7 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(userId, srv, _), _v, sessId
26022602

26032603
messagesRcvd :: NonEmpty AMessageReceipt -> MsgMeta -> Connection 'CDuplex -> AM ACKd
26042604
messagesRcvd rcpts msgMeta@MsgMeta {broker = (srvMsgId, _)} _ = do
2605-
logServer "<--" c srv rId $ "MSG <RCPT>:" <> logSecret srvMsgId
2605+
logServer "<--" c srv rId $ "MSG <RCPT>:" <> logSecret' srvMsgId
26062606
rs <- forM rcpts $ \rcpt -> clientReceipt rcpt `catchAgentError` \e -> notify (ERR e) $> Nothing
26072607
case L.nonEmpty . catMaybes $ L.toList rs of
26082608
Just rs' -> notify (RCVD msgMeta rs') $> ACKPending
@@ -2642,7 +2642,7 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(userId, srv, _), _v, sessId
26422642
sq2 <- withStore c $ \db -> do
26432643
liftIO $ mapM_ (deleteConnSndQueue db connId) delSqs
26442644
addConnSndQueue db connId (sq_ :: NewSndQueue) {primary = True, dbReplaceQueueId = Just dbQueueId}
2645-
logServer "<--" c srv rId $ "MSG <QADD>:" <> logSecret srvMsgId <> " " <> logSecret (senderId queueAddress)
2645+
logServer "<--" c srv rId $ "MSG <QADD>:" <> logSecret' srvMsgId <> " " <> logSecret (senderId queueAddress)
26462646
let sqInfo' = (sqInfo :: SMPQueueInfo) {queueAddress = queueAddress {dhPublicKey}}
26472647
void . enqueueMessages c cData' sqs SMP.noMsgFlags $ QKEY [(sqInfo', sndPublicKey)]
26482648
sq1 <- withStore' c $ \db -> setSndSwitchStatus db sq $ Just SSSendingQKEY
@@ -2663,7 +2663,7 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(userId, srv, _), _v, sessId
26632663
Just rq'@RcvQueue {rcvId, e2ePrivKey = dhPrivKey, smpClientVersion = cVer, status = status'}
26642664
| status' == New || status' == Confirmed -> do
26652665
checkRQSwchStatus rq RSSendingQADD
2666-
logServer "<--" c srv rId $ "MSG <QKEY>:" <> logSecret srvMsgId <> " " <> logSecret senderId
2666+
logServer "<--" c srv rId $ "MSG <QKEY>:" <> logSecret' srvMsgId <> " " <> logSecret senderId
26672667
let dhSecret = C.dh' dhPublicKey dhPrivKey
26682668
withStore' c $ \db -> setRcvQueueConfirmedE2E db rq' dhSecret $ min cVer cVer'
26692669
enqueueCommand c "" connId (Just smpServer) $ AInternalCommand $ ICQSecure rcvId senderKey
@@ -2684,7 +2684,7 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(userId, srv, _), _v, sessId
26842684
case find ((replaceQId ==) . dbQId) sqs of
26852685
Just sq1 -> do
26862686
checkSQSwchStatus sq1 SSSendingQKEY
2687-
logServer "<--" c srv rId $ "MSG <QUSE>:" <> logSecret srvMsgId <> " " <> logSecret (snd addr)
2687+
logServer "<--" c srv rId $ "MSG <QUSE>:" <> logSecret' srvMsgId <> " " <> logSecret (snd addr)
26882688
withStore' c $ \db -> setSndQueueStatus db sq' Secured
26892689
let sq'' = (sq' :: SndQueue) {status = Secured}
26902690
-- sending QTEST to the new queue only, the old one will be removed if sent successfully
@@ -2708,7 +2708,7 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(userId, srv, _), _v, sessId
27082708

27092709
smpInvitation :: SMP.MsgId -> Connection c -> ConnectionRequestUri 'CMInvitation -> ConnInfo -> AM ()
27102710
smpInvitation srvMsgId conn' connReq@(CRInvitationUri crData _) cInfo = do
2711-
logServer "<--" c srv rId $ "MSG <KEY>:" <> logSecret srvMsgId
2711+
logServer "<--" c srv rId $ "MSG <KEY>:" <> logSecret' srvMsgId
27122712
case conn' of
27132713
ContactConnection {} -> do
27142714
-- show connection request even if invitaion via contact address is not compatible.

0 commit comments

Comments
 (0)