wip, NCQ3 failed

This commit is contained in:
voidlizard 2025-08-21 15:28:23 +03:00
parent 2f28d65e59
commit 1a36018aa5
4 changed files with 37 additions and 28 deletions

View File

@ -31,7 +31,8 @@ import HBS2.Net.Proto.Notify
import HBS2.Peer.Proto.Mailbox import HBS2.Peer.Proto.Mailbox
import HBS2.OrDie import HBS2.OrDie
import HBS2.Storage.Simple import HBS2.Storage.Simple
import HBS2.Storage.NCQ3 -- import HBS2.Storage.NCQ3
import HBS2.Storage.NCQ
import HBS2.Storage.Operations.Missed import HBS2.Storage.Operations.Missed
import HBS2.Data.Detect import HBS2.Data.Detect
@ -785,9 +786,6 @@ runPeer opts = respawnOnError opts $ flip runContT pure do
let pref = fromMaybe xdg (view storage opts <|> storConf) let pref = fromMaybe xdg (view storage opts <|> storConf)
let ncqPath = coerce pref </> "ncq3"
debug $ "storage prefix:" <+> pretty ncqPath
liftIO $ print $ pretty "debug: " <+> pretty (show debugConf) liftIO $ print $ pretty "debug: " <+> pretty (show debugConf)
liftIO $ print $ pretty "trace: " <+> pretty (show traceConf) liftIO $ print $ pretty "trace: " <+> pretty (show traceConf)
@ -824,7 +822,13 @@ runPeer opts = respawnOnError opts $ flip runContT pure do
-- error "STOP" -- error "STOP"
s <- ContT $ ncqWithStorage ncqPath -- let ncqPath = coerce pref </> "ncq3"
let ncqPath = coerce pref </> "ncq"
debug $ "storage prefix:" <+> pretty ncqPath
-- s <- ContT $ ncqWithStorage ncqPath
s <- lift $ ncqStorageOpen ncqPath
-- simpleStorageInit @HbSync (Just pref) -- simpleStorageInit @HbSync (Just pref)
let blk = liftIO . hasBlock s let blk = liftIO . hasBlock s
@ -1364,17 +1368,17 @@ runPeer opts = respawnOnError opts $ flip runContT pure do
monkeys <- liftIO $ async $ runMonkeys rpcctx monkeys <- liftIO $ async $ runMonkeys rpcctx
void $ waitAnyCancel $ w : [ loop void $ waitAnyCancel $ w : [ loop
, m1 , m1
, rpcProto , rpcProto
-- , probesMenv -- , probesMenv
-- , ann -- , ann
, probesPenv , probesPenv
, proxyThread , proxyThread
, brainsThread , brainsThread
, messWatchDog , messWatchDog
, monkeys , monkeys
] ]
-- liftIO $ ncqStorageStop s -- liftIO $ ncqStorageStop s
pause @'Seconds 1 pause @'Seconds 1
@ -1395,7 +1399,7 @@ checkMigration prefix = flip runContT pure $ callCC \exit -> do
already <- Sy.doesDirectoryExist migration already <- Sy.doesDirectoryExist migration
when (L.null blocks && not already) do when (L.null blocks && not already) do
checkNCQ1 -- checkNCQ1
exit () exit ()
let reason = if already then let reason = if already then
@ -1413,14 +1417,14 @@ checkMigration prefix = flip runContT pure $ callCC \exit -> do
where where
checkNCQ1 = do -- checkNCQ1 = do
let ncq1Dir = prefix </> "ncq" -- let ncq1Dir = prefix </> "ncq"
ncq1Here <- Sy.doesDirectoryExist ncq1Dir -- ncq1Here <- Sy.doesDirectoryExist ncq1Dir
when ncq1Here do -- when ncq1Here do
notice $ yellow "found NCQv1 storage" -- notice $ yellow "found NCQv1 storage"
notice $ red "Run" <+> "hbs2-peer migrate" <+> pretty prefix -- notice $ red "Run" <+> "hbs2-peer migrate" <+> pretty prefix
<> line -- <> line
<> "to migrate the storage to a new version" -- <> "to migrate the storage to a new version"
notice $ "You may also: backup" <+> pretty ncq1Dir <+> "or move it or remove permanently" -- notice $ "You may also: backup" <+> pretty ncq1Dir <+> "or move it or remove permanently"
liftIO exitFailure -- liftIO exitFailure

View File

@ -67,6 +67,7 @@ ncqStorageOpen fp upd = do
ncqStateKey <- newTVarIO (FileKey maxBound) ncqStateKey <- newTVarIO (FileKey maxBound)
ncqStateUse <- newTVarIO mempty ncqStateUse <- newTVarIO mempty
ncqServiceSem <- atomically $ newTSem 1 ncqServiceSem <- atomically $ newTSem 1
ncqRunSem <- atomically $ newTSem 1
ncqFileLock <- newTVarIO Nothing ncqFileLock <- newTVarIO Nothing
ncqCurrentFossils <- newTVarIO mempty ncqCurrentFossils <- newTVarIO mempty

View File

@ -32,12 +32,15 @@ ncqStorageStop NCQStorage{..} = do
ncqStorageRun :: forall m . MonadUnliftIO m ncqStorageRun :: forall m . MonadUnliftIO m
=> NCQStorage => NCQStorage
-> m () -> m ()
ncqStorageRun ncq@NCQStorage{..} = flip runContT pure do ncqStorageRun ncq@NCQStorage{..} = withSem ncqRunSem $ flip runContT pure do
ContT $ bracket setAlive (const unsetAlive) ContT $ bracket setAlive (const unsetAlive)
ContT $ bracket none $ const $ liftIO do ContT $ bracket none $ const $ liftIO do
readTVarIO ncqFileLock >>= mapM_ FL.unlockFile readTVarIO ncqFileLock >>= mapM_ FL.unlockFile
ContT $ bracket none $ const $ liftIO do
debug "storage done"
closeQ <- liftIO newTQueueIO closeQ <- liftIO newTQueueIO
closer <- spawnActivity $ liftIO $ fix \loop -> do closer <- spawnActivity $ liftIO $ fix \loop -> do

View File

@ -116,6 +116,7 @@ data NCQStorage =
, ncqOnRunWriteIdle :: TVar (IO ()) , ncqOnRunWriteIdle :: TVar (IO ())
, ncqSyncNo :: TVar Int , ncqSyncNo :: TVar Int
, ncqServiceSem :: TSem , ncqServiceSem :: TSem
, ncqRunSem :: TSem
, ncqFileLock :: TVar (Maybe FileLock) , ncqFileLock :: TVar (Maybe FileLock)
} }