@@ -111,9 +111,6 @@ module Simplex.Messaging.Agent
111111 execAgentStoreSQL ,
112112 getAgentMigrations ,
113113 debugAgentLocks ,
114- getAgentStats ,
115- resetAgentStats ,
116- getMsgCounts ,
117114 getAgentSubscriptions ,
118115 logConnection ,
119116 )
@@ -126,7 +123,7 @@ import Control.Monad.Reader
126123import Control.Monad.Trans.Except
127124import Crypto.Random (ChaChaDRG )
128125import qualified Data.Aeson as J
129- import Data.Bifunctor (bimap , first , second )
126+ import Data.Bifunctor (bimap , first )
130127import Data.ByteString.Char8 (ByteString )
131128import qualified Data.ByteString.Char8 as B
132129import Data.Composition ((.:) , (.:.) , (.::) , (.::.) )
@@ -591,16 +588,6 @@ resetAgentServersStats :: AgentClient -> AE ()
591588resetAgentServersStats c = withAgentEnv c $ resetAgentServersStats' c
592589{-# INLINE resetAgentServersStats #-}
593590
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-
604591withAgentEnv' :: AgentClient -> AM' a -> IO a
605592withAgentEnv' c = (`runReaderT` agentEnv c)
606593{-# INLINE withAgentEnv' #-}
@@ -2270,7 +2257,6 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(_, srv, _), _v, sessId, ts)
22702257 _ -> pure ()
22712258 let encryptedMsgHash = C. sha256Hash encAgentMessage
22722259 g <- asks random
2273- atomically updateTotalMsgCount
22742260 tryAgentError (agentClientMsg g encryptedMsgHash) >>= \ case
22752261 Right (Just (msgId, msgMeta, aMessage, rcPrev)) -> do
22762262 conn'' <- resetRatchetSync
@@ -2304,7 +2290,6 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(_, srv, _), _v, sessId, ts)
23042290 | otherwise = pure conn'
23052291 Right Nothing -> prohibited " msg: bad agent msg" >> ack
23062292 Left e@ (AGENT A_DUPLICATE ) -> do
2307- atomically updateDupMsgCount
23082293 atomically $ incSMPServerStat c userId srv recvDuplicates
23092294 withStore' c (\ db -> getLastMsg db connId srvMsgId) >>= \ case
23102295 Just RcvMsg {internalId, msgMeta, msgBody = agentMsgBody, userAck}
@@ -2339,20 +2324,6 @@ processSMPTransmissions c@AgentClient {subQ} (tSess@(_, srv, _), _v, sessId, ts)
23392324 checkDuplicateHash e encryptedMsgHash =
23402325 unlessM (withStore' c $ \ db -> checkRcvMsgHashExists db connId encryptedMsgHash) $
23412326 throwE e
2342- updateTotalMsgCount :: STM ()
2343- updateTotalMsgCount =
2344- TM. lookup connId (msgCounts c) >>= \ case
2345- Just v -> modifyTVar' v $ first (+ 1 )
2346- Nothing -> addMsgCount 0
2347- updateDupMsgCount :: STM ()
2348- updateDupMsgCount =
2349- TM. lookup connId (msgCounts c) >>= \ case
2350- Just v -> modifyTVar' v $ second (+ 1 )
2351- Nothing -> addMsgCount 1
2352- addMsgCount :: Int -> STM ()
2353- addMsgCount duplicate = do
2354- counts <- newTVar (1 , duplicate)
2355- TM. insert connId counts (msgCounts c)
23562327 agentClientMsg :: TVar ChaChaDRG -> ByteString -> AM (Maybe (InternalId , MsgMeta , AMessage , CR. RatchetX448 ))
23572328 agentClientMsg g encryptedMsgHash = withStore c $ \ db -> runExceptT $ do
23582329 rc <- ExceptT $ getRatchet db connId -- ratchet state pre-decryption - required for processing EREADY
0 commit comments