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

View File

@ -26,6 +26,7 @@ import UnliftIO.Async
import UnliftIO qualified as UIO
import UnliftIO (TVar,TQueue,atomically)
import System.Random (randomIO)
import Data.Hashable
import Data.Word
import Data.HashMap.Strict (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)
makeRequestR input = do
t <- getTimeCoarse <&> round @_ @Word64 . realToFrac
rnum <- atomically do
n <- readTVar rnumnum
modifyTVar rnumnum succ
pure n
modifyTVar' rnumnum succ
pure (fromIntegral $ hash (n+t))
pure $ ServiceRequest rnum (serialise (fromIntegral idx :: Int, serialise input))
where

View File

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