wip, file lock introduced

This commit is contained in:
voidlizard 2025-05-19 07:10:08 +03:00
parent 3ef135a25c
commit 5f08753132
3 changed files with 49 additions and 0 deletions

View File

@ -92,6 +92,7 @@ library
, unordered-containers , unordered-containers
, vector , vector
, zstd , zstd
, filelock
hs-source-dirs: lib hs-source-dirs: lib

View File

@ -86,6 +86,8 @@ import UnliftIO
import UnliftIO.Concurrent(getNumCapabilities) import UnliftIO.Concurrent(getNumCapabilities)
import UnliftIO.IO.File import UnliftIO.IO.File
import System.FileLock as FL
{- HLINT ignore "Functor law" -} {- HLINT ignore "Functor law" -}
type NCQPerks m = MonadIO m type NCQPerks m = MonadIO m
@ -98,6 +100,7 @@ data NCQStorageException =
| NCQStorageCantOpenCurrent | NCQStorageCantOpenCurrent
| NCQStorageBrokenCurrent | NCQStorageBrokenCurrent
| NCQMergeInvariantFailed String | NCQMergeInvariantFailed String
| NCQStorageCantLock FilePath
deriving stock (Show,Typeable) deriving stock (Show,Typeable)
instance Exception NCQStorageException instance Exception NCQStorageException
@ -158,6 +161,7 @@ data NCQStorage =
, ncqCurrentFd :: TVar (Maybe (RFd,WFd)) , ncqCurrentFd :: TVar (Maybe (RFd,WFd))
, ncqCurrentUsage :: TVar (IntMap Int) , ncqCurrentUsage :: TVar (IntMap Int)
, ncqCurrentReadReq :: TVar (Seq (Fd, Word64, Word64, TMVar ByteString)) , ncqCurrentReadReq :: TVar (Seq (Fd, Word64, Word64, TMVar ByteString))
, ncqLock :: TVar FL.FileLock
, ncqFsyncNum :: TVar Int , ncqFsyncNum :: TVar Int
, ncqFlushNow :: TVar [TQueue ()] , ncqFlushNow :: TVar [TQueue ()]
, ncqMergeReq :: TVar Int , ncqMergeReq :: TVar Int
@ -978,7 +982,9 @@ ncqStorageOpen :: MonadUnliftIO m => FilePath -> m NCQStorage
ncqStorageOpen fp' = do ncqStorageOpen fp' = do
flip fix 0 $ \next i -> do flip fix 0 $ \next i -> do
fp <- liftIO $ makeAbsolute fp' fp <- liftIO $ makeAbsolute fp'
ncq@NCQStorage{..} <- ncqStorageInit_ False fp ncq@NCQStorage{..} <- ncqStorageInit_ False fp
ncqReadTrackedFiles ncq ncqReadTrackedFiles ncq
ncqFixIndexes ncq ncqFixIndexes ncq
ncqLoadIndexes ncq ncqLoadIndexes ncq
@ -1058,6 +1064,8 @@ ncqStorageInit_ check path = do
let ncqGen = 0 let ncqGen = 0
let lockName = dropFileName (ncqGetCurrentName_ path ncqGen) </> ".lock"
here <- doesPathExist path here <- doesPathExist path
when (here && check) $ throwIO (NCQStorageAlreadyExist path) when (here && check) $ throwIO (NCQStorageAlreadyExist path)
@ -1066,6 +1074,12 @@ ncqStorageInit_ check path = do
let seedPath = path </> ".seed" let seedPath = path </> ".seed"
ncqLock_ <- liftIO do
mkdir (takeDirectory lockName)
l <- tryLockFile lockName Exclusive >>= orThrow (NCQStorageCantLock lockName)
touch lockName
pure l
unless here do unless here do
now <- liftIO $ getPOSIXTime <&> round @_ @Int now <- liftIO $ getPOSIXTime <&> round @_ @Int
@ -1115,6 +1129,7 @@ ncqStorageInit_ check path = do
ncqIndexed <- newTVarIO mempty ncqIndexed <- newTVarIO mempty
ncqMergeReq <- newTVarIO 0 ncqMergeReq <- newTVarIO 0
ncqFsyncNum <- newTVarIO 0 ncqFsyncNum <- newTVarIO 0
ncqLock <- newTVarIO ncqLock_
let currentName = ncqGetCurrentName_ path ncqGen let currentName = ncqGetCurrentName_ path ncqGen
@ -1152,6 +1167,7 @@ ncqStorageInit_ check path = do
debug $ "currentFileName" <+> pretty (ncqGetCurrentName_ path ncqGen) debug $ "currentFileName" <+> pretty (ncqGetCurrentName_ path ncqGen)
let ncq = NCQStorage{..} let ncq = NCQStorage{..}
ncqOpenCurrent ncq ncqOpenCurrent ncq
pure ncq pure ncq
@ -1175,6 +1191,8 @@ ncqFinalize NCQStorage{..} = do
_ -> none _ -> none
liftIO $ unlockFile =<< readTVarIO ncqLock
withNCQ :: forall m a . MonadUnliftIO m withNCQ :: forall m a . MonadUnliftIO m
=> (NCQStorage -> NCQStorage) => (NCQStorage -> NCQStorage)
-> FilePath -> FilePath

View File

@ -38,6 +38,7 @@ import Data.Text.Encoding qualified as TE
import Data.ByteString.Char8 qualified as BS8 import Data.ByteString.Char8 qualified as BS8
import Data.ByteString.Builder import Data.ByteString.Builder
import Data.Maybe import Data.Maybe
import Data.Either
import Data.Word import Data.Word
import Data.List qualified as List import Data.List qualified as List
import Data.Vector qualified as V import Data.Vector qualified as V
@ -417,6 +418,35 @@ main = do
e -> throwIO $ BadFormException @C (mkList e) e -> throwIO $ BadFormException @C (mkList e)
entry $ bindMatch "test:ncq:test-lock" $ nil_ $ \case
[ ] -> do
runTest $ \TestEnv{..} -> do
debug $ "test:ncq:test-lock" <+> pretty testEnvDir
let ncq1 = testEnvDir </> "ncq1"
flip runContT pure do
pause @'Seconds 2
r1 <- ContT $ withAsync do
withNCQ id ncq1 $ \_ -> do
forever $ pause @'Seconds 1
-- link r1
sto2 <- ContT $ withNCQ id ncq1
result <- poll r1
notice $ viaShow result
case result of
Just Left{} -> none
_ -> liftIO $ assertBool "must be (Left _)" False
e -> throwIO $ BadFormException @C (mkList e)
hidden do hidden do
internalEntries internalEntries
entry $ bindMatch "#!" $ nil_ $ const none entry $ bindMatch "#!" $ nil_ $ const none