wip, rpc issue fix?

This commit is contained in:
voidlizard 2025-02-15 13:48:16 +03:00
parent 96ac593e71
commit dd310888a5
3 changed files with 22 additions and 18 deletions

View File

@ -158,19 +158,20 @@ getStat :: forall e w m . ( ForByPass e
) )
=> ByPass e w => ByPass e w
-> m ByPassStat -> m ByPassStat
getStat bus = liftIO $ getStat ByPass{..} = liftIO do
ByPassStat <$> readTVarIO (bypassed bus) atomically do
<*> readTVarIO (encrypted bus) ByPassStat <$> readTVar bypassed
<*> readTVarIO (decrypted bus) <*> readTVar encrypted
<*> readTVarIO (decryptFails bus) <*> readTVar decrypted
<*> readTVarIO (sentNum bus) <*> readTVar decryptFails
<*> readTVarIO (recvNum bus) <*> readTVar sentNum
<*> readTVarIO (sentBytes bus) <*> readTVar recvNum
<*> readTVarIO (recvBytes bus) <*> readTVar sentBytes
<*> (readTVarIO (flowKeys bus) <&> HashMap.size) <*> readTVar recvBytes
<*> (readTVarIO (noncesByPeer bus) <&> HashMap.size) <*> (readTVar flowKeys <&> HashMap.size)
<*> readTVarIO (authFail bus) <*> (readTVar noncesByPeer <&> HashMap.size)
<*> readTVarIO (maxPkt bus) <*> readTVar authFail
<*> readTVar maxPkt
cleanupByPassMessaging :: forall e w m . ( ForByPass e cleanupByPassMessaging :: forall e w m . ( ForByPass e
, MonadIO m , MonadIO m

View File

@ -26,6 +26,7 @@ import UnliftIO.Async
import UnliftIO qualified as UIO import UnliftIO qualified as UIO
import UnliftIO (TVar,TQueue,atomically) import UnliftIO (TVar,TQueue,atomically)
import System.Random (randomIO) import System.Random (randomIO)
import Data.Hashable
import Data.Word import Data.Word
import Data.HashMap.Strict (HashMap) import Data.HashMap.Strict (HashMap)
import Data.HashMap.Strict qualified as HashMap import Data.HashMap.Strict qualified as HashMap
@ -130,10 +131,13 @@ makeRequestR :: forall api method e m . ( KnownNat (FromJust (FindMethodIndex 0
) )
=> Input method -> m (ServiceProto api e) => Input method -> m (ServiceProto api e)
makeRequestR input = do makeRequestR input = do
t <- getTimeCoarse <&> round @_ @Word64 . realToFrac
rnum <- atomically do rnum <- atomically do
n <- readTVar rnumnum n <- readTVar rnumnum
modifyTVar rnumnum succ modifyTVar' rnumnum succ
pure n pure (fromIntegral $ hash (n+t))
pure $ ServiceRequest rnum (serialise (fromIntegral idx :: Int, serialise input)) pure $ ServiceRequest rnum (serialise (fromIntegral idx :: Int, serialise input))
where where

View File

@ -604,8 +604,7 @@ runCLI = do
pByPassShow = do pByPassShow = do
rpc <- pRpcCommon rpc <- pRpcCommon
pure $ withMyRPC @PeerAPI rpc $ \caller -> do pure $ withMyRPC @PeerAPI rpc $ \caller -> do
void $ runMaybeT do d <- callRpcWaitRetry @RpcByPassInfo (TimeoutSec 1) 10 caller ()
d <- toMPlus =<< callService @RpcByPassInfo caller ()
liftIO $ print $ pretty d liftIO $ print $ pretty d
pRunGC = do pRunGC = do