@@ -70,9 +70,9 @@ import Simplex.Messaging.Protocol
70
70
QueueId ,
71
71
SMPServer ,
72
72
SParty (.. ),
73
- SubscriberParty ,
74
- subscriberParty ,
75
- subscriberServiceRole
73
+ ServiceParty ,
74
+ serviceParty ,
75
+ partyServiceRole
76
76
)
77
77
import Simplex.Messaging.Session
78
78
import Simplex.Messaging.TMap (TMap )
@@ -331,11 +331,11 @@ reconnectClient ca@SMPClientAgent {active, agentCfg, smpSubWorkers, workerSeq} s
331
331
332
332
reconnectSMPClient :: forall p . SMPClientAgent p -> SMPServer -> (Maybe (ServiceId , Int64 ), Maybe (Map QueueId C. APrivateAuthKey )) -> ExceptT SMPClientError IO ()
333
333
reconnectSMPClient ca@ SMPClientAgent {agentCfg, agentParty} srv (sSub_, qSubs_) =
334
- withSMP ca srv $ \ smp -> liftIO $ case subscriberParty agentParty of
334
+ withSMP ca srv $ \ smp -> liftIO $ case serviceParty agentParty of
335
335
Just Dict -> resubscribe smp
336
336
Nothing -> pure ()
337
337
where
338
- resubscribe :: (PartyI p , SubscriberParty p ) => SMPClient -> IO ()
338
+ resubscribe :: (PartyI p , ServiceParty p ) => SMPClient -> IO ()
339
339
resubscribe smp = do
340
340
mapM_ (smpSubscribeService ca smp srv) sSub_
341
341
forM_ qSubs_ $ \ qSubs -> do
@@ -394,22 +394,22 @@ withSMP ca srv action = (getSMPServerClient' ca srv >>= action) `catchE` logSMPE
394
394
logInfo $ " SMP error (" <> safeDecodeUtf8 (strEncode $ host srv) <> " ): " <> tshow e
395
395
throwE e
396
396
397
- subscribeQueuesNtfs :: SMPClientAgent 'Notifier -> SMPServer -> NonEmpty (NotifierId , NtfPrivateAuthKey ) -> IO ()
397
+ subscribeQueuesNtfs :: SMPClientAgent 'NotifierService -> SMPServer -> NonEmpty (NotifierId , NtfPrivateAuthKey ) -> IO ()
398
398
subscribeQueuesNtfs = subscribeQueues_
399
399
{-# INLINE subscribeQueuesNtfs #-}
400
400
401
- subscribeQueues_ :: SubscriberParty p => SMPClientAgent p -> SMPServer -> NonEmpty (QueueId , C. APrivateAuthKey ) -> IO ()
401
+ subscribeQueues_ :: ServiceParty p => SMPClientAgent p -> SMPServer -> NonEmpty (QueueId , C. APrivateAuthKey ) -> IO ()
402
402
subscribeQueues_ ca srv subs = do
403
403
atomically $ addPendingSubs ca srv $ L. toList subs
404
404
runExceptT (getSMPServerClient' ca srv) >>= \ case
405
405
Right smp -> smpSubscribeQueues ca smp srv subs
406
406
Left _ -> pure () -- no call to reconnectClient - failing getSMPServerClient' does that
407
407
408
- smpSubscribeQueues :: SubscriberParty p => SMPClientAgent p -> SMPClient -> SMPServer -> NonEmpty (QueueId , C. APrivateAuthKey ) -> IO ()
408
+ smpSubscribeQueues :: ServiceParty p => SMPClientAgent p -> SMPClient -> SMPServer -> NonEmpty (QueueId , C. APrivateAuthKey ) -> IO ()
409
409
smpSubscribeQueues ca smp srv subs = do
410
410
rs <- case agentParty ca of
411
- SRecipient -> subscribeSMPQueues smp subs
412
- SNotifier -> subscribeSMPQueuesNtfs smp subs
411
+ SRecipientService -> subscribeSMPQueues smp subs
412
+ SNotifierService -> subscribeSMPQueuesNtfs smp subs
413
413
rs' <-
414
414
atomically $
415
415
ifM
@@ -454,18 +454,18 @@ smpSubscribeQueues ca smp srv subs = do
454
454
notify_ :: (SMPServer -> NonEmpty a -> SMPClientAgentEvent ) -> [a ] -> IO ()
455
455
notify_ evt qs = mapM_ (notify ca . evt srv) $ L. nonEmpty qs
456
456
457
- subscribeServiceNtfs :: SMPClientAgent 'Notifier -> SMPServer -> (ServiceId , Int64 ) -> IO ()
457
+ subscribeServiceNtfs :: SMPClientAgent 'NotifierService -> SMPServer -> (ServiceId , Int64 ) -> IO ()
458
458
subscribeServiceNtfs = subscribeService_
459
459
{-# INLINE subscribeServiceNtfs #-}
460
460
461
- subscribeService_ :: (PartyI p , SubscriberParty p ) => SMPClientAgent p -> SMPServer -> (ServiceId , Int64 ) -> IO ()
461
+ subscribeService_ :: (PartyI p , ServiceParty p ) => SMPClientAgent p -> SMPServer -> (ServiceId , Int64 ) -> IO ()
462
462
subscribeService_ ca srv serviceSub = do
463
463
atomically $ setPendingServiceSub ca srv $ Just serviceSub
464
464
runExceptT (getSMPServerClient' ca srv) >>= \ case
465
465
Right smp -> smpSubscribeService ca smp srv serviceSub
466
466
Left _ -> pure () -- no call to reconnectClient - failing getSMPServerClient' does that
467
467
468
- smpSubscribeService :: (PartyI p , SubscriberParty p ) => SMPClientAgent p -> SMPClient -> SMPServer -> (ServiceId , Int64 ) -> IO ()
468
+ smpSubscribeService :: (PartyI p , ServiceParty p ) => SMPClientAgent p -> SMPClient -> SMPServer -> (ServiceId , Int64 ) -> IO ()
469
469
smpSubscribeService ca smp srv serviceSub@ (serviceId, _) = case smpClientService smp of
470
470
Just service | serviceAvailable service -> subscribe
471
471
_ -> notifyUnavailable
@@ -490,7 +490,7 @@ smpSubscribeService ca smp srv serviceSub@(serviceId, _) = case smpClientService
490
490
setActiveServiceSub ca srv $ Just ((serviceId, n), sessId)
491
491
setPendingServiceSub ca srv Nothing
492
492
serviceAvailable THClientService {serviceRole, serviceId = serviceId'} =
493
- serviceId == serviceId' && subscriberServiceRole (agentParty ca) == serviceRole
493
+ serviceId == serviceId' && partyServiceRole (agentParty ca) == serviceRole
494
494
notifyUnavailable = do
495
495
atomically $ setPendingServiceSub ca srv Nothing
496
496
notify ca $ CAServiceUnavailable srv serviceSub -- this will resubscribe all queues directly
0 commit comments