make commitMigration interuption safe
Fixed inversion of control issue, so the tree is recorded in streamLogFile finalizer. Sponsored-by: Leon Schuermann on Patreon
This commit is contained in:
parent
0bd8b17b59
commit
d06aee7ce0
3 changed files with 60 additions and 49 deletions
47
Git/Tree.hs
47
Git/Tree.hs
|
@ -23,7 +23,8 @@ module Git.Tree (
|
||||||
graftTree',
|
graftTree',
|
||||||
withMkTreeHandle,
|
withMkTreeHandle,
|
||||||
MkTreeHandle,
|
MkTreeHandle,
|
||||||
mkTree,
|
sendMkTree,
|
||||||
|
finishMkTree,
|
||||||
treeMode,
|
treeMode,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
@ -92,39 +93,37 @@ recordTree :: Tree -> Repo -> IO Sha
|
||||||
recordTree t repo = withMkTreeHandle repo $ \h -> recordTree' h t
|
recordTree t repo = withMkTreeHandle repo $ \h -> recordTree' h t
|
||||||
|
|
||||||
recordTree' :: MkTreeHandle -> Tree -> IO Sha
|
recordTree' :: MkTreeHandle -> Tree -> IO Sha
|
||||||
recordTree' h (Tree l) = mkTree' h =<< mapM (recordSubTree h) l
|
recordTree' h (Tree l) = mkTree h =<< mapM (recordSubTree h) l
|
||||||
|
|
||||||
{- Note that the returned RecordedSubTree does not have its [TreeContent]
|
{- Note that the returned RecordedSubTree does not have its [TreeContent]
|
||||||
- list populated. This is a memory optimisation, since the list is not
|
- list populated. This is a memory optimisation, since the list is not
|
||||||
- used. -}
|
- used. -}
|
||||||
recordSubTree :: MkTreeHandle -> TreeContent -> IO TreeContent
|
recordSubTree :: MkTreeHandle -> TreeContent -> IO TreeContent
|
||||||
recordSubTree h (NewSubTree d l) = do
|
recordSubTree h (NewSubTree d l) = do
|
||||||
sha <- mkTree' h =<< mapM (recordSubTree h) l
|
sha <- mkTree h =<< mapM (recordSubTree h) l
|
||||||
return (RecordedSubTree d sha [])
|
return (RecordedSubTree d sha [])
|
||||||
recordSubTree _ alreadyrecorded = return alreadyrecorded
|
recordSubTree _ alreadyrecorded = return alreadyrecorded
|
||||||
|
|
||||||
{- Note that this creates a single tree. It cannot create a recursive tree
|
sendMkTree :: MkTreeHandle -> FileMode -> ObjectType -> Sha -> TopFilePath -> IO ()
|
||||||
- with subtrees in a single call. -}
|
sendMkTree (MkTreeHandle cp) fm ot s f =
|
||||||
mkTree
|
CoProcess.send cp $ \h ->
|
||||||
:: (MonadIO m, MonadCatch m)
|
hPutStr h (mkTreeOutput fm ot s f)
|
||||||
=> MkTreeHandle
|
|
||||||
-> ((FileMode -> ObjectType -> Sha -> TopFilePath -> m ()) -> m ())
|
|
||||||
-> m Sha
|
|
||||||
mkTree (MkTreeHandle cp) a = CoProcess.query cp send receive
|
|
||||||
where
|
|
||||||
send h = do
|
|
||||||
a $ \fm ot s f -> liftIO $ hPutStr h (mkTreeOutput fm ot s f)
|
|
||||||
-- NUL to signal end of tree to --batch
|
|
||||||
liftIO $ hPutStr h "\NUL"
|
|
||||||
receive h = liftIO $ getSha "mktree" (S8.hGetLine h)
|
|
||||||
|
|
||||||
mkTree' :: MkTreeHandle -> [TreeContent] -> IO Sha
|
finishMkTree :: MkTreeHandle -> IO Sha
|
||||||
mkTree' h l = mkTree h $ \send ->
|
finishMkTree (MkTreeHandle cp) = do
|
||||||
|
CoProcess.send cp $ \h ->
|
||||||
|
-- NUL to signal end of tree to --batch
|
||||||
|
hPutStr h "\NUL"
|
||||||
|
getSha "mktree" (CoProcess.receive cp S8.hGetLine)
|
||||||
|
|
||||||
|
mkTree :: MkTreeHandle -> [TreeContent] -> IO Sha
|
||||||
|
mkTree h l = do
|
||||||
forM_ l $ \case
|
forM_ l $ \case
|
||||||
TreeBlob f fm s -> send fm BlobObject s f
|
TreeBlob f fm s -> sendMkTree h fm BlobObject s f
|
||||||
RecordedSubTree f s _ -> send treeMode TreeObject s f
|
RecordedSubTree f s _ -> sendMkTree h treeMode TreeObject s f
|
||||||
NewSubTree _ _ -> error "recordSubTree internal error; unexpected NewSubTree"
|
NewSubTree _ _ -> error "recordSubTree internal error; unexpected NewSubTree"
|
||||||
TreeCommit f fm s -> send fm CommitObject s f
|
TreeCommit f fm s -> sendMkTree h fm CommitObject s f
|
||||||
|
finishMkTree h
|
||||||
|
|
||||||
treeMode :: FileMode
|
treeMode :: FileMode
|
||||||
treeMode = 0o040000
|
treeMode = 0o040000
|
||||||
|
@ -233,7 +232,7 @@ adjustTree adjusttreeitem addtreeitems resolveaddconflict removefiles r repo =
|
||||||
(l, cleanup) <- liftIO $ lsTreeWithObjects LsTree.LsTreeRecursive r repo
|
(l, cleanup) <- liftIO $ lsTreeWithObjects LsTree.LsTreeRecursive r repo
|
||||||
(l', _, _) <- go h False [] 1 inTopTree l
|
(l', _, _) <- go h False [] 1 inTopTree l
|
||||||
l'' <- adjustlist h 0 inTopTree (const True) l'
|
l'' <- adjustlist h 0 inTopTree (const True) l'
|
||||||
sha <- liftIO $ mkTree' h l''
|
sha <- liftIO $ mkTree h l''
|
||||||
void $ liftIO cleanup
|
void $ liftIO cleanup
|
||||||
return sha
|
return sha
|
||||||
where
|
where
|
||||||
|
@ -344,7 +343,7 @@ graftTree' subtree graftloc basetree repo hdl = go basetree subdirs graftdirs
|
||||||
return $ RecordedSubTree tloc tsha'' []
|
return $ RecordedSubTree tloc tsha'' []
|
||||||
_ -> graftin (topmostgraphdir:restgraphdirs)
|
_ -> graftin (topmostgraphdir:restgraphdirs)
|
||||||
return (newshas ++ rest)
|
return (newshas ++ rest)
|
||||||
mkTree' hdl t'
|
mkTree hdl t'
|
||||||
go _ _ [] = return subtree
|
go _ _ [] = return subtree
|
||||||
go _ [] _ = return subtree
|
go _ [] _ = return subtree
|
||||||
|
|
||||||
|
|
|
@ -66,37 +66,36 @@ commitMigration = do
|
||||||
logf <- fromRawFilePath <$> fromRepo gitAnnexMigrateLog
|
logf <- fromRawFilePath <$> fromRepo gitAnnexMigrateLog
|
||||||
lckf <- fromRepo gitAnnexMigrateLock
|
lckf <- fromRepo gitAnnexMigrateLock
|
||||||
nv <- liftIO $ newTVarIO (0 :: Integer)
|
nv <- liftIO $ newTVarIO (0 :: Integer)
|
||||||
newtv <- liftIO newEmptyTMVarIO
|
|
||||||
g <- Annex.gitRepo
|
g <- Annex.gitRepo
|
||||||
oldt <- withMkTreeHandle g $ \oldh ->
|
withMkTreeHandle g $ \oldh ->
|
||||||
withMkTreeHandle g $ \newh ->
|
withMkTreeHandle g $ \newh ->
|
||||||
mkTree oldh $ \oldsend -> do
|
streamLogFile logf lckf
|
||||||
newt <- mkTree newh $ \newsend ->
|
(finalizer nv oldh newh g)
|
||||||
streamLogFile logf lckf noop $
|
(processor nv oldh newh)
|
||||||
processor nv oldsend newsend
|
|
||||||
liftIO $ atomically $ writeTMVar newtv newt
|
|
||||||
newt <- liftIO $ atomically $ takeTMVar newtv
|
|
||||||
n <- liftIO $ atomically $ readTVar nv
|
|
||||||
when (n > 0) $ do
|
|
||||||
treesha <- liftIO $ flip recordTree g $ Tree
|
|
||||||
[ RecordedSubTree (asTopFilePath "old") oldt []
|
|
||||||
, RecordedSubTree (asTopFilePath "new") newt []
|
|
||||||
]
|
|
||||||
Annex.Branch.rememberTreeish treesha
|
|
||||||
(asTopFilePath migrationTreeGraftPoint)
|
|
||||||
where
|
where
|
||||||
processor nv oldsend newsend s = case words s of
|
processor nv oldh newh s = case words s of
|
||||||
(old:new:[]) -> do
|
(old:new:[]) -> do
|
||||||
fn <- liftIO $ atomically $ do
|
fn <- liftIO $ atomically $ do
|
||||||
n <- readTVar nv
|
n <- readTVar nv
|
||||||
let !n' = succ n
|
let !n' = succ n
|
||||||
writeTVar nv n'
|
writeTVar nv n'
|
||||||
return (asTopFilePath (encodeBS (show n')))
|
return (asTopFilePath (encodeBS (show n')))
|
||||||
let rec f r = f
|
let rec h r = liftIO $ sendMkTree h
|
||||||
(fromTreeItemType TreeFile)
|
(fromTreeItemType TreeFile)
|
||||||
BlobObject
|
BlobObject
|
||||||
(Git.Ref (encodeBS r))
|
(Git.Ref (encodeBS r))
|
||||||
fn
|
fn
|
||||||
void $ rec oldsend old
|
rec oldh old
|
||||||
void $ rec newsend new
|
rec newh new
|
||||||
_ -> error "migrate.log parse error"
|
_ -> error "migrate.log parse error"
|
||||||
|
finalizer nv oldh newh g = do
|
||||||
|
oldt <- liftIO $ finishMkTree oldh
|
||||||
|
newt <- liftIO $ finishMkTree newh
|
||||||
|
n <- liftIO $ atomically $ readTVar nv
|
||||||
|
when (n > 0) $ do
|
||||||
|
treesha <- liftIO $ flip recordTree g $ Tree
|
||||||
|
[ RecordedSubTree (asTopFilePath "old") oldt []
|
||||||
|
, RecordedSubTree (asTopFilePath "new") newt []
|
||||||
|
]
|
||||||
|
Annex.Branch.rememberTreeish treesha
|
||||||
|
(asTopFilePath migrationTreeGraftPoint)
|
||||||
|
|
|
@ -1,7 +1,7 @@
|
||||||
{- Interface for running a shell command as a coprocess,
|
{- Interface for running a shell command as a coprocess,
|
||||||
- sending it queries and getting back results.
|
- sending it queries and getting back results.
|
||||||
-
|
-
|
||||||
- Copyright 2012-2013 Joey Hess <id@joeyh.name>
|
- Copyright 2012-2023 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- License: BSD-2-clause
|
- License: BSD-2-clause
|
||||||
-}
|
-}
|
||||||
|
@ -14,6 +14,8 @@ module Utility.CoProcess (
|
||||||
start,
|
start,
|
||||||
stop,
|
stop,
|
||||||
query,
|
query,
|
||||||
|
send,
|
||||||
|
receive,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Common
|
import Common
|
||||||
|
@ -67,11 +69,11 @@ stop ch = do
|
||||||
- receive actions are assumed to mean communication with the process
|
- receive actions are assumed to mean communication with the process
|
||||||
- failed, and the failed action is re-run with a new process. -}
|
- failed, and the failed action is re-run with a new process. -}
|
||||||
query :: (MonadIO m, MonadCatch m) => CoProcessHandle -> (Handle -> m a) -> (Handle -> m b) -> m b
|
query :: (MonadIO m, MonadCatch m) => CoProcessHandle -> (Handle -> m a) -> (Handle -> m b) -> m b
|
||||||
query ch send receive = do
|
query ch sender receiver = do
|
||||||
s <- liftIO $ readMVar ch
|
s <- liftIO $ readMVar ch
|
||||||
restartable s (send $ coProcessTo s) $ const $
|
restartable s (sender $ coProcessTo s) $ const $
|
||||||
restartable s (liftIO $ hFlush $ coProcessTo s) $ const $
|
restartable s (liftIO $ hFlush $ coProcessTo s) $ const $
|
||||||
restartable s (receive $ coProcessFrom s)
|
restartable s (receiver $ coProcessFrom s)
|
||||||
return
|
return
|
||||||
where
|
where
|
||||||
restartable s a cont
|
restartable s a cont
|
||||||
|
@ -87,4 +89,15 @@ query ch send receive = do
|
||||||
s' <- liftIO $ start' $ (coProcessSpec s)
|
s' <- liftIO $ start' $ (coProcessSpec s)
|
||||||
{ coProcessNumRestarts = coProcessNumRestarts (coProcessSpec s) - 1 }
|
{ coProcessNumRestarts = coProcessNumRestarts (coProcessSpec s) - 1 }
|
||||||
liftIO $ putMVar ch s'
|
liftIO $ putMVar ch s'
|
||||||
query ch send receive
|
query ch sender receiver
|
||||||
|
|
||||||
|
send :: MonadIO m => CoProcessHandle -> (Handle -> m a) -> m a
|
||||||
|
send ch a = do
|
||||||
|
s <- liftIO $ readMVar ch
|
||||||
|
a (coProcessTo s)
|
||||||
|
|
||||||
|
receive :: MonadIO m => CoProcessHandle -> (Handle -> m a) -> m a
|
||||||
|
receive ch a = do
|
||||||
|
s <- liftIO $ readMVar ch
|
||||||
|
liftIO $ hFlush $ coProcessTo s
|
||||||
|
a (coProcessFrom s)
|
||||||
|
|
Loading…
Add table
Reference in a new issue