@@ -48,6 +48,7 @@ module Simplex.Messaging.Agent.Client
4848 newRcvQueue ,
4949 newRcvQueue_ ,
5050 subscribeQueues ,
51+ subscribeClientService ,
5152 getQueueMessage ,
5253 decryptSMPMessage ,
5354 addSubscription ,
@@ -215,6 +216,7 @@ import Data.Text.Encoding
215216import Data.Time (UTCTime , addUTCTime , defaultTimeLocale , formatTime , getCurrentTime )
216217import Data.Time.Clock.System (getSystemTime )
217218import Data.Word (Word16 )
219+ import qualified Data.X509.Validation as XV
218220import Network.Socket (HostName )
219221import Simplex.FileTransfer.Client (XFTPChunkSpec (.. ), XFTPClient , XFTPClientConfig (.. ), XFTPClientError )
220222import qualified Simplex.FileTransfer.Client as X
@@ -230,7 +232,8 @@ import Simplex.Messaging.Agent.Protocol
230232import Simplex.Messaging.Agent.RetryInterval
231233import Simplex.Messaging.Agent.Stats
232234import Simplex.Messaging.Agent.Store
233- import Simplex.Messaging.Agent.Store.Common (DBStore , withTransaction )
235+ import Simplex.Messaging.Agent.Store.AgentStore
236+ import Simplex.Messaging.Agent.Store.Common (DBStore )
234237import qualified Simplex.Messaging.Agent.Store.DB as DB
235238import Simplex.Messaging.Agent.TRcvQueues (TRcvQueues (getRcvQueues ))
236239import qualified Simplex.Messaging.Agent.TRcvQueues as RQ
@@ -284,8 +287,9 @@ import Simplex.Messaging.Session
284287import Simplex.Messaging.Agent.Store.Entity
285288import Simplex.Messaging.TMap (TMap )
286289import qualified Simplex.Messaging.TMap as TM
287- import Simplex.Messaging.Transport (SMPVersion , ServiceCredentials , SessionId , THandleParams (sessionId , thVersion ), TransportError (.. ), TransportPeer (.. ), sndAuthKeySMPVersion , shortLinksSMPVersion , newNtfCredsSMPVersion )
290+ import Simplex.Messaging.Transport (SMPServiceRole ( .. ), SMPVersion , ServiceCredentials ( .. ) , SessionId , THClientService' ( .. ) , THandleParams (sessionId , thVersion ), TransportError (.. ), TransportPeer (.. ), sndAuthKeySMPVersion , shortLinksSMPVersion , newNtfCredsSMPVersion )
288291import Simplex.Messaging.Transport.Client (TransportHost (.. ))
292+ import Simplex.Messaging.Transport.Credentials
289293import Simplex.Messaging.Util
290294import Simplex.Messaging.Version
291295import System.Mem.Weak (Weak , deRefWeak )
@@ -321,7 +325,7 @@ data AgentClient = AgentClient
321325 msgQ :: TBQueue (ServerTransmissionBatch SMPVersion ErrorType BrokerMsg ),
322326 smpServers :: TMap UserId (UserServers 'PSMP),
323327 smpClients :: TMap SMPTransportSession SMPClientVar ,
324- smpServiceCreds :: TMap UserId ( Maybe ( TMap SMPServer ServiceCredentials )), -- Nothing means not to use certificates for this user record
328+ useClientServices :: TMap UserId Bool ,
325329 -- smpProxiedRelays:
326330 -- SMPTransportSession defines connection from proxy to relay,
327331 -- SMPServerWithAuth defines client connected to SMP proxy (with the same userId and entityId in TransportSession)
@@ -494,7 +498,7 @@ newAgentClient clientId InitialAgentServers {smp, ntf, xftp, netCfg, useServices
494498 msgQ <- newTBQueueIO qSize
495499 smpServers <- newTVarIO $ M. map mkUserServers smp
496500 smpClients <- TM. emptyIO
497- smpServiceCreds <- newTVarIO =<< mapM ( \ enable -> if enable then Just <$> TM. emptyIO else pure Nothing ) useServices
501+ useClientServices <- newTVarIO useServices
498502 smpProxiedRelays <- TM. emptyIO
499503 ntfServers <- newTVarIO ntf
500504 ntfClients <- TM. emptyIO
@@ -533,7 +537,7 @@ newAgentClient clientId InitialAgentServers {smp, ntf, xftp, netCfg, useServices
533537 msgQ,
534538 smpServers,
535539 smpClients,
536- smpServiceCreds ,
540+ useClientServices ,
537541 smpProxiedRelays,
538542 ntfServers,
539543 ntfClients,
@@ -586,6 +590,28 @@ agentDRG :: AgentClient -> TVar ChaChaDRG
586590agentDRG AgentClient {agentEnv = Env {random}} = random
587591{-# INLINE agentDRG #-}
588592
593+ getServiceCredentials :: AgentClient -> UserId -> SMPServer -> AM (Maybe (ServiceCredentials , Maybe ServiceId ))
594+ getServiceCredentials c userId srv =
595+ liftIO (TM. lookupIO userId $ useClientServices c)
596+ $>>= \ useService -> if useService then Just <$> getService else pure Nothing
597+ where
598+ getService :: AM (ServiceCredentials , Maybe ServiceId )
599+ getService = do
600+ let g = agentDRG c
601+ ((C. KeyHash kh, serviceCreds), serviceId_) <-
602+ withStore' c $ \ db ->
603+ getClientService db userId srv >>= \ case
604+ Just service -> pure service
605+ Nothing -> do
606+ cred <- genCredentials g Nothing (25 , 24 * 999999 ) " simplex"
607+ let tlsCreds = tlsCredentials [cred]
608+ createClientService db userId srv tlsCreds
609+ pure (tlsCreds, Nothing )
610+ (_, pk) <- atomically $ C. generateKeyPair g
611+ let serviceSignKey = C. APrivateSignKey C. SEd25519 pk
612+ creds = ServiceCredentials {serviceRole = SRMessaging , serviceCreds, serviceCertHash = XV. Fingerprint kh, serviceSignKey}
613+ pure (creds, serviceId_)
614+
589615class (Encoding err , Show err ) => ProtocolServerClient v err msg | msg -> v , msg -> err where
590616 type Client msg = c | c -> msg
591617 getProtocolServerClient :: AgentClient -> NetworkRequestMode -> TransportSession msg -> AM (Client msg )
@@ -689,19 +715,29 @@ getSMPProxyClient c@AgentClient {active, smpClients, smpProxiedRelays, workerSeq
689715 Nothing -> Left $ BROKER (B. unpack $ strEncode srv) TIMEOUT
690716
691717smpConnectClient :: AgentClient -> NetworkRequestMode -> SMPTransportSession -> TMap SMPServer ProxiedRelayVar -> SMPClientVar -> AM SMPConnectedClient
692- smpConnectClient c@ AgentClient {smpClients, msgQ, proxySessTs} nm tSess@ (_ , srv, _) prs v =
718+ smpConnectClient c@ AgentClient {smpClients, msgQ, proxySessTs} nm tSess@ (userId , srv, _) prs v =
693719 newProtocolClient c tSess smpClients connectClient v
694720 `catchAgentError` \ e -> lift (resubscribeSMPSession c tSess) >> throwE e
695721 where
696722 connectClient :: SMPClientVar -> AM SMPConnectedClient
697723 connectClient v' = do
698724 cfg <- lift $ getClientConfig c smpCfg
699725 g <- asks random
726+ service <- getServiceCredentials c userId srv
727+ let cfg' = cfg {serviceCredentials = fst <$> service}
700728 env <- ask
701- liftError (protocolClientError SMP $ B. unpack $ strEncode srv) $ do
729+ smp <- liftError (protocolClientError SMP $ B. unpack $ strEncode srv) $ do
702730 ts <- readTVarIO proxySessTs
703- smp <- ExceptT $ getProtocolClient g nm tSess cfg (presetSMPDomains c) (Just msgQ) ts $ smpClientDisconnected c tSess env v' prs
704- pure SMPConnectedClient {connectedClient = smp, proxiedRelays = prs}
731+ ExceptT $ getProtocolClient g nm tSess cfg' (presetSMPDomains c) (Just msgQ) ts $ smpClientDisconnected c tSess env v' prs
732+ updateClientService service smp
733+ pure SMPConnectedClient {connectedClient = smp, proxiedRelays = prs}
734+ updateClientService service smp = case (service, smpClientService smp) of
735+ (Just (_, serviceId_), Just THClientService {serviceId})
736+ | serviceId_ /= Just serviceId -> withStore' c $ \ db -> setClientServiceId db userId srv serviceId
737+ | otherwise -> pure ()
738+ (Just _, Nothing ) -> withStore' c $ \ db -> deleteClientService db userId srv -- e.g., server version downgrade
739+ (Nothing , Just _) -> logError " server returned serviceId without service credentials in request"
740+ (Nothing , Nothing ) -> pure ()
705741
706742smpClientDisconnected :: AgentClient -> SMPTransportSession -> Env -> SMPClientVar -> TMap SMPServer ProxiedRelayVar -> SMPClient -> IO ()
707743smpClientDisconnected c@ AgentClient {active, smpClients, smpProxiedRelays} tSess@ (userId, srv, qId) env v prs client = do
@@ -858,7 +894,6 @@ waitForProtocolClient c nm tSess@(_, srv, _) clients v = do
858894 (throwE e)
859895 Nothing -> throwE $ BROKER (B. unpack $ strEncode srv) TIMEOUT
860896
861- -- clientConnected arg is only passed for SMP server
862897newProtocolClient ::
863898 forall v err msg .
864899 (ProtocolTypeI (ProtoType msg ), ProtocolServerClient v err msg ) =>
@@ -1355,7 +1390,7 @@ getSessionMode :: MonadIO m => AgentClient -> m TransportSessionMode
13551390getSessionMode = fmap sessionMode . getNetworkConfig
13561391{-# INLINE getSessionMode #-}
13571392
1358- newRcvQueue :: AgentClient -> NetworkRequestMode -> UserId -> ConnId -> SMPServerWithAuth -> VersionRangeSMPC -> SConnectionMode c -> Bool -> SubscriptionMode -> AM (NewRcvQueue , SMPQueueUri , Maybe ServiceId , SMPTransportSession , SessionId )
1393+ newRcvQueue :: AgentClient -> NetworkRequestMode -> UserId -> ConnId -> SMPServerWithAuth -> VersionRangeSMPC -> SConnectionMode c -> Bool -> SubscriptionMode -> AM (NewRcvQueue , SMPQueueUri , SMPTransportSession , SessionId )
13591394newRcvQueue c nm userId connId srv vRange cMode enableNtfs subMode = do
13601395 let qrd = case cMode of SCMInvitation -> CQRMessaging Nothing ; SCMContact -> CQRContact Nothing
13611396 e2eKeys <- atomically . C. generateKeyPair =<< asks random
@@ -1376,7 +1411,7 @@ queueReqData = \case
13761411 CQRMessaging d -> QRMessaging $ srvReq <$> d
13771412 CQRContact d -> QRContact $ srvReq <$> d
13781413
1379- newRcvQueue_ :: AgentClient -> NetworkRequestMode -> UserId -> ConnId -> SMPServerWithAuth -> VersionRangeSMPC -> ClntQueueReqData -> Bool -> SubscriptionMode -> Maybe C. CbNonce -> C. KeyPairX25519 -> AM (NewRcvQueue , SMPQueueUri , Maybe ServiceId , SMPTransportSession , SessionId )
1414+ newRcvQueue_ :: AgentClient -> NetworkRequestMode -> UserId -> ConnId -> SMPServerWithAuth -> VersionRangeSMPC -> ClntQueueReqData -> Bool -> SubscriptionMode -> Maybe C. CbNonce -> C. KeyPairX25519 -> AM (NewRcvQueue , SMPQueueUri , SMPTransportSession , SessionId )
13801415newRcvQueue_ c nm userId connId (ProtoServerWithAuth srv auth) vRange cqrd enableNtfs subMode nonce_ (e2eDhKey, e2ePrivKey) = do
13811416 C. AuthAlg a <- asks (rcvAuthAlg . config)
13821417 g <- asks random
@@ -1388,7 +1423,7 @@ newRcvQueue_ c nm userId connId (ProtoServerWithAuth srv auth) vRange cqrd enabl
13881423 withClient c nm tSess $ \ (SMPConnectedClient smp _) -> do
13891424 (ntfKeys, ntfCreds) <- liftIO $ mkNtfCreds a g smp
13901425 (thParams smp,ntfKeys,) <$> createSMPQueue smp nm nonce_ rKeys dhKey auth subMode (queueReqData cqrd) ntfCreds
1391- -- TODO [certs rcv] validate that serviceId is the same as in the client session
1426+ -- TODO [certs rcv] validate that serviceId is the same as in the client session, fail otherwise
13921427 liftIO . logServer " <--" c srv NoEntity $ B. unwords [" IDS" , logSecret rcvId, logSecret sndId]
13931428 shortLink <- mkShortLinkCreds thParams' qik
13941429 let rq =
@@ -1415,7 +1450,7 @@ newRcvQueue_ c nm userId connId (ProtoServerWithAuth srv auth) vRange cqrd enabl
14151450 deleteErrors = 0
14161451 }
14171452 qUri = SMPQueueUri vRange $ SMPQueueAddress srv sndId e2eDhKey queueMode
1418- pure (rq, qUri, serviceId, tSess, sessionId thParams')
1453+ pure (rq, qUri, tSess, sessionId thParams')
14191454 where
14201455 mkNtfCreds :: (C. AlgorithmI a , C. AuthAlgorithm a ) => C. SAlgorithm a -> TVar ChaChaDRG -> SMPClient -> IO (Maybe (C. AAuthKeyPair , C. PrivateKeyX25519 ), Maybe NewNtfCreds )
14211456 mkNtfCreds a g smp
@@ -1540,6 +1575,11 @@ subscribeQueues c qs = do
15401575 processSubResults = mapM_ $ uncurry $ processSubResult c sessId
15411576 resubscribe = resubscribeSMPSession c tSess `runReaderT` env
15421577
1578+ subscribeClientService :: AgentClient -> UserId -> SMPServer -> AM Int64
1579+ subscribeClientService c userId srv =
1580+ withLogClient c NRMBackground (userId, srv, Nothing ) B. empty " SUBS" $
1581+ (`subscribeService` SMP. SRecipientService ) . connectedClient
1582+
15431583activeClientSession :: AgentClient -> SMPTransportSession -> SessionId -> STM Bool
15441584activeClientSession c tSess sessId = sameSess <$> tryReadSessVar tSess (smpClients c)
15451585 where
0 commit comments