Skip to content

Commit 18e73b8

Browse files
authored
agent: pass CRClientData to setContactShortLink (#1546)
* agent: pass CRClientData to setContactShortLink * fix * fix
1 parent af9ca59 commit 18e73b8

File tree

3 files changed

+17
-12
lines changed

3 files changed

+17
-12
lines changed

src/Simplex/Messaging/Agent.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -371,8 +371,8 @@ createConnection c userId enableNtfs = withAgentEnv c .::. newConn c userId enab
371371
{-# INLINE createConnection #-}
372372

373373
-- | Create or update user's contact connection short link
374-
setContactShortLink :: AgentClient -> ConnId -> ConnInfo -> AE (ConnShortLink 'CMContact)
375-
setContactShortLink c = withAgentEnv c .: setContactShortLink' c
374+
setContactShortLink :: AgentClient -> ConnId -> ConnInfo -> Maybe CRClientData -> AE (ConnShortLink 'CMContact)
375+
setContactShortLink c = withAgentEnv c .:. setContactShortLink' c
376376
{-# INLINE setContactShortLink #-}
377377

378378
deleteContactShortLink :: AgentClient -> ConnId -> AE ()
@@ -832,8 +832,8 @@ newConn c userId enableNtfs cMode userData_ clientData pqInitKeys subMode = do
832832
(connId,) <$> newRcvConnSrv c userId connId enableNtfs cMode userData_ clientData pqInitKeys subMode srv
833833
`catchE` \e -> withStore' c (`deleteConnRecord` connId) >> throwE e
834834

835-
setContactShortLink' :: AgentClient -> ConnId -> ConnInfo -> AM (ConnShortLink 'CMContact)
836-
setContactShortLink' c connId userData =
835+
setContactShortLink' :: AgentClient -> ConnId -> ConnInfo -> Maybe CRClientData -> AM (ConnShortLink 'CMContact)
836+
setContactShortLink' c connId userData clientData =
837837
withConnLock c connId "setContactShortLink" $
838838
withStore c (`getConn` connId) >>= \case
839839
SomeConn _ (ContactConnection _ rq) -> do
@@ -855,7 +855,7 @@ setContactShortLink' c connId userData =
855855
Nothing -> do
856856
sigKeys@(_, privSigKey) <- atomically $ C.generateKeyPair @'C.Ed25519 g
857857
let qUri = SMPQueueUri vr $ SMPQueueAddress server sndId (C.publicKey e2ePrivKey) (Just QMContact)
858-
connReq = CRContactUri $ ConnReqUriData SSSimplex smpAgentVRange [qUri] Nothing
858+
connReq = CRContactUri $ ConnReqUriData SSSimplex smpAgentVRange [qUri] clientData
859859
(linkKey, linkData) = SL.encodeSignLinkData sigKeys smpAgentVRange connReq userData
860860
(linkId, k) = SL.contactShortLinkKdf linkKey
861861
srvData <- liftError id $ SL.encryptLinkData g k linkData

src/Simplex/Messaging/TMap.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ module Simplex.Messaging.TMap
1313
insert,
1414
insertM,
1515
delete,
16+
lookupInsert,
1617
lookupDelete,
1718
adjust,
1819
update,
@@ -72,6 +73,10 @@ delete :: Ord k => k -> TMap k a -> STM ()
7273
delete k m = modifyTVar' m $ M.delete k
7374
{-# INLINE delete #-}
7475

76+
lookupInsert :: Ord k => k -> a -> TMap k a -> STM (Maybe a)
77+
lookupInsert k v m = stateTVar m $ M.alterF (,Just v) k
78+
{-# INLINE lookupInsert #-}
79+
7580
lookupDelete :: Ord k => k -> TMap k a -> STM (Maybe a)
7681
lookupDelete k m = stateTVar m $ M.alterF (,Nothing) k
7782
{-# INLINE lookupDelete #-}

tests/AgentTests/FunctionalAPITests.hs

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1200,13 +1200,13 @@ testContactShortLink viaProxy a b =
12001200
exchangeGreetingsViaProxy viaProxy a bId b aId
12011201
-- update user data
12021202
let updatedData = "updated user data"
1203-
shortLink' <- runRight $ setContactShortLink a contactId updatedData
1203+
shortLink' <- runRight $ setContactShortLink a contactId updatedData Nothing
12041204
shortLink' `shouldBe` shortLink
12051205
(connReq4, updatedConnData') <- runRight $ getConnShortLink c 1 shortLink
12061206
connReq4 `shouldBe` connReq
12071207
linkUserData updatedConnData' `shouldBe` updatedData
12081208
-- one more time
1209-
shortLink2 <- runRight $ setContactShortLink a contactId updatedData
1209+
shortLink2 <- runRight $ setContactShortLink a contactId updatedData Nothing
12101210
shortLink2 `shouldBe` shortLink
12111211
-- delete short link
12121212
runRight_ $ deleteContactShortLink a contactId
@@ -1219,7 +1219,7 @@ testAddContactShortLink viaProxy a b =
12191219
(contactId, CCLink connReq0 Nothing) <- runRight $ A.createConnection a 1 True SCMContact Nothing Nothing CR.IKPQOn SMSubscribe
12201220
Right connReq <- pure $ smpDecode (smpEncode connReq0) --
12211221
let userData = "some user data"
1222-
shortLink <- runRight $ setContactShortLink a contactId userData
1222+
shortLink <- runRight $ setContactShortLink a contactId userData Nothing
12231223
(connReq', connData') <- runRight $ getConnShortLink b 1 shortLink
12241224
strDecode (strEncode shortLink) `shouldBe` Right shortLink
12251225
connReq' `shouldBe` connReq
@@ -1247,7 +1247,7 @@ testAddContactShortLink viaProxy a b =
12471247
exchangeGreetingsViaProxy viaProxy a bId b aId
12481248
-- update user data
12491249
let updatedData = "updated user data"
1250-
shortLink' <- runRight $ setContactShortLink a contactId updatedData
1250+
shortLink' <- runRight $ setContactShortLink a contactId updatedData Nothing
12511251
shortLink' `shouldBe` shortLink
12521252
(connReq4, updatedConnData') <- runRight $ getConnShortLink c 1 shortLink
12531253
connReq4 `shouldBe` connReq
@@ -1278,7 +1278,7 @@ testContactShortLinkRestart ps = withAgentClients2 $ \a b -> do
12781278
connReq' `shouldBe` connReq
12791279
linkUserData connData' `shouldBe` userData
12801280
-- update user data
1281-
shortLink' <- runRight $ setContactShortLink a contactId updatedData
1281+
shortLink' <- runRight $ setContactShortLink a contactId updatedData Nothing
12821282
shortLink' `shouldBe` shortLink
12831283
withSmpServer ps $ do
12841284
(connReq4, updatedConnData') <- runRight $ getConnShortLink b 1 shortLink
@@ -1290,7 +1290,7 @@ testAddContactShortLinkRestart ps = withAgentClients2 $ \a b -> do
12901290
let userData = "some user data"
12911291
((contactId, CCLink connReq0 Nothing), shortLink) <- withSmpServer ps $ runRight $ do
12921292
r@(contactId, _) <- A.createConnection a 1 True SCMContact Nothing Nothing CR.IKPQOn SMOnlyCreate
1293-
(r,) <$> setContactShortLink a contactId userData
1293+
(r,) <$> setContactShortLink a contactId userData Nothing
12941294
Right connReq <- pure $ smpDecode (smpEncode connReq0)
12951295
let updatedData = "updated user data"
12961296
withSmpServer ps $ do
@@ -1299,7 +1299,7 @@ testAddContactShortLinkRestart ps = withAgentClients2 $ \a b -> do
12991299
connReq' `shouldBe` connReq
13001300
linkUserData connData' `shouldBe` userData
13011301
-- update user data
1302-
shortLink' <- runRight $ setContactShortLink a contactId updatedData
1302+
shortLink' <- runRight $ setContactShortLink a contactId updatedData Nothing
13031303
shortLink' `shouldBe` shortLink
13041304
withSmpServer ps $ do
13051305
(connReq4, updatedConnData') <- runRight $ getConnShortLink b 1 shortLink

0 commit comments

Comments
 (0)