@@ -120,6 +120,7 @@ module Simplex.Messaging.Agent.Client
120120 getAgentSubscriptions ,
121121 slowNetworkConfig ,
122122 protocolClientError ,
123+ clientServiceError ,
123124 Worker (.. ),
124125 SessionVar (.. ),
125126 SubscriptionsInfo (.. ),
@@ -303,7 +304,7 @@ import Simplex.Messaging.Session
303304import Simplex.Messaging.SystemTime
304305import Simplex.Messaging.TMap (TMap )
305306import qualified Simplex.Messaging.TMap as TM
306- import Simplex.Messaging.Transport (SMPServiceRole (.. ), SMPVersion , ServiceCredentials (.. ), SessionId , THClientService' (.. ), THandleParams (sessionId , thVersion ), TransportError (.. ), TransportPeer (.. ), sndAuthKeySMPVersion , shortLinksSMPVersion , newNtfCredsSMPVersion )
307+ import Simplex.Messaging.Transport (HandshakeError ( .. ), SMPServiceRole (.. ), SMPVersion , ServiceCredentials (.. ), SessionId , THClientService' (.. ), THandleAuth ( .. ), THandleParams (sessionId , thAuth , thVersion ), TransportError (.. ), TransportPeer (.. ), sndAuthKeySMPVersion , shortLinksSMPVersion , newNtfCredsSMPVersion )
307308import Simplex.Messaging.Transport.Client (TransportHost (.. ))
308309import Simplex.Messaging.Transport.Credentials
309310import Simplex.Messaging.Util
@@ -619,7 +620,7 @@ getServiceCredentials c userId srv =
619620 let g = agentDRG c
620621 ((C. KeyHash kh, serviceCreds), serviceId_) <-
621622 withStore' c $ \ db ->
622- getClientService db userId srv >>= \ case
623+ getClientServiceCredentials db userId srv >>= \ case
623624 Just service -> pure service
624625 Nothing -> do
625626 cred <- genCredentials g Nothing (25 , 24 * 999999 ) " simplex"
@@ -747,15 +748,13 @@ smpConnectClient c@AgentClient {smpClients, msgQ, proxySessTs, presetDomains} nm
747748 smp <- liftError (protocolClientError SMP $ B. unpack $ strEncode srv) $ do
748749 ts <- readTVarIO proxySessTs
749750 ExceptT $ getProtocolClient g nm tSess cfg' presetDomains (Just msgQ) ts $ smpClientDisconnected c tSess env v' prs
750- -- TODO [certs rcv] add service to SS, possibly combine with SS.setSessionId
751751 atomically $ SS. setSessionId tSess (sessionId $ thParams smp) $ currentSubs c
752752 updateClientService service smp
753753 pure SMPConnectedClient {connectedClient = smp, proxiedRelays = prs}
754- -- TODO [certs rcv] this should differentiate between service ID just set and service ID changed, and in the latter case disassociate the queues
755754 updateClientService service smp = case (service, smpClientService smp) of
756- (Just (_, serviceId_), Just THClientService {serviceId})
757- | serviceId_ /= Just serviceId -> withStore' c $ \ db -> setClientServiceId db userId srv serviceId
758- | otherwise -> pure ()
755+ (Just (_, serviceId_), Just THClientService {serviceId}) -> withStore' c $ \ db -> do
756+ setClientServiceId db userId srv serviceId
757+ forM_ serviceId_ $ \ sId -> when (sId /= serviceId) $ removeRcvServiceAssocs db userId srv
759758 (Just _, Nothing ) -> withStore' c $ \ db -> deleteClientService db userId srv -- e.g., server version downgrade
760759 (Nothing , Just _) -> logError " server returned serviceId without service credentials in request"
761760 (Nothing , Nothing ) -> pure ()
@@ -1258,6 +1257,14 @@ protocolClientError protocolError_ host = \case
12581257 PCEServiceUnavailable {} -> BROKER host NO_SERVICE
12591258 PCEIOError e -> BROKER host $ NETWORK $ NEConnectError $ E. displayException e
12601259
1260+ -- it is consistent with smpClientServiceError
1261+ clientServiceError :: AgentErrorType -> Bool
1262+ clientServiceError = \ case
1263+ BROKER _ NO_SERVICE -> True
1264+ SMP _ SMP. SERVICE -> True
1265+ SMP _ (SMP. PROXY (SMP. BROKER NO_SERVICE )) -> True -- for completeness, it cannot happen.
1266+ _ -> False
1267+
12611268data ProtocolTestStep
12621269 = TSConnect
12631270 | TSDisconnect
@@ -1446,8 +1453,8 @@ newRcvQueue_ c nm userId connId (ProtoServerWithAuth srv auth) vRange cqrd enabl
14461453 withClient c nm tSess $ \ (SMPConnectedClient smp _) -> do
14471454 (ntfKeys, ntfCreds) <- liftIO $ mkNtfCreds a g smp
14481455 (thParams smp,ntfKeys,) <$> createSMPQueue smp nm nonce_ rKeys dhKey auth subMode (queueReqData cqrd) ntfCreds
1449- -- TODO [certs rcv] validate that serviceId is the same as in the client session, fail otherwise
1450- -- possibly, it should allow returning Nothing - it would indicate incorrect old version
1456+ let sessServiceId = ( \ THClientService { serviceId = sId} -> sId) <$> (clientService =<< thAuth thParams')
1457+ when (isJust serviceId && serviceId /= sessServiceId) $ logError " incorrect service ID in NEW response "
14511458 liftIO . logServer " <--" c srv NoEntity $ B. unwords [" IDS" , logSecret rcvId, logSecret sndId]
14521459 shortLink <- mkShortLinkCreds thParams' qik
14531460 let rq =
@@ -1463,7 +1470,7 @@ newRcvQueue_ c nm userId connId (ProtoServerWithAuth srv auth) vRange cqrd enabl
14631470 sndId,
14641471 queueMode,
14651472 shortLink,
1466- rcvServiceAssoc = isJust serviceId,
1473+ rcvServiceAssoc = isJust serviceId && serviceId == sessServiceId ,
14671474 status = New ,
14681475 enableNtfs,
14691476 clientNoticeId = Nothing ,
@@ -1559,6 +1566,8 @@ temporaryAgentError :: AgentErrorType -> Bool
15591566temporaryAgentError = \ case
15601567 BROKER _ e -> tempBrokerError e
15611568 SMP _ (SMP. PROXY (SMP. BROKER e)) -> tempBrokerError e
1569+ SMP _ (SMP. STORE _) -> True
1570+ NTF _ (SMP. STORE _) -> True
15621571 XFTP _ XFTP. TIMEOUT -> True
15631572 PROXY _ _ (ProxyProtocolError (SMP. PROXY (SMP. BROKER e))) -> tempBrokerError e
15641573 PROXY _ _ (ProxyProtocolError (SMP. PROXY SMP. NO_SESSION )) -> True
@@ -1569,6 +1578,7 @@ temporaryAgentError = \case
15691578 tempBrokerError = \ case
15701579 NETWORK _ -> True
15711580 TIMEOUT -> True
1581+ TRANSPORT (TEHandshake BAD_SERVICE ) -> True -- this error is considered temporary because it is DB error
15721582 _ -> False
15731583
15741584temporaryOrHostError :: AgentErrorType -> Bool
@@ -1715,11 +1725,16 @@ processClientNotices c@AgentClient {presetServers} tSess notices = do
17151725 notifySub' c " " $ ERR e
17161726
17171727resubscribeClientService :: AgentClient -> SMPTransportSession -> ServiceSub -> AM ServiceSubResult
1718- resubscribeClientService c tSess serviceSub =
1719- withServiceClient c tSess $ \ smp _ -> subscribeClientService_ c True tSess smp serviceSub
1720-
1721- subscribeClientService :: AgentClient -> Bool -> UserId -> SMPServer -> Int64 -> IdsHash -> AM ServiceSubResult
1722- subscribeClientService c withEvent userId srv n idsHash =
1728+ resubscribeClientService c tSess@ (userId, srv, _) serviceSub =
1729+ withServiceClient c tSess (\ smp _ -> subscribeClientService_ c True tSess smp serviceSub) `catchE` \ e -> do
1730+ when (clientServiceError e) $ do
1731+ qs <- withStore' c $ \ db -> unassocUserServerRcvQueueSubs db userId srv
1732+ void $ lift $ subscribeUserServerQueues c userId srv qs
1733+ throwE e
1734+
1735+ -- TODO [certs rcv] update service in the database if it has different ID and re-associate queues, and send event
1736+ subscribeClientService :: AgentClient -> Bool -> UserId -> SMPServer -> ServiceSub -> AM ServiceSubResult
1737+ subscribeClientService c withEvent userId srv (ServiceSub _ n idsHash) =
17231738 withServiceClient c tSess $ \ smp smpServiceId -> do
17241739 let serviceSub = ServiceSub smpServiceId n idsHash
17251740 atomically $ SS. setPendingServiceSub tSess serviceSub $ currentSubs c
@@ -1728,14 +1743,15 @@ subscribeClientService c withEvent userId srv n idsHash =
17281743 tSess = (userId, srv, Nothing )
17291744
17301745withServiceClient :: AgentClient -> SMPTransportSession -> (SMPClient -> ServiceId -> ExceptT SMPClientError IO a ) -> AM a
1731- withServiceClient c tSess action =
1746+ withServiceClient c tSess subscribe =
17321747 withLogClient c NRMBackground tSess B. empty " SUBS" $ \ (SMPConnectedClient smp _) ->
17331748 case (\ THClientService {serviceId} -> serviceId) <$> smpClientService smp of
1734- Just smpServiceId -> action smp smpServiceId
1749+ Just smpServiceId -> subscribe smp smpServiceId
17351750 Nothing -> throwE PCEServiceUnavailable
17361751
1752+ -- TODO [certs rcv] send subscription error event?
17371753subscribeClientService_ :: AgentClient -> Bool -> SMPTransportSession -> SMPClient -> ServiceSub -> ExceptT SMPClientError IO ServiceSubResult
1738- subscribeClientService_ c withEvent tSess@ (_ , srv, _) smp expected@ (ServiceSub _ n idsHash) = do
1754+ subscribeClientService_ c withEvent tSess@ (userId , srv, _) smp expected@ (ServiceSub _ n idsHash) = do
17391755 subscribed <- subscribeService smp SMP. SRecipientService n idsHash
17401756 let sessId = sessionId $ thParams smp
17411757 r = serviceSubResult expected subscribed
0 commit comments