@@ -111,9 +111,6 @@ module Simplex.Messaging.Agent
111
111
execAgentStoreSQL ,
112
112
getAgentMigrations ,
113
113
debugAgentLocks ,
114
- getAgentStats ,
115
- resetAgentStats ,
116
- getMsgCounts ,
117
114
getAgentSubscriptions ,
118
115
logConnection ,
119
116
)
@@ -126,7 +123,7 @@ import Control.Monad.Reader
126
123
import Control.Monad.Trans.Except
127
124
import Crypto.Random (ChaChaDRG )
128
125
import qualified Data.Aeson as J
129
- import Data.Bifunctor (bimap , first , second )
126
+ import Data.Bifunctor (bimap , first )
130
127
import Data.ByteString.Char8 (ByteString )
131
128
import qualified Data.ByteString.Char8 as B
132
129
import Data.Composition ((.:) , (.:.) , (.::) , (.::.) )
@@ -591,16 +588,6 @@ resetAgentServersStats :: AgentClient -> AE ()
591
588
resetAgentServersStats c = withAgentEnv c $ resetAgentServersStats' c
592
589
{-# INLINE resetAgentServersStats #-}
593
590
594
- getAgentStats :: AgentClient -> IO [(AgentStatsKey , Int )]
595
- getAgentStats c = readTVarIO (agentStats c) >>= mapM (\ (k, cnt) -> (k,) <$> readTVarIO cnt) . M. assocs
596
-
597
- resetAgentStats :: AgentClient -> IO ()
598
- resetAgentStats = atomically . TM. clear . agentStats
599
- {-# INLINE resetAgentStats #-}
600
-
601
- getMsgCounts :: AgentClient -> IO [(ConnId , (Int , Int ))] -- (total, duplicates)
602
- getMsgCounts c = readTVarIO (msgCounts c) >>= mapM (\ (connId, cnt) -> (connId,) <$> readTVarIO cnt) . M. assocs
603
-
604
591
withAgentEnv' :: AgentClient -> AM' a -> IO a
605
592
withAgentEnv' c = (`runReaderT` agentEnv c)
606
593
{-# INLINE withAgentEnv' #-}
@@ -2246,7 +2233,6 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(_, srv, _), _v, sessId, ts)
2246
2233
_ -> pure ()
2247
2234
let encryptedMsgHash = C. sha256Hash encAgentMessage
2248
2235
g <- asks random
2249
- atomically updateTotalMsgCount
2250
2236
tryAgentError (agentClientMsg g encryptedMsgHash) >>= \ case
2251
2237
Right (Just (msgId, msgMeta, aMessage, rcPrev)) -> do
2252
2238
conn'' <- resetRatchetSync
@@ -2280,7 +2266,6 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(_, srv, _), _v, sessId, ts)
2280
2266
| otherwise = pure conn'
2281
2267
Right Nothing -> prohibited " msg: bad agent msg" >> ack
2282
2268
Left e@ (AGENT A_DUPLICATE ) -> do
2283
- atomically updateDupMsgCount
2284
2269
atomically $ incSMPServerStat c userId srv recvDuplicates
2285
2270
withStore' c (\ db -> getLastMsg db connId srvMsgId) >>= \ case
2286
2271
Just RcvMsg {internalId, msgMeta, msgBody = agentMsgBody, userAck}
@@ -2315,20 +2300,6 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(_, srv, _), _v, sessId, ts)
2315
2300
checkDuplicateHash e encryptedMsgHash =
2316
2301
unlessM (withStore' c $ \ db -> checkRcvMsgHashExists db connId encryptedMsgHash) $
2317
2302
throwE e
2318
- updateTotalMsgCount :: STM ()
2319
- updateTotalMsgCount =
2320
- TM. lookup connId (msgCounts c) >>= \ case
2321
- Just v -> modifyTVar' v $ first (+ 1 )
2322
- Nothing -> addMsgCount 0
2323
- updateDupMsgCount :: STM ()
2324
- updateDupMsgCount =
2325
- TM. lookup connId (msgCounts c) >>= \ case
2326
- Just v -> modifyTVar' v $ second (+ 1 )
2327
- Nothing -> addMsgCount 1
2328
- addMsgCount :: Int -> STM ()
2329
- addMsgCount duplicate = do
2330
- counts <- newTVar (1 , duplicate)
2331
- TM. insert connId counts (msgCounts c)
2332
2303
agentClientMsg :: TVar ChaChaDRG -> ByteString -> AM (Maybe (InternalId , MsgMeta , AMessage , CR. RatchetX448 ))
2333
2304
agentClientMsg g encryptedMsgHash = withStore c $ \ db -> runExceptT $ do
2334
2305
rc <- ExceptT $ getRatchet db connId -- ratchet state pre-decryption - required for processing EREADY
0 commit comments