mirror of https://github.com/voidlizard/hbs2
wip, fix
This commit is contained in:
parent
6c3dc29041
commit
b57919aa85
|
@ -72,7 +72,7 @@ ncqFossilMergeStep me@NCQStorage3{..} = withSem ncqServiceSem $ flip runContT p
|
||||||
for_ [f1, f2] $ \fi -> do
|
for_ [f1, f2] $ \fi -> do
|
||||||
let fik = coerce fi
|
let fik = coerce fi
|
||||||
writeFiltered me (ncqGetFileName me fi) fd $ \_ _ k _ -> do
|
writeFiltered me (ncqGetFileName me fi) fd $ \_ _ k _ -> do
|
||||||
ncqLocate me k >>= \case
|
ncqLocate_ False me k >>= \case
|
||||||
Nothing -> pure True
|
Nothing -> pure True
|
||||||
Just (InMemory{}) -> pure False
|
Just (InMemory{}) -> pure False
|
||||||
Just (InFossil fk _ _) -> do
|
Just (InFossil fk _ _) -> do
|
||||||
|
|
|
@ -49,16 +49,21 @@ ncqLookupIndex hx (mmaped, nway) = do
|
||||||
{-# INLINE ncqLookupIndex #-}
|
{-# INLINE ncqLookupIndex #-}
|
||||||
|
|
||||||
|
|
||||||
ncqLocate :: MonadUnliftIO m => NCQStorage3 -> HashRef -> m (Maybe Location)
|
|
||||||
ncqLocate me@NCQStorage3{..} href = ncqOperation me (pure Nothing) do
|
ncqLocate_ :: MonadUnliftIO m => Bool -> NCQStorage3 -> HashRef -> m (Maybe Location)
|
||||||
|
ncqLocate_ f me@NCQStorage3{..} href = ncqOperation me (pure Nothing) do
|
||||||
answ <- newEmptyTMVarIO
|
answ <- newEmptyTMVarIO
|
||||||
|
|
||||||
atomically do
|
atomically do
|
||||||
-- modifyTVar ncqWrites succ
|
when f $ modifyTVar ncqWrites succ
|
||||||
writeTQueue ncqReadReq (href, answ)
|
writeTQueue ncqReadReq (href, answ)
|
||||||
|
|
||||||
atomically $ takeTMVar answ
|
atomically $ takeTMVar answ
|
||||||
|
|
||||||
|
ncqLocate :: MonadUnliftIO m => NCQStorage3 -> HashRef -> m (Maybe Location)
|
||||||
|
ncqLocate me href = ncqOperation me (pure Nothing) do
|
||||||
|
ncqLocate_ True me href
|
||||||
|
|
||||||
ncqIndexFile :: MonadUnliftIO m => NCQStorage3 -> DataFile FileKey -> m (Maybe FilePath)
|
ncqIndexFile :: MonadUnliftIO m => NCQStorage3 -> DataFile FileKey -> m (Maybe FilePath)
|
||||||
ncqIndexFile n fk = runMaybeT do
|
ncqIndexFile n fk = runMaybeT do
|
||||||
|
|
||||||
|
@ -154,7 +159,8 @@ ncqIndexCompactStep me@NCQStorage3{..} = withSem ncqServiceSem $ flip runContT p
|
||||||
|
|
||||||
ts <- liftIO (PFS.getFileStatus idx1Name) <&> PFS.modificationTimeHiRes
|
ts <- liftIO (PFS.getFileStatus idx1Name) <&> PFS.modificationTimeHiRes
|
||||||
|
|
||||||
result <- lift $ nwayWriteBatch ncqIndexAllocForMerge dir "merged-.cq$" e
|
-- result <- lift $ nwayWriteBatch ncqIndexAllocForMerge dir "merged-.cq$" e
|
||||||
|
result <- lift $ nwayWriteBatch ncqIndexAlloc dir "merged-.cq$" e
|
||||||
|
|
||||||
liftIO $ PFS.setFileTimesHiRes result ts ts
|
liftIO $ PFS.setFileTimesHiRes result ts ts
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue