mirror of https://github.com/voidlizard/hbs2
parallel lookup attempt; does not work. ncqLocateMt
This commit is contained in:
parent
f6b756fd31
commit
8da69dc38e
|
@ -272,12 +272,15 @@ ncqEntrySize = \case
|
||||||
InFossil _ _ size -> fromIntegral size
|
InFossil _ _ size -> fromIntegral size
|
||||||
InMemory bs -> fromIntegral (BS.length bs)
|
InMemory bs -> fromIntegral (BS.length bs)
|
||||||
|
|
||||||
|
|
||||||
ncqLocate2 :: MonadUnliftIO m => NCQStorage2 -> HashRef -> m (Maybe Location)
|
ncqLocate2 :: MonadUnliftIO m => NCQStorage2 -> HashRef -> m (Maybe Location)
|
||||||
ncqLocate2 ncq@NCQStorage2{..} href = flip runContT pure $ callCC \exit -> do
|
ncqLocate2 ncq@NCQStorage2{..} href = flip runContT pure $ callCC \exit -> do
|
||||||
now <- getTimeCoarse
|
now <- getTimeCoarse
|
||||||
|
|
||||||
lift (ncqLookupEntry ncq href) >>= maybe none (exit . Just . InMemory . coerce)
|
lift (ncqLookupEntry ncq href) >>= maybe none (exit . Just . InMemory . coerce)
|
||||||
|
|
||||||
|
atomically $ modifyTVar' ncqWrites succ
|
||||||
|
|
||||||
tracked <- readTVarIO ncqTrackedFiles <&> HPSQ.toList
|
tracked <- readTVarIO ncqTrackedFiles <&> HPSQ.toList
|
||||||
|
|
||||||
for_ tracked $ \(fk, prio, mCached) -> case mCached of
|
for_ tracked $ \(fk, prio, mCached) -> case mCached of
|
||||||
|
@ -318,6 +321,7 @@ ncqLocate2 ncq@NCQStorage2{..} href = flip runContT pure $ callCC \exit -> do
|
||||||
pure
|
pure
|
||||||
( fromIntegral $ N.word64 (BS.take 8 entryBs)
|
( fromIntegral $ N.word64 (BS.take 8 entryBs)
|
||||||
, fromIntegral $ N.word32 (BS.take 4 (BS.drop 8 entryBs)) )
|
, fromIntegral $ N.word32 (BS.take 4 (BS.drop 8 entryBs)) )
|
||||||
|
{-# INLINE lookupEntry #-}
|
||||||
|
|
||||||
ncqAlterEntrySTM :: NCQStorage2 -> HashRef -> (Maybe NCQEntry -> Maybe NCQEntry) -> STM ()
|
ncqAlterEntrySTM :: NCQStorage2 -> HashRef -> (Maybe NCQEntry -> Maybe NCQEntry) -> STM ()
|
||||||
ncqAlterEntrySTM ncq h alterFn = do
|
ncqAlterEntrySTM ncq h alterFn = do
|
||||||
|
|
Loading…
Reference in New Issue