summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Git/Tree.hs32
-rw-r--r--Test.hs22
-rw-r--r--doc/bugs/sync_in_adjusted_branch_deleted_recently_added_files.mdwn14
-rw-r--r--doc/devblog/day_421__lost_in_the_trees.mdwn6
4 files changed, 61 insertions, 13 deletions
diff --git a/Git/Tree.hs b/Git/Tree.hs
index 65c3d713a..c341e1f5b 100644
--- a/Git/Tree.hs
+++ b/Git/Tree.hs
@@ -143,6 +143,16 @@ treeItemsToTree = go M.empty
where
parent = takeDirectory d
+{- Flattens the top N levels of a Tree. -}
+flattenTree :: Int -> Tree -> Tree
+flattenTree 0 t = t
+flattenTree n (Tree l) = Tree (concatMap (go n) l)
+ where
+ go 0 c = [c]
+ go _ b@(TreeBlob _ _ _) = [b]
+ go n' (RecordedSubTree _ _ l') = concatMap (go (n'-1)) l'
+ go n' (NewSubTree _ l') = concatMap (go (n'-1)) l'
+
{- Applies an adjustment to items in a tree.
-
- While less flexible than using getTree and recordTree,
@@ -163,42 +173,42 @@ adjustTree
adjustTree adjusttreeitem addtreeitems removefiles r repo =
withMkTreeHandle repo $ \h -> do
(l, cleanup) <- liftIO $ lsTreeWithObjects r repo
- (l', _, _) <- go h False [] inTopTree l
- l'' <- adjustlist h inTopTree (const True) l'
+ (l', _, _) <- go h False [] 1 inTopTree l
+ l'' <- adjustlist h 0 inTopTree (const True) l'
sha <- liftIO $ mkTree h l''
void $ liftIO cleanup
return sha
where
- go _ wasmodified c _ [] = return (c, wasmodified, [])
- go h wasmodified c intree (i:is)
+ go _ wasmodified c _ _ [] = return (c, wasmodified, [])
+ go h wasmodified c depth intree (i:is)
| intree i = case readObjectType (LsTree.typeobj i) of
Just BlobObject -> do
let ti = TreeItem (LsTree.file i) (LsTree.mode i) (LsTree.sha i)
v <- adjusttreeitem ti
case v of
- Nothing -> go h True c intree is
+ Nothing -> go h True c depth intree is
Just ti'@(TreeItem f m s) ->
let !modified = wasmodified || ti' /= ti
blob = TreeBlob f m s
- in go h modified (blob:c) intree is
+ in go h modified (blob:c) depth intree is
Just TreeObject -> do
- (sl, modified, is') <- go h False [] (beneathSubTree i) is
- sl' <- adjustlist h (inTree i) (beneathSubTree i) sl
+ (sl, modified, is') <- go h False [] (depth+1) (beneathSubTree i) is
+ sl' <- adjustlist h depth (inTree i) (beneathSubTree i) sl
let slmodified = sl' /= sl
subtree <- if modified || slmodified
then liftIO $ recordSubTree h $ NewSubTree (LsTree.file i) sl'
else return $ RecordedSubTree (LsTree.file i) (LsTree.sha i) []
let !modified' = modified || slmodified || wasmodified
- go h modified' (subtree : c) intree is'
+ go h modified' (subtree : c) depth intree is'
_ -> error ("unexpected object type \"" ++ LsTree.typeobj i ++ "\"")
| otherwise = return (c, wasmodified, i:is)
- adjustlist h ishere underhere l = do
+ adjustlist h depth ishere underhere l = do
let (addhere, rest) = partition ishere addtreeitems
let l' = filter (not . removed) $
map treeItemToTreeContent addhere ++ l
let inl i = any (\t -> beneathSubTree t i) l'
- let (Tree addunderhere) = treeItemsToTree $
+ let (Tree addunderhere) = flattenTree depth $ treeItemsToTree $
filter (\i -> underhere i && not (inl i)) rest
addunderhere' <- liftIO $ mapM (recordSubTree h) addunderhere
return (addunderhere'++l')
diff --git a/Test.hs b/Test.hs
index cd7118fe4..abd26e4ea 100644
--- a/Test.hs
+++ b/Test.hs
@@ -234,6 +234,7 @@ unitTests note = testGroup ("Unit Tests " ++ note)
, testCase "sync" test_sync
, testCase "union merge regression" test_union_merge_regression
, testCase "adjusted branch merge regression" test_adjusted_branch_merge_regression
+ , testCase "adjusted branch subtree regression" test_adjusted_branch_subtree_regression
, testCase "conflict resolution" test_conflict_resolution
, testCase "conflict resolution (adjusted branch)" test_conflict_resolution_adjusted_branch
, testCase "conflict resolution movein regression" test_conflict_resolution_movein_regression
@@ -1425,6 +1426,27 @@ test_adjusted_branch_merge_regression = whenM Annex.AdjustedBranch.isGitVersionS
conflictor `elem` l
@? ("conflictor not present after merge in " ++ what)
+{- Regression test for a bug in adjusted branch syncing code, where adding
+ - a subtree to an existing tree lost files. -}
+test_adjusted_branch_subtree_regression :: Assertion
+test_adjusted_branch_subtree_regression =
+ whenM Annex.AdjustedBranch.isGitVersionSupported $
+ withtmpclonerepo $ \r -> do
+ indir r $ do
+ disconnectOrigin
+ git_annex "upgrade" [] @? "upgrade failed"
+ git_annex "adjust" ["--unlock", "--force"] @? "adjust failed"
+ createDirectoryIfMissing True "a/b/c"
+ writeFile "a/b/c/d" "foo"
+ git_annex "add" ["a/b/c"] @? "add a/b/c failed"
+ git_annex "sync" [] @? "sync failed"
+ createDirectoryIfMissing True "a/b/x"
+ writeFile "a/b/x/y" "foo"
+ git_annex "add" ["a/b/x"] @? "add a/b/x failed"
+ git_annex "sync" [] @? "sync failed"
+ boolSystem "git" [Param "checkout", Param "master"] @? "git checkout master failed"
+ doesFileExist "a/b/x/y" @? ("a/b/x/y missing from master after adjusted branch sync")
+
{- Set up repos as remotes of each other. -}
pair :: FilePath -> FilePath -> Assertion
pair r1 r2 = forM_ [r1, r2] $ \r -> indir r $ do
diff --git a/doc/bugs/sync_in_adjusted_branch_deleted_recently_added_files.mdwn b/doc/bugs/sync_in_adjusted_branch_deleted_recently_added_files.mdwn
index ce271d8dd..6c82fcf82 100644
--- a/doc/bugs/sync_in_adjusted_branch_deleted_recently_added_files.mdwn
+++ b/doc/bugs/sync_in_adjusted_branch_deleted_recently_added_files.mdwn
@@ -64,8 +64,7 @@ tree items, but it can forget that it needed to modify the tree, which
prevents the change from propigating up from the subtree to the root, and
so it gets left out of the reverse adjusted commit.
-I'm committing a fix, but this needs a test case. Leaving bug open for
-that.
+I'm committing a fix.
With the fix, when I git annex sync in felix's tree, the files that
were getting wrongly deleted are added. The commit summary shows
@@ -77,4 +76,15 @@ This seems wrong. I think this is a separate bug that was hidden
by the other one, it's grafting in files using their whole path,
to a subtree that is itself part way down that path.
+---
+
+A simpler case of the both bugs is to have a file like a/b/c/d already
+committed and make a commit that adds a/b/x/y, without otherwise modifying
+that tree. On an adjusted branch, `git annex sync` makes a commit of a tree
+that does not include the new file. It may made a commit on top of it for
+the adjusted branch that adds the file back, but the file doesn't reach
+the master branch in this scenario.
+
--[[Joey]]
+
+Both bugs fixed now. [[done]] --[[Joey]]
diff --git a/doc/devblog/day_421__lost_in_the_trees.mdwn b/doc/devblog/day_421__lost_in_the_trees.mdwn
new file mode 100644
index 000000000..1cb09b63d
--- /dev/null
+++ b/doc/devblog/day_421__lost_in_the_trees.mdwn
@@ -0,0 +1,6 @@
+Finished up where I left off yesterday, writing test cases and fixing
+bugs with syncing in adjusted branches. While adjusted branches need v6
+mode, and v6 mode is still considered experimental, this is still a rather
+nasty bug, since it can make files go missing (though still available
+in git history of course). So, planning to release a new version with these
+fixes as soon as the autobuilders build it.