Skip to content

Commit 944a22a

Browse files
authored
ntf server: record token invalidation reason, add date of the last token activity (#1449)
* ntf server: record token invalidation reason, add date of the last token activity * update time * rename * optional * include token ID in delivery error * version * protocol version * fix, log error
1 parent ce24f83 commit 944a22a

File tree

8 files changed

+153
-89
lines changed

8 files changed

+153
-89
lines changed

simplexmq.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
cabal-version: 1.12
22

33
name: simplexmq
4-
version: 6.3.0.3
4+
version: 6.3.0.301
55
synopsis: SimpleXMQ message broker
66
description: This package includes <./docs/Simplex-Messaging-Server.html server>,
77
<./docs/Simplex-Messaging-Client.html client> and

src/Simplex/Messaging/Notifications/Protocol.hs

Lines changed: 32 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@
1111

1212
module Simplex.Messaging.Notifications.Protocol where
1313

14-
import Control.Applicative ((<|>))
14+
import Control.Applicative (optional, (<|>))
1515
import Data.Aeson (FromJSON (..), ToJSON (..), (.:), (.=))
1616
import qualified Data.Aeson as J
1717
import qualified Data.Aeson.Encoding as JE
@@ -32,7 +32,7 @@ import Simplex.Messaging.Agent.Store.DB (FromField (..), ToField (..))
3232
import qualified Simplex.Messaging.Crypto as C
3333
import Simplex.Messaging.Encoding
3434
import Simplex.Messaging.Encoding.String
35-
import Simplex.Messaging.Notifications.Transport (NTFVersion, ntfClientHandshake)
35+
import Simplex.Messaging.Notifications.Transport (NTFVersion, invalidReasonNTFVersion, ntfClientHandshake)
3636
import Simplex.Messaging.Parsers (fromTextField_)
3737
import Simplex.Messaging.Protocol hiding (Command (..), CommandTag (..))
3838
import Simplex.Messaging.Util (eitherToMaybe, (<$?>))
@@ -296,12 +296,18 @@ data NtfResponse
296296

297297
instance ProtocolEncoding NTFVersion ErrorType NtfResponse where
298298
type Tag NtfResponse = NtfResponseTag
299-
encodeProtocol _v = \case
299+
encodeProtocol v = \case
300300
NRTknId entId dhKey -> e (NRTknId_, ' ', entId, dhKey)
301301
NRSubId entId -> e (NRSubId_, ' ', entId)
302302
NROk -> e NROk_
303303
NRErr err -> e (NRErr_, ' ', err)
304-
NRTkn stat -> e (NRTkn_, ' ', stat)
304+
NRTkn stat -> e (NRTkn_, ' ', stat')
305+
where
306+
stat'
307+
| v >= invalidReasonNTFVersion = stat
308+
| otherwise = case stat of
309+
NTInvalid _ -> NTInvalid Nothing
310+
_ -> stat
305311
NRSub stat -> e (NRSub_, ' ', stat)
306312
NRPong -> e NRPong_
307313
where
@@ -520,7 +526,7 @@ data NtfTknStatus
520526
| -- | state after registration (TNEW)
521527
NTRegistered
522528
| -- | if initial notification failed (push provider error) or verification failed
523-
NTInvalid
529+
NTInvalid (Maybe NTInvalidReason)
524530
| -- | Token confirmed via notification (accepted by push provider or verification code received by client)
525531
NTConfirmed
526532
| -- | after successful verification (TVFY)
@@ -533,20 +539,39 @@ instance Encoding NtfTknStatus where
533539
smpEncode = \case
534540
NTNew -> "NEW"
535541
NTRegistered -> "REGISTERED"
536-
NTInvalid -> "INVALID"
542+
NTInvalid r_ -> "INVALID" <> maybe "" (\r -> ',' `B.cons` strEncode r) r_
537543
NTConfirmed -> "CONFIRMED"
538544
NTActive -> "ACTIVE"
539545
NTExpired -> "EXPIRED"
540546
smpP =
541547
A.takeTill (== ' ') >>= \case
542548
"NEW" -> pure NTNew
543549
"REGISTERED" -> pure NTRegistered
544-
"INVALID" -> pure NTInvalid
550+
"INVALID" -> NTInvalid <$> optional (A.char ',' *> strP)
545551
"CONFIRMED" -> pure NTConfirmed
546552
"ACTIVE" -> pure NTActive
547553
"EXPIRED" -> pure NTExpired
548554
_ -> fail "bad NtfTknStatus"
549555

556+
instance StrEncoding NTInvalidReason where
557+
strEncode = smpEncode
558+
strP = smpP
559+
560+
data NTInvalidReason = NTIRBadToken | NTIRTokenNotForTopic | NTIRGone410
561+
deriving (Eq, Show)
562+
563+
instance Encoding NTInvalidReason where
564+
smpEncode = \case
565+
NTIRBadToken -> "BAD"
566+
NTIRTokenNotForTopic -> "TOPIC"
567+
NTIRGone410 -> "GONE"
568+
smpP =
569+
A.takeTill (== ' ') >>= \case
570+
"BAD" -> pure NTIRBadToken
571+
"TOPIC" -> pure NTIRTokenNotForTopic
572+
"GONE" -> pure NTIRGone410
573+
_ -> fail "bad NTInvalidReason"
574+
550575
instance StrEncoding NtfTknStatus where
551576
strEncode = smpEncode
552577
strP = smpP

src/Simplex/Messaging/Notifications/Server.hs

Lines changed: 46 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,7 @@ import Simplex.Messaging.Protocol (EntityId (..), ErrorType (..), ProtocolServer
5858
import qualified Simplex.Messaging.Protocol as SMP
5959
import Simplex.Messaging.Server
6060
import Simplex.Messaging.Server.Control (CPClientRole (..))
61+
import Simplex.Messaging.Server.QueueStore (RoundedSystemTime, getSystemDate)
6162
import Simplex.Messaging.Server.Stats (PeriodStats (..), PeriodStatCounts (..), periodStatCounts, updatePeriodStats)
6263
import Simplex.Messaging.TMap (TMap)
6364
import qualified Simplex.Messaging.TMap as TM
@@ -435,17 +436,19 @@ ntfPush s@NtfPushServer {pushQ} = forever $ do
435436
liftIO $ logDebug $ "sending push notification to " <> T.pack (show pp)
436437
status <- readTVarIO tknStatus
437438
case ntf of
438-
PNVerification _
439-
| status /= NTInvalid && status /= NTExpired ->
440-
deliverNotification pp tkn ntf >>= \case
441-
Right _ -> do
442-
status_ <- atomically $ stateTVar tknStatus $ \case
443-
NTActive -> (Nothing, NTActive)
444-
NTConfirmed -> (Nothing, NTConfirmed)
445-
_ -> (Just NTConfirmed, NTConfirmed)
446-
forM_ status_ $ \status' -> withNtfLog $ \sl -> logTokenStatus sl ntfTknId status'
447-
_ -> pure ()
448-
| otherwise -> logError "bad notification token status"
439+
PNVerification _ -> case status of
440+
NTInvalid _ -> logError $ "bad notification token status: " <> tshow status
441+
-- TODO nothing makes token "expired" on the server
442+
NTExpired -> logError $ "bad notification token status: " <> tshow status
443+
_ ->
444+
deliverNotification pp tkn ntf >>= \case
445+
Right _ -> do
446+
status_ <- atomically $ stateTVar tknStatus $ \case
447+
NTActive -> (Nothing, NTActive)
448+
NTConfirmed -> (Nothing, NTConfirmed)
449+
_ -> (Just NTConfirmed, NTConfirmed)
450+
forM_ status_ $ \status' -> withNtfLog $ \sl -> logTokenStatus sl ntfTknId status'
451+
_ -> pure ()
449452
PNCheckMessages -> checkActiveTkn status $ do
450453
void $ deliverNotification pp tkn ntf
451454
PNMessage {} -> checkActiveTkn status $ do
@@ -459,7 +462,7 @@ ntfPush s@NtfPushServer {pushQ} = forever $ do
459462
| status == NTActive = action
460463
| otherwise = liftIO $ logError "bad notification token status"
461464
deliverNotification :: PushProvider -> NtfTknData -> PushNotification -> M (Either PushProviderError ())
462-
deliverNotification pp tkn ntf = do
465+
deliverNotification pp tkn@NtfTknData {ntfTknId} ntf = do
463466
deliver <- liftIO $ getPushClient s pp
464467
liftIO (runExceptT $ deliver tkn ntf) >>= \case
465468
Right _ -> pure $ Right ()
@@ -468,14 +471,14 @@ ntfPush s@NtfPushServer {pushQ} = forever $ do
468471
PPRetryLater -> retryDeliver
469472
PPCryptoError _ -> err e
470473
PPResponseError _ _ -> err e
471-
PPTokenInvalid -> updateTknStatus tkn NTInvalid >> err e
474+
PPTokenInvalid r -> updateTknStatus tkn (NTInvalid $ Just r) >> err e
472475
PPPermanentError -> err e
473476
where
474477
retryDeliver :: M (Either PushProviderError ())
475478
retryDeliver = do
476479
deliver <- liftIO $ newPushClient s pp
477480
liftIO (runExceptT $ deliver tkn ntf) >>= either err (pure . Right)
478-
err e = logError (T.pack $ "Push provider error (" <> show pp <> "): " <> show e) $> Left e
481+
err e = logError ("Push provider error (" <> tshow pp <> ", " <> tshow ntfTknId <> "): " <> tshow e) $> Left e
479482

480483
updateTknStatus :: NtfTknData -> NtfTknStatus -> M ()
481484
updateTknStatus NtfTknData {ntfTknId, tknStatus} status = do
@@ -509,13 +512,17 @@ receive th@THandle {params = THandleParams {thAuth}} NtfServerClient {rcvQ, sndQ
509512
where
510513
cmdAction t@(_, _, (corrId, entId, cmdOrError)) =
511514
case cmdOrError of
512-
Left e -> pure $ Left (corrId, entId, NRErr e)
515+
Left e -> do
516+
logError $ "invalid client request: " <> tshow e
517+
pure $ Left (corrId, entId, NRErr e)
513518
Right cmd ->
514-
verified <$> verifyNtfTransmission ((,C.cbNonce (SMP.bs corrId)) <$> thAuth) t cmd
519+
verified =<< verifyNtfTransmission ((,C.cbNonce (SMP.bs corrId)) <$> thAuth) t cmd
515520
where
516521
verified = \case
517-
VRVerified req -> Right req
518-
VRFailed -> Left (corrId, entId, NRErr AUTH)
522+
VRVerified req -> pure $ Right req
523+
VRFailed -> do
524+
logError "unauthorized client request"
525+
pure $ Left (corrId, entId, NRErr AUTH)
519526
write q = mapM_ (atomically . writeTBQueue q) . L.nonEmpty
520527

521528
send :: Transport c => THandleNTF c 'TServer -> NtfServerClient -> IO ()
@@ -524,7 +531,7 @@ send h@THandle {params} NtfServerClient {sndQ, sndActiveAt} = forever $ do
524531
void . liftIO $ tPut h $ L.map (\t -> Right (Nothing, encodeTransmission params t)) ts
525532
atomically . (writeTVar sndActiveAt $!) =<< liftIO getSystemTime
526533

527-
data VerificationResult = VRVerified NtfRequest | VRFailed
534+
data VerificationResult = VRVerified (Maybe NtfTknData, NtfRequest) | VRFailed
528535

529536
verifyNtfTransmission :: Maybe (THandleAuth 'TServer, C.CbNonce) -> SignedTransmission ErrorType NtfCmd -> NtfCmd -> M VerificationResult
530537
verifyNtfTransmission auth_ (tAuth, authorized, (corrId, entId, _)) cmd = do
@@ -538,34 +545,34 @@ verifyNtfTransmission auth_ (tAuth, authorized, (corrId, entId, _)) cmd = do
538545
Just t@NtfTknData {tknVerifyKey}
539546
| k == tknVerifyKey -> verifiedTknCmd t c
540547
| otherwise -> VRFailed
541-
_ -> VRVerified (NtfReqNew corrId (ANE SToken tkn))
548+
Nothing -> VRVerified (Nothing, NtfReqNew corrId (ANE SToken tkn))
542549
else VRFailed
543550
NtfCmd SToken c -> do
544-
t_ <- atomically $ getNtfToken st entId
551+
t_ <- liftIO $ getNtfTokenIO st entId
545552
verifyToken t_ (`verifiedTknCmd` c)
546553
NtfCmd SSubscription c@(SNEW sub@(NewNtfSub tknId smpQueue _)) -> do
547554
s_ <- atomically $ findNtfSubscription st smpQueue
548555
case s_ of
549556
Nothing -> do
550557
t_ <- atomically $ getActiveNtfToken st tknId
551-
verifyToken' t_ $ VRVerified (NtfReqNew corrId (ANE SSubscription sub))
558+
verifyToken' t_ $ VRVerified (t_, NtfReqNew corrId (ANE SSubscription sub))
552559
Just s@NtfSubData {tokenId = subTknId} ->
553560
if subTknId == tknId
554561
then do
555562
t_ <- atomically $ getActiveNtfToken st subTknId
556-
verifyToken' t_ $ verifiedSubCmd s c
563+
verifyToken' t_ $ verifiedSubCmd t_ s c
557564
else pure $ maybe False (dummyVerifyCmd auth_ authorized) tAuth `seq` VRFailed
558-
NtfCmd SSubscription PING -> pure $ VRVerified $ NtfReqPing corrId entId
565+
NtfCmd SSubscription PING -> pure $ VRVerified (Nothing, NtfReqPing corrId entId)
559566
NtfCmd SSubscription c -> do
560-
s_ <- atomically $ getNtfSubscription st entId
567+
s_ <- liftIO $ getNtfSubscriptionIO st entId
561568
case s_ of
562569
Just s@NtfSubData {tokenId = subTknId} -> do
563570
t_ <- atomically $ getActiveNtfToken st subTknId
564-
verifyToken' t_ $ verifiedSubCmd s c
571+
verifyToken' t_ $ verifiedSubCmd t_ s c
565572
_ -> pure $ maybe False (dummyVerifyCmd auth_ authorized) tAuth `seq` VRFailed
566573
where
567-
verifiedTknCmd t c = VRVerified (NtfReqCmd SToken (NtfTkn t) (corrId, entId, c))
568-
verifiedSubCmd s c = VRVerified (NtfReqCmd SSubscription (NtfSub s) (corrId, entId, c))
574+
verifiedTknCmd t c = VRVerified (Just t, NtfReqCmd SToken (NtfTkn t) (corrId, entId, c))
575+
verifiedSubCmd t_ s c = VRVerified (t_, NtfReqCmd SSubscription (NtfSub s) (corrId, entId, c))
569576
verifyToken :: Maybe NtfTknData -> (NtfTknData -> VerificationResult) -> M VerificationResult
570577
verifyToken t_ positiveVerificationResult =
571578
pure $ case t_ of
@@ -579,11 +586,18 @@ verifyNtfTransmission auth_ (tAuth, authorized, (corrId, entId, _)) cmd = do
579586

580587
client :: NtfServerClient -> NtfSubscriber -> NtfPushServer -> M ()
581588
client NtfServerClient {rcvQ, sndQ} NtfSubscriber {newSubQ, smpAgent = ca} NtfPushServer {pushQ, intervalNotifiers} =
582-
forever $
589+
forever $ do
590+
ts <- liftIO getSystemDate
583591
atomically (readTBQueue rcvQ)
584-
>>= mapM processCommand
592+
>>= mapM (\(tkn_, req) -> updateTokenDate ts tkn_ >> processCommand req)
585593
>>= atomically . writeTBQueue sndQ
586594
where
595+
updateTokenDate :: RoundedSystemTime -> Maybe NtfTknData -> M ()
596+
updateTokenDate ts' = mapM_ $ \NtfTknData {ntfTknId, tknUpdatedAt} -> do
597+
let t' = Just ts'
598+
t <- atomically $ swapTVar tknUpdatedAt t'
599+
unless (t' == t) $ withNtfLog $ \s -> logUpdateTokenTime s ntfTknId ts'
600+
587601
processCommand :: NtfRequest -> M (Transmission NtfResponse)
588602
processCommand = \case
589603
NtfReqNew corrId (ANE SToken newTkn@(NewNtfTkn token _ dhPubKey)) -> do
@@ -593,7 +607,8 @@ client NtfServerClient {rcvQ, sndQ} NtfSubscriber {newSubQ, smpAgent = ca} NtfPu
593607
let dhSecret = C.dh' dhPubKey srvDhPrivKey
594608
tknId <- getId
595609
regCode <- getRegCode
596-
tkn <- atomically $ mkNtfTknData tknId newTkn ks dhSecret regCode
610+
ts <- liftIO $ getSystemDate
611+
tkn <- liftIO $ mkNtfTknData tknId newTkn ks dhSecret regCode ts
597612
atomically $ addNtfToken st tknId tkn
598613
atomically $ writeTBQueue pushQ (tkn, PNVerification regCode)
599614
withNtfLog (`logCreateToken` tkn)

src/Simplex/Messaging/Notifications/Server/Env.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -159,7 +159,7 @@ data NtfRequest
159159
| NtfReqPing CorrId NtfEntityId
160160

161161
data NtfServerClient = NtfServerClient
162-
{ rcvQ :: TBQueue (NonEmpty NtfRequest),
162+
{ rcvQ :: TBQueue (NonEmpty (Maybe NtfTknData, NtfRequest)),
163163
sndQ :: TBQueue (NonEmpty (Transmission NtfResponse)),
164164
ntfThParams :: THandleParams NTFVersion 'TServer,
165165
connected :: TVar Bool,

src/Simplex/Messaging/Notifications/Server/Push/APNS.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -308,7 +308,7 @@ data PushProviderError
308308
= PPConnection HTTP2ClientError
309309
| PPCryptoError C.CryptoError
310310
| PPResponseError (Maybe Status) Text
311-
| PPTokenInvalid
311+
| PPTokenInvalid NTInvalidReason
312312
| PPRetryLater
313313
| PPPermanentError
314314
deriving (Show, Exception)
@@ -338,15 +338,15 @@ apnsPushProviderClient c@APNSPushClient {nonceDrg, apnsCfg} tkn@NtfTknData {toke
338338
| status == Just N.ok200 = pure ()
339339
| status == Just N.badRequest400 =
340340
case reason' of
341-
"BadDeviceToken" -> throwE PPTokenInvalid
342-
"DeviceTokenNotForTopic" -> throwE PPTokenInvalid
341+
"BadDeviceToken" -> throwE $ PPTokenInvalid NTIRBadToken
342+
"DeviceTokenNotForTopic" -> throwE $ PPTokenInvalid NTIRTokenNotForTopic
343343
"TopicDisallowed" -> throwE PPPermanentError
344344
_ -> err status reason'
345345
| status == Just N.forbidden403 = case reason' of
346346
"ExpiredProviderToken" -> throwE PPPermanentError -- there should be no point retrying it as the token was refreshed
347347
"InvalidProviderToken" -> throwE PPPermanentError
348348
_ -> err status reason'
349-
| status == Just N.gone410 = throwE PPTokenInvalid
349+
| status == Just N.gone410 = throwE $ PPTokenInvalid NTIRGone410
350350
| status == Just N.serviceUnavailable503 = liftIO (disconnectApnsHTTP2Client c) >> throwE PPRetryLater
351351
-- Just tooManyRequests429 -> TooManyRequests - too many requests for the same token
352352
| otherwise = err status reason'

src/Simplex/Messaging/Notifications/Server/Store.hs

Lines changed: 11 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@ import qualified Simplex.Messaging.Crypto as C
2525
import Simplex.Messaging.Encoding.String
2626
import Simplex.Messaging.Notifications.Protocol
2727
import Simplex.Messaging.Protocol (NtfPrivateAuthKey, NtfPublicAuthKey, SMPServer)
28+
import Simplex.Messaging.Server.QueueStore (RoundedSystemTime)
2829
import Simplex.Messaging.TMap (TMap)
2930
import qualified Simplex.Messaging.TMap as TM
3031
import Simplex.Messaging.Util (whenM, ($>>=))
@@ -57,14 +58,16 @@ data NtfTknData = NtfTknData
5758
tknDhKeys :: C.KeyPair 'C.X25519,
5859
tknDhSecret :: C.DhSecretX25519,
5960
tknRegCode :: NtfRegCode,
60-
tknCronInterval :: TVar Word16
61+
tknCronInterval :: TVar Word16,
62+
tknUpdatedAt :: TVar (Maybe RoundedSystemTime)
6163
}
6264

63-
mkNtfTknData :: NtfTokenId -> NewNtfEntity 'Token -> C.KeyPair 'C.X25519 -> C.DhSecretX25519 -> NtfRegCode -> STM NtfTknData
64-
mkNtfTknData ntfTknId (NewNtfTkn token tknVerifyKey _) tknDhKeys tknDhSecret tknRegCode = do
65-
tknStatus <- newTVar NTRegistered
66-
tknCronInterval <- newTVar 0
67-
pure NtfTknData {ntfTknId, token, tknStatus, tknVerifyKey, tknDhKeys, tknDhSecret, tknRegCode, tknCronInterval}
65+
mkNtfTknData :: NtfTokenId -> NewNtfEntity 'Token -> C.KeyPair 'C.X25519 -> C.DhSecretX25519 -> NtfRegCode -> RoundedSystemTime -> IO NtfTknData
66+
mkNtfTknData ntfTknId (NewNtfTkn token tknVerifyKey _) tknDhKeys tknDhSecret tknRegCode ts = do
67+
tknStatus <- newTVarIO NTRegistered
68+
tknCronInterval <- newTVarIO 0
69+
tknUpdatedAt <- newTVarIO $ Just ts
70+
pure NtfTknData {ntfTknId, token, tknStatus, tknVerifyKey, tknDhKeys, tknDhSecret, tknRegCode, tknCronInterval, tknUpdatedAt}
6871

6972
data NtfSubData = NtfSubData
7073
{ ntfSubId :: NtfSubscriptionId,
@@ -156,9 +159,8 @@ deleteTokenSubs st tknId = do
156159
$>>= \NtfSubData {smpQueue} ->
157160
TM.delete smpQueue (subscriptionLookup st) $> Just smpQueue
158161

159-
getNtfSubscription :: NtfStore -> NtfSubscriptionId -> STM (Maybe NtfSubData)
160-
getNtfSubscription st subId =
161-
TM.lookup subId (subscriptions st)
162+
getNtfSubscriptionIO :: NtfStore -> NtfSubscriptionId -> IO (Maybe NtfSubData)
163+
getNtfSubscriptionIO st subId = TM.lookupIO subId (subscriptions st)
162164

163165
findNtfSubscription :: NtfStore -> SMPQueueNtf -> STM (Maybe NtfSubData)
164166
findNtfSubscription st smpQueue = do

0 commit comments

Comments
 (0)