mirror of https://github.com/voidlizard/hbs2
wip
This commit is contained in:
parent
1f1b96f3b4
commit
82f97e148c
|
@ -1121,8 +1121,9 @@ theDict = do
|
||||||
che <- ContT withGitCat
|
che <- ContT withGitCat
|
||||||
pure $ gitReadObjectMaybe che
|
pure $ gitReadObjectMaybe che
|
||||||
|
|
||||||
out <- newTQueueIO
|
|
||||||
r <- ContT $ withAsync $ forConcurrently_ (HPSQ.toList r) $ \(commit,_,_) -> do
|
new_ <- newTVarIO mempty
|
||||||
|
lift $ forConcurrently_ (HPSQ.toList r) $ \(commit,_,_) -> do
|
||||||
|
|
||||||
(_,self) <- gitCatBatchQ commit
|
(_,self) <- gitCatBatchQ commit
|
||||||
>>= orThrow (GitReadError (show $ pretty commit))
|
>>= orThrow (GitReadError (show $ pretty commit))
|
||||||
|
@ -1131,19 +1132,35 @@ theDict = do
|
||||||
|
|
||||||
hashes <- gitReadTreeObjectsOnly commit
|
hashes <- gitReadTreeObjectsOnly commit
|
||||||
<&> ([commit,tree]<>)
|
<&> ([commit,tree]<>)
|
||||||
>>= filterM req
|
-- >>= filterM req
|
||||||
|
|
||||||
atomically $ mapM_ (writeTQueue out) hashes
|
atomically $ modifyTVar new_ (HS.union (HS.fromList hashes))
|
||||||
|
|
||||||
fix \next -> do
|
|
||||||
h' <- atomically do
|
|
||||||
pollSTM r >>= \case
|
|
||||||
Just{} -> pure Nothing
|
|
||||||
Nothing -> readTQueue out <&> Just
|
|
||||||
|
|
||||||
maybe1 h' none $ \h ->do
|
fps <- lift $ listObjectIndexFiles
|
||||||
liftIO $ print $ pretty h
|
<&> fmap fst
|
||||||
next
|
>>= liftIO . mapM (`mmapFileByteString` Nothing)
|
||||||
|
|
||||||
|
allHashes <- readTVarIO new_
|
||||||
|
newHashes <- newTVarIO mempty
|
||||||
|
for_ fps $ \mmaped -> do
|
||||||
|
for_ allHashes $ \ha -> do
|
||||||
|
found <- binarySearchBS 56 ( BS.take 20 . BS.drop 4) (coerce ha) mmaped
|
||||||
|
when (isNothing found) do
|
||||||
|
atomically $ modifyTVar newHashes (HS.insert ha)
|
||||||
|
|
||||||
|
readTVarIO newHashes >>= liftIO . print . pretty . HS.size
|
||||||
|
-- liftIO $ print $ pretty (HS
|
||||||
|
|
||||||
|
-- fix \next -> do
|
||||||
|
-- h' <- atomically do
|
||||||
|
-- pollSTM r >>= \case
|
||||||
|
-- Just{} -> pure Nothing
|
||||||
|
-- Nothing -> readTQueue out <&> Just
|
||||||
|
|
||||||
|
-- maybe1 h' none $ \h ->do
|
||||||
|
-- liftIO $ print $ pretty h
|
||||||
|
-- next
|
||||||
|
|
||||||
entry $ bindMatch "test:git:export" $ nil_ $ \syn -> lift $ connectedDo do
|
entry $ bindMatch "test:git:export" $ nil_ $ \syn -> lift $ connectedDo do
|
||||||
let (opts, argz) = splitOpts [("--index",1),("--ref",1)] syn
|
let (opts, argz) = splitOpts [("--index",1),("--ref",1)] syn
|
||||||
|
|
|
@ -101,37 +101,37 @@ startReflogIndexQueryQueue rq = flip runContT pure do
|
||||||
|
|
||||||
mmaped <- liftIO $ for files (liftIO . flip mmapFileByteString Nothing)
|
mmaped <- liftIO $ for files (liftIO . flip mmapFileByteString Nothing)
|
||||||
|
|
||||||
r <- newTVarIO (mempty :: HashMap N.ByteString N.ByteString)
|
-- r <- newTVarIO (mempty :: HashMap N.ByteString N.ByteString)
|
||||||
|
|
||||||
-- FIXME: may-explode
|
-- -- FIXME: may-explode
|
||||||
for_ mmaped $ \bs -> do
|
-- liftIO $ forConcurrently_ mmaped $ \bs -> do
|
||||||
scanBS bs $ \segment -> do
|
-- scanBS bs $ \segment -> do
|
||||||
let ha = BS.take 20 segment & coerce
|
-- let ha = BS.take 20 segment & coerce
|
||||||
atomically $ modifyTVar r (HM.insert ha segment)
|
-- atomically $ modifyTVar r (HM.insert ha segment)
|
||||||
|
|
||||||
forever do
|
-- forever do
|
||||||
(s, f, answ) <- atomically $ readTQueue rq
|
|
||||||
found <- readTVarIO r <&> HM.lookup s
|
|
||||||
|
|
||||||
atomically do
|
|
||||||
case found of
|
|
||||||
Nothing -> writeTMVar answ Nothing
|
|
||||||
Just x -> writeTMVar answ (Just (f x))
|
|
||||||
|
|
||||||
-- forever $ liftIO do
|
|
||||||
-- (s, f, answ) <- atomically $ readTQueue rq
|
-- (s, f, answ) <- atomically $ readTQueue rq
|
||||||
|
-- found <- readTVarIO r <&> HM.lookup s
|
||||||
|
|
||||||
-- found <- forConcurrently mmaped $ \bs -> runMaybeT do
|
-- atomically do
|
||||||
-- -- FIXME: size-hardcodes
|
-- case found of
|
||||||
-- w <- binarySearchBS 56 ( BS.take 20 . BS.drop 4 ) s bs
|
-- Nothing -> writeTMVar answ Nothing
|
||||||
-- >>= toMPlus
|
-- Just x -> writeTMVar answ (Just (f x))
|
||||||
|
|
||||||
-- let v = BS.drop ( w * 56 ) bs
|
forever $ liftIO do
|
||||||
|
(s, f, answ) <- atomically $ readTQueue rq
|
||||||
|
|
||||||
-- pure $ f v
|
found <- forConcurrently mmaped $ \bs -> runMaybeT do
|
||||||
|
-- FIXME: size-hardcodes
|
||||||
|
w <- binarySearchBS 56 ( BS.take 20 . BS.drop 4 ) s bs
|
||||||
|
>>= toMPlus
|
||||||
|
|
||||||
-- let what = headMay (catMaybes found)
|
let v = BS.drop ( w * 56 ) bs
|
||||||
-- atomically $ writeTMVar answ what
|
|
||||||
|
pure $ f v
|
||||||
|
|
||||||
|
let what = headMay (catMaybes found)
|
||||||
|
atomically $ writeTMVar answ what
|
||||||
|
|
||||||
writeReflogIndex :: forall m . ( Git3Perks m
|
writeReflogIndex :: forall m . ( Git3Perks m
|
||||||
, MonadReader Git3Env m
|
, MonadReader Git3Env m
|
||||||
|
|
Loading…
Reference in New Issue