2016-02-23 20:36:08 +00:00
|
|
|
{- git trees
|
|
|
|
-
|
2024-01-16 15:52:45 +00:00
|
|
|
- Copyright 2016-2023 Joey Hess <id@joeyh.name>
|
2016-02-23 20:36:08 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2016-02-23 20:36:08 +00:00
|
|
|
-}
|
|
|
|
|
2016-03-11 23:29:43 +00:00
|
|
|
{-# LANGUAGE BangPatterns, TypeSynonymInstances, FlexibleInstances #-}
|
2024-01-16 15:52:45 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2016-02-24 00:25:31 +00:00
|
|
|
|
2016-02-23 20:36:08 +00:00
|
|
|
module Git.Tree (
|
|
|
|
Tree(..),
|
|
|
|
TreeContent(..),
|
|
|
|
getTree,
|
|
|
|
recordTree,
|
2019-02-22 16:41:17 +00:00
|
|
|
recordTree',
|
2021-10-06 21:05:32 +00:00
|
|
|
recordSubTree,
|
2016-02-24 01:35:16 +00:00
|
|
|
TreeItem(..),
|
2019-02-21 21:32:59 +00:00
|
|
|
treeItemsToTree,
|
2019-05-20 20:37:04 +00:00
|
|
|
treeItemToLsTreeItem,
|
|
|
|
lsTreeItemToTreeItem,
|
2016-02-24 01:35:16 +00:00
|
|
|
adjustTree,
|
2019-02-21 21:32:59 +00:00
|
|
|
graftTree,
|
2019-02-22 16:41:17 +00:00
|
|
|
graftTree',
|
|
|
|
withMkTreeHandle,
|
2021-10-06 21:05:32 +00:00
|
|
|
MkTreeHandle,
|
2023-12-06 20:27:12 +00:00
|
|
|
sendMkTree,
|
|
|
|
finishMkTree,
|
2017-08-31 22:06:49 +00:00
|
|
|
treeMode,
|
2016-02-23 20:36:08 +00:00
|
|
|
) where
|
|
|
|
|
|
|
|
import Common
|
|
|
|
import Git
|
|
|
|
import Git.FilePath
|
|
|
|
import Git.Types
|
|
|
|
import Git.Command
|
2016-02-23 22:30:11 +00:00
|
|
|
import Git.Sha
|
2016-02-23 20:36:08 +00:00
|
|
|
import qualified Git.LsTree as LsTree
|
|
|
|
import qualified Utility.CoProcess as CoProcess
|
2021-10-05 19:42:29 +00:00
|
|
|
import qualified System.FilePath.ByteString as P
|
2016-02-23 20:36:08 +00:00
|
|
|
|
|
|
|
import Numeric
|
|
|
|
import System.Posix.Types
|
2016-02-24 01:35:16 +00:00
|
|
|
import Control.Monad.IO.Class
|
2016-03-11 20:30:06 +00:00
|
|
|
import qualified Data.Set as S
|
2016-03-11 23:29:43 +00:00
|
|
|
import qualified Data.Map as M
|
2021-10-05 19:42:29 +00:00
|
|
|
import qualified Data.ByteString as B
|
2020-04-07 17:27:11 +00:00
|
|
|
import qualified Data.ByteString.Char8 as S8
|
2016-02-23 20:36:08 +00:00
|
|
|
|
|
|
|
newtype Tree = Tree [TreeContent]
|
|
|
|
deriving (Show)
|
|
|
|
|
|
|
|
data TreeContent
|
2017-02-20 17:44:55 +00:00
|
|
|
-- A blob object in the tree.
|
2016-02-23 20:36:08 +00:00
|
|
|
= TreeBlob TopFilePath FileMode Sha
|
|
|
|
-- A subtree that is already recorded in git, with a known sha.
|
|
|
|
| RecordedSubTree TopFilePath Sha [TreeContent]
|
|
|
|
-- A subtree that has not yet been recorded in git.
|
|
|
|
| NewSubTree TopFilePath [TreeContent]
|
2017-02-20 17:44:55 +00:00
|
|
|
-- A commit object that is part of a tree (used for submodules)
|
|
|
|
| TreeCommit TopFilePath FileMode Sha
|
2016-03-11 23:29:43 +00:00
|
|
|
deriving (Show, Eq, Ord)
|
2016-02-23 20:36:08 +00:00
|
|
|
|
|
|
|
{- Gets the Tree for a Ref. -}
|
2021-03-23 16:44:29 +00:00
|
|
|
getTree :: LsTree.LsTreeRecursive -> Ref -> Repo -> IO Tree
|
|
|
|
getTree recursive r repo = do
|
|
|
|
(l, cleanup) <- lsTreeWithObjects recursive r repo
|
2023-04-10 17:38:14 +00:00
|
|
|
let !t = either (\e -> giveup ("ls-tree parse error:" ++ e)) id
|
2016-02-24 00:25:31 +00:00
|
|
|
(extractTree l)
|
|
|
|
void cleanup
|
|
|
|
return t
|
2016-02-23 20:36:08 +00:00
|
|
|
|
2021-03-23 16:44:29 +00:00
|
|
|
lsTreeWithObjects :: LsTree.LsTreeRecursive -> Ref -> Repo -> IO ([LsTree.TreeItem], IO Bool)
|
|
|
|
lsTreeWithObjects recursive =
|
|
|
|
LsTree.lsTree' [Param "-t"] recursive (LsTree.LsTreeLong False)
|
2016-02-23 20:36:08 +00:00
|
|
|
|
2016-02-24 02:21:25 +00:00
|
|
|
newtype MkTreeHandle = MkTreeHandle CoProcess.CoProcessHandle
|
|
|
|
|
|
|
|
withMkTreeHandle :: (MonadIO m, MonadMask m) => Repo -> (MkTreeHandle -> m a) -> m a
|
|
|
|
withMkTreeHandle repo a = bracketIO setup cleanup (a . MkTreeHandle)
|
|
|
|
where
|
2016-11-01 18:03:55 +00:00
|
|
|
setup = gitCoProcessStart False ps repo
|
2023-05-31 16:31:14 +00:00
|
|
|
ps = [Param "mktree", Param "--missing", Param "--batch", Param "-z"]
|
2016-02-24 02:21:25 +00:00
|
|
|
cleanup = CoProcess.stop
|
|
|
|
|
2016-02-23 20:36:08 +00:00
|
|
|
{- Records a Tree in the Repo, returning its Sha.
|
|
|
|
-
|
|
|
|
- Efficiently handles subtrees, by only recording ones that have not
|
|
|
|
- already been recorded before. And even when many subtrees need to be
|
|
|
|
- recorded, it's done with a single call to git mktree, using its batch
|
|
|
|
- interface.
|
|
|
|
-}
|
2016-02-24 01:35:16 +00:00
|
|
|
recordTree :: Tree -> Repo -> IO Sha
|
2016-02-24 02:21:25 +00:00
|
|
|
recordTree t repo = withMkTreeHandle repo $ \h -> recordTree' h t
|
2016-02-23 20:36:08 +00:00
|
|
|
|
2016-02-24 02:21:25 +00:00
|
|
|
recordTree' :: MkTreeHandle -> Tree -> IO Sha
|
2023-12-06 20:27:12 +00:00
|
|
|
recordTree' h (Tree l) = mkTree h =<< mapM (recordSubTree h) l
|
2016-02-23 20:36:08 +00:00
|
|
|
|
2016-02-24 01:35:16 +00:00
|
|
|
{- Note that the returned RecordedSubTree does not have its [TreeContent]
|
|
|
|
- list populated. This is a memory optimisation, since the list is not
|
|
|
|
- used. -}
|
2016-02-24 02:21:25 +00:00
|
|
|
recordSubTree :: MkTreeHandle -> TreeContent -> IO TreeContent
|
2016-02-23 20:36:08 +00:00
|
|
|
recordSubTree h (NewSubTree d l) = do
|
2023-12-06 20:27:12 +00:00
|
|
|
sha <- mkTree h =<< mapM (recordSubTree h) l
|
2016-02-24 01:35:16 +00:00
|
|
|
return (RecordedSubTree d sha [])
|
2016-02-23 20:36:08 +00:00
|
|
|
recordSubTree _ alreadyrecorded = return alreadyrecorded
|
2023-12-06 19:38:01 +00:00
|
|
|
|
2023-12-06 20:27:12 +00:00
|
|
|
sendMkTree :: MkTreeHandle -> FileMode -> ObjectType -> Sha -> TopFilePath -> IO ()
|
|
|
|
sendMkTree (MkTreeHandle cp) fm ot s f =
|
|
|
|
CoProcess.send cp $ \h ->
|
|
|
|
hPutStr h (mkTreeOutput fm ot s f)
|
|
|
|
|
|
|
|
finishMkTree :: MkTreeHandle -> IO Sha
|
|
|
|
finishMkTree (MkTreeHandle cp) = do
|
|
|
|
CoProcess.send cp $ \h ->
|
2023-12-06 19:38:01 +00:00
|
|
|
-- NUL to signal end of tree to --batch
|
2023-12-06 20:27:12 +00:00
|
|
|
hPutStr h "\NUL"
|
|
|
|
getSha "mktree" (CoProcess.receive cp S8.hGetLine)
|
2023-12-06 19:38:01 +00:00
|
|
|
|
2023-12-06 20:27:12 +00:00
|
|
|
mkTree :: MkTreeHandle -> [TreeContent] -> IO Sha
|
|
|
|
mkTree h l = do
|
2023-12-06 19:38:01 +00:00
|
|
|
forM_ l $ \case
|
2023-12-06 20:27:12 +00:00
|
|
|
TreeBlob f fm s -> sendMkTree h fm BlobObject s f
|
|
|
|
RecordedSubTree f s _ -> sendMkTree h treeMode TreeObject s f
|
2023-12-06 19:38:01 +00:00
|
|
|
NewSubTree _ _ -> error "recordSubTree internal error; unexpected NewSubTree"
|
2023-12-06 20:27:12 +00:00
|
|
|
TreeCommit f fm s -> sendMkTree h fm CommitObject s f
|
|
|
|
finishMkTree h
|
2016-02-23 20:36:08 +00:00
|
|
|
|
2017-08-31 22:06:49 +00:00
|
|
|
treeMode :: FileMode
|
|
|
|
treeMode = 0o040000
|
|
|
|
|
2016-02-23 20:36:08 +00:00
|
|
|
mkTreeOutput :: FileMode -> ObjectType -> Sha -> TopFilePath -> String
|
2016-02-23 21:21:42 +00:00
|
|
|
mkTreeOutput fm ot s f = concat
|
|
|
|
[ showOct fm ""
|
|
|
|
, " "
|
2019-11-25 20:18:19 +00:00
|
|
|
, decodeBS (fmtObjectType ot)
|
2016-02-23 21:21:42 +00:00
|
|
|
, " "
|
|
|
|
, fromRef s
|
|
|
|
, "\t"
|
2019-12-09 17:49:05 +00:00
|
|
|
, takeFileName (fromRawFilePath (getTopFilePath f))
|
2016-02-23 21:21:42 +00:00
|
|
|
, "\NUL"
|
|
|
|
]
|
2016-02-24 01:35:16 +00:00
|
|
|
|
|
|
|
data TreeItem = TreeItem TopFilePath FileMode Sha
|
2016-03-11 20:00:14 +00:00
|
|
|
deriving (Show, Eq)
|
2016-02-24 01:35:16 +00:00
|
|
|
|
2016-03-11 18:08:06 +00:00
|
|
|
treeItemToTreeContent :: TreeItem -> TreeContent
|
2019-10-23 15:52:56 +00:00
|
|
|
treeItemToTreeContent (TreeItem f m s) = case toTreeItemType m of
|
|
|
|
Just TreeSubmodule -> TreeCommit f m s
|
|
|
|
_ -> TreeBlob f m s
|
2016-03-11 23:29:43 +00:00
|
|
|
|
2019-05-20 20:37:04 +00:00
|
|
|
treeItemToLsTreeItem :: TreeItem -> LsTree.TreeItem
|
|
|
|
treeItemToLsTreeItem (TreeItem f mode sha) = LsTree.TreeItem
|
|
|
|
{ LsTree.mode = mode
|
2021-03-12 17:24:19 +00:00
|
|
|
, LsTree.typeobj = fmtObjectType $ case toTreeItemType mode of
|
|
|
|
Just TreeSubmodule -> CommitObject
|
|
|
|
Just TreeSubtree -> TreeObject
|
|
|
|
_ -> BlobObject
|
2019-05-20 20:37:04 +00:00
|
|
|
, LsTree.sha = sha
|
2021-03-23 16:44:29 +00:00
|
|
|
, LsTree.size = Nothing
|
2019-05-20 20:37:04 +00:00
|
|
|
, LsTree.file = f
|
|
|
|
}
|
|
|
|
|
|
|
|
lsTreeItemToTreeItem :: LsTree.TreeItem -> TreeItem
|
|
|
|
lsTreeItemToTreeItem ti = TreeItem
|
|
|
|
(LsTree.file ti)
|
|
|
|
(LsTree.mode ti)
|
|
|
|
(LsTree.sha ti)
|
|
|
|
|
2016-03-11 23:29:43 +00:00
|
|
|
treeItemsToTree :: [TreeItem] -> Tree
|
|
|
|
treeItemsToTree = go M.empty
|
|
|
|
where
|
2016-05-03 22:56:06 +00:00
|
|
|
go m [] = Tree $ filter inTopTree (M.elems m)
|
2016-03-11 23:29:43 +00:00
|
|
|
go m (i:is)
|
2016-05-03 22:56:06 +00:00
|
|
|
| inTopTree p =
|
2016-03-11 23:29:43 +00:00
|
|
|
go (M.insert p (treeItemToTreeContent i) m) is
|
|
|
|
| otherwise = case M.lookup idir m of
|
|
|
|
Just (NewSubTree d l) ->
|
|
|
|
go (addsubtree idir m (NewSubTree d (c:l))) is
|
|
|
|
_ ->
|
2021-10-05 19:42:29 +00:00
|
|
|
go (addsubtree idir m (NewSubTree (asTopFilePath idir) [c])) is
|
2016-03-11 23:29:43 +00:00
|
|
|
where
|
|
|
|
p = gitPath i
|
2021-10-05 19:42:29 +00:00
|
|
|
idir = P.takeDirectory p
|
2016-03-11 23:29:43 +00:00
|
|
|
c = treeItemToTreeContent i
|
|
|
|
|
|
|
|
addsubtree d m t
|
2016-05-03 22:56:06 +00:00
|
|
|
| not (inTopTree d) =
|
2016-03-11 23:29:43 +00:00
|
|
|
let m' = M.insert d t m
|
|
|
|
in case M.lookup parent m' of
|
|
|
|
Just (NewSubTree d' l) ->
|
|
|
|
let l' = filter (\ti -> gitPath ti /= d) l
|
|
|
|
in addsubtree parent m' (NewSubTree d' (t:l'))
|
2021-10-05 19:42:29 +00:00
|
|
|
_ -> addsubtree parent m' (NewSubTree (asTopFilePath parent) [t])
|
2016-03-11 23:29:43 +00:00
|
|
|
| otherwise = M.insert d t m
|
|
|
|
where
|
2021-10-05 19:42:29 +00:00
|
|
|
parent = P.takeDirectory d
|
2016-03-11 18:08:06 +00:00
|
|
|
|
2016-10-11 19:36:40 +00:00
|
|
|
{- 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'
|
2017-02-20 17:44:55 +00:00
|
|
|
go _ c@(TreeCommit _ _ _) = [c]
|
2016-10-11 19:36:40 +00:00
|
|
|
|
2016-02-24 01:35:16 +00:00
|
|
|
{- Applies an adjustment to items in a tree.
|
|
|
|
-
|
2016-03-11 20:45:40 +00:00
|
|
|
- While less flexible than using getTree and recordTree,
|
|
|
|
- this avoids buffering the whole tree in memory.
|
2016-02-24 01:35:16 +00:00
|
|
|
-}
|
2016-03-11 20:30:06 +00:00
|
|
|
adjustTree
|
2016-04-08 20:09:00 +00:00
|
|
|
:: (Functor m, MonadIO m, MonadMask m)
|
2016-03-11 20:30:06 +00:00
|
|
|
=> (TreeItem -> m (Maybe TreeItem))
|
|
|
|
-- ^ Adjust an item in the tree. Nothing deletes the item.
|
|
|
|
-- Cannot move the item to a different tree.
|
|
|
|
-> [TreeItem]
|
|
|
|
-- ^ New items to add to the tree.
|
2019-05-20 20:37:04 +00:00
|
|
|
-> (TreeContent -> TreeContent -> TreeContent)
|
|
|
|
-- ^ When adding a new item to the tree and an item with the same
|
|
|
|
-- name already exists, this function picks which to use.
|
|
|
|
-- The first one is the item that was already in the tree.
|
2016-03-11 20:30:06 +00:00
|
|
|
-> [TopFilePath]
|
|
|
|
-- ^ Files to remove from the tree.
|
|
|
|
-> Ref
|
|
|
|
-> Repo
|
|
|
|
-> m Sha
|
2019-05-20 20:37:04 +00:00
|
|
|
adjustTree adjusttreeitem addtreeitems resolveaddconflict removefiles r repo =
|
2016-03-11 20:30:06 +00:00
|
|
|
withMkTreeHandle repo $ \h -> do
|
2019-02-21 21:32:59 +00:00
|
|
|
(l, cleanup) <- liftIO $ lsTreeWithObjects LsTree.LsTreeRecursive r repo
|
2016-10-11 19:36:40 +00:00
|
|
|
(l', _, _) <- go h False [] 1 inTopTree l
|
2024-01-16 15:52:45 +00:00
|
|
|
l'' <- adjustlist h 0 inTopTree topTreePath l'
|
2023-12-06 20:27:12 +00:00
|
|
|
sha <- liftIO $ mkTree h l''
|
2016-03-11 20:30:06 +00:00
|
|
|
void $ liftIO cleanup
|
|
|
|
return sha
|
2016-02-24 01:35:16 +00:00
|
|
|
where
|
2016-10-11 19:36:40 +00:00
|
|
|
go _ wasmodified c _ _ [] = return (c, wasmodified, [])
|
|
|
|
go h wasmodified c depth intree (i:is)
|
2016-03-11 18:46:54 +00:00
|
|
|
| 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
|
2016-10-11 19:36:40 +00:00
|
|
|
Nothing -> go h True c depth intree is
|
2016-03-11 18:46:54 +00:00
|
|
|
Just ti'@(TreeItem f m s) ->
|
|
|
|
let !modified = wasmodified || ti' /= ti
|
|
|
|
blob = TreeBlob f m s
|
2016-10-11 19:36:40 +00:00
|
|
|
in go h modified (blob:c) depth intree is
|
2016-03-11 18:46:54 +00:00
|
|
|
Just TreeObject -> do
|
2016-10-11 19:36:40 +00:00
|
|
|
(sl, modified, is') <- go h False [] (depth+1) (beneathSubTree i) is
|
2024-01-16 15:52:45 +00:00
|
|
|
sl' <- adjustlist h depth (inTree i) (gitPath i) sl
|
2016-10-10 19:00:45 +00:00
|
|
|
let slmodified = sl' /= sl
|
|
|
|
subtree <- if modified || slmodified
|
2016-03-11 20:45:40 +00:00
|
|
|
then liftIO $ recordSubTree h $ NewSubTree (LsTree.file i) sl'
|
2016-03-11 18:46:54 +00:00
|
|
|
else return $ RecordedSubTree (LsTree.file i) (LsTree.sha i) []
|
2016-10-10 19:00:45 +00:00
|
|
|
let !modified' = modified || slmodified || wasmodified
|
2016-10-11 19:36:40 +00:00
|
|
|
go h modified' (subtree : c) depth intree is'
|
2017-02-20 17:44:55 +00:00
|
|
|
Just CommitObject -> do
|
2020-03-18 02:16:06 +00:00
|
|
|
let ti = TreeItem (LsTree.file i) (LsTree.mode i) (LsTree.sha i)
|
|
|
|
v <- adjusttreeitem ti
|
2021-03-12 17:19:23 +00:00
|
|
|
case v of
|
|
|
|
Nothing -> go h True c depth intree is
|
|
|
|
Just (TreeItem f m s) ->
|
|
|
|
let commit = TreeCommit f m s
|
|
|
|
in go h wasmodified (commit:c) depth intree is
|
2023-04-10 17:38:14 +00:00
|
|
|
_ -> giveup ("unexpected object type \"" ++ decodeBS (LsTree.typeobj i) ++ "\"")
|
2016-02-24 01:35:16 +00:00
|
|
|
| otherwise = return (c, wasmodified, i:is)
|
2016-03-11 23:29:43 +00:00
|
|
|
|
2024-01-16 15:52:45 +00:00
|
|
|
adjustlist h depth ishere herepath l = do
|
|
|
|
let addhere = fromMaybe [] $ M.lookup herepath addtreeitempathmap
|
2016-03-11 23:29:43 +00:00
|
|
|
let l' = filter (not . removed) $
|
2019-05-20 20:37:04 +00:00
|
|
|
addoldnew l (map treeItemToTreeContent addhere)
|
2016-03-11 23:29:43 +00:00
|
|
|
let inl i = any (\t -> beneathSubTree t i) l'
|
2016-10-11 19:36:40 +00:00
|
|
|
let (Tree addunderhere) = flattenTree depth $ treeItemsToTree $
|
2024-01-16 15:52:45 +00:00
|
|
|
filter (not . inl) $ if herepath == topTreePath
|
|
|
|
then filter (not . ishere) addtreeitems
|
|
|
|
else fromMaybe [] $
|
|
|
|
M.lookup (subTreePrefix herepath) addtreeitemprefixmap
|
2016-03-11 23:29:43 +00:00
|
|
|
addunderhere' <- liftIO $ mapM (recordSubTree h) addunderhere
|
2019-05-20 20:37:04 +00:00
|
|
|
return (addoldnew l' addunderhere')
|
2016-03-11 23:29:43 +00:00
|
|
|
|
2024-01-16 15:52:45 +00:00
|
|
|
addtreeitempathmap = mkPathMap addtreeitems
|
|
|
|
addtreeitemprefixmap = mkSubTreePathPrefixMap addtreeitems
|
|
|
|
|
2021-10-05 19:42:29 +00:00
|
|
|
removeset = S.fromList $ map (P.normalise . gitPath) removefiles
|
|
|
|
removed (TreeBlob f _ _) = S.member (P.normalise (gitPath f)) removeset
|
|
|
|
removed (TreeCommit f _ _) = S.member (P.normalise (gitPath f)) removeset
|
2021-01-07 17:44:23 +00:00
|
|
|
removed (RecordedSubTree _ _ _) = False
|
|
|
|
removed (NewSubTree _ _) = False
|
2016-02-24 01:35:16 +00:00
|
|
|
|
2019-05-20 20:37:04 +00:00
|
|
|
addoldnew [] new = new
|
|
|
|
addoldnew old [] = old
|
|
|
|
addoldnew old new = addoldnew' (M.fromList $ map (\i -> (mkk i, i)) old) new
|
|
|
|
addoldnew' oldm (n:ns) =
|
|
|
|
let k = mkk n
|
|
|
|
in case M.lookup k oldm of
|
|
|
|
Just o ->
|
|
|
|
resolveaddconflict o n
|
|
|
|
:
|
|
|
|
addoldnew' (M.delete k oldm) ns
|
|
|
|
Nothing -> n : addoldnew' oldm ns
|
|
|
|
addoldnew' oldm [] = M.elems oldm
|
2021-10-05 19:42:29 +00:00
|
|
|
mkk = P.normalise . gitPath
|
2019-05-20 20:37:04 +00:00
|
|
|
|
2019-02-22 02:25:42 +00:00
|
|
|
{- Grafts subtree into the basetree at the specified location, replacing
|
|
|
|
- anything that the basetree already had at that location.
|
2019-02-21 21:32:59 +00:00
|
|
|
-
|
|
|
|
- This is generally much more efficient than using getTree and recordTree,
|
|
|
|
- or adjustTree, since it only needs to traverse from the top of the tree
|
|
|
|
- down to the graft location. It does not buffer the whole tree in memory.
|
|
|
|
-}
|
|
|
|
graftTree
|
|
|
|
:: Sha
|
|
|
|
-> TopFilePath
|
|
|
|
-> Sha
|
|
|
|
-> Repo
|
|
|
|
-> IO Sha
|
|
|
|
graftTree subtree graftloc basetree repo =
|
2019-02-22 16:41:17 +00:00
|
|
|
withMkTreeHandle repo $ graftTree' subtree graftloc basetree repo
|
|
|
|
|
|
|
|
graftTree'
|
|
|
|
:: Sha
|
|
|
|
-> TopFilePath
|
|
|
|
-> Sha
|
|
|
|
-> Repo
|
|
|
|
-> MkTreeHandle
|
|
|
|
-> IO Sha
|
Fix bug importing from a special remote into a subdirectory more than one level deep
Which generated unusual git trees that could confuse git merge,
since they incorrectly had 2 subtrees with the same name.
Root of the bug was a) not testing that at all! but also
b) confusing graftdirs, which contains eg "foo/bar" with
non-recursively read trees, which would contain eg "bar"
when reading a subtree of "foo".
It's worth noting that Annex.Import uses graftTree, but it really
shouldn't have needed to. Eg, when importing into foo/bar from a remote,
it's enough to generate a tree of foo/bar/x, foo/bar/y, and does not
include other files that are at the top of the master branch. It uses
graftTree, so it does include the other files, as well as the foo/bar
tree. git merge will do the same thing for both trees. With that said,
switching it away from graftTree would result in another import
generating a new commit that seems to delete files that were there in a
previous commit, so it probably has to keep using graftTree since it
used it before.
This commit was sponsored by Kevin Mueller on Patreon.
2021-03-26 20:01:55 +00:00
|
|
|
graftTree' subtree graftloc basetree repo hdl = go basetree subdirs graftdirs
|
2019-02-21 21:32:59 +00:00
|
|
|
where
|
Fix bug importing from a special remote into a subdirectory more than one level deep
Which generated unusual git trees that could confuse git merge,
since they incorrectly had 2 subtrees with the same name.
Root of the bug was a) not testing that at all! but also
b) confusing graftdirs, which contains eg "foo/bar" with
non-recursively read trees, which would contain eg "bar"
when reading a subtree of "foo".
It's worth noting that Annex.Import uses graftTree, but it really
shouldn't have needed to. Eg, when importing into foo/bar from a remote,
it's enough to generate a tree of foo/bar/x, foo/bar/y, and does not
include other files that are at the top of the master branch. It uses
graftTree, so it does include the other files, as well as the foo/bar
tree. git merge will do the same thing for both trees. With that said,
switching it away from graftTree would result in another import
generating a new commit that seems to delete files that were there in a
previous commit, so it probably has to keep using graftTree since it
used it before.
This commit was sponsored by Kevin Mueller on Patreon.
2021-03-26 20:01:55 +00:00
|
|
|
go tsha (subdir:restsubdirs) (topmostgraphdir:restgraphdirs) = do
|
2019-02-21 21:32:59 +00:00
|
|
|
Tree t <- getTree LsTree.LsTreeNonRecursive tsha repo
|
Fix bug importing from a special remote into a subdirectory more than one level deep
Which generated unusual git trees that could confuse git merge,
since they incorrectly had 2 subtrees with the same name.
Root of the bug was a) not testing that at all! but also
b) confusing graftdirs, which contains eg "foo/bar" with
non-recursively read trees, which would contain eg "bar"
when reading a subtree of "foo".
It's worth noting that Annex.Import uses graftTree, but it really
shouldn't have needed to. Eg, when importing into foo/bar from a remote,
it's enough to generate a tree of foo/bar/x, foo/bar/y, and does not
include other files that are at the top of the master branch. It uses
graftTree, so it does include the other files, as well as the foo/bar
tree. git merge will do the same thing for both trees. With that said,
switching it away from graftTree would result in another import
generating a new commit that seems to delete files that were there in a
previous commit, so it probably has to keep using graftTree since it
used it before.
This commit was sponsored by Kevin Mueller on Patreon.
2021-03-26 20:01:55 +00:00
|
|
|
let abovegraftpoint i = gitPath i == gitPath subdir
|
|
|
|
t' <- case partition abovegraftpoint t of
|
|
|
|
-- the graft point is not already in the tree,
|
|
|
|
-- so graft it in, keeping the existing tree
|
|
|
|
-- content
|
2019-02-21 21:32:59 +00:00
|
|
|
([], _) -> do
|
2019-02-22 16:41:17 +00:00
|
|
|
graft <- graftin (topmostgraphdir:restgraphdirs)
|
2019-02-21 21:32:59 +00:00
|
|
|
return (graft:t)
|
|
|
|
(matching, rest) -> do
|
|
|
|
newshas <- forM matching $ \case
|
2019-02-22 02:25:42 +00:00
|
|
|
RecordedSubTree tloc tsha' _
|
|
|
|
| null restgraphdirs -> return $
|
|
|
|
RecordedSubTree tloc subtree []
|
|
|
|
| otherwise -> do
|
Fix bug importing from a special remote into a subdirectory more than one level deep
Which generated unusual git trees that could confuse git merge,
since they incorrectly had 2 subtrees with the same name.
Root of the bug was a) not testing that at all! but also
b) confusing graftdirs, which contains eg "foo/bar" with
non-recursively read trees, which would contain eg "bar"
when reading a subtree of "foo".
It's worth noting that Annex.Import uses graftTree, but it really
shouldn't have needed to. Eg, when importing into foo/bar from a remote,
it's enough to generate a tree of foo/bar/x, foo/bar/y, and does not
include other files that are at the top of the master branch. It uses
graftTree, so it does include the other files, as well as the foo/bar
tree. git merge will do the same thing for both trees. With that said,
switching it away from graftTree would result in another import
generating a new commit that seems to delete files that were there in a
previous commit, so it probably has to keep using graftTree since it
used it before.
This commit was sponsored by Kevin Mueller on Patreon.
2021-03-26 20:01:55 +00:00
|
|
|
tsha'' <- go tsha' restsubdirs restgraphdirs
|
2019-02-22 02:25:42 +00:00
|
|
|
return $ RecordedSubTree tloc tsha'' []
|
2019-02-22 16:41:17 +00:00
|
|
|
_ -> graftin (topmostgraphdir:restgraphdirs)
|
2019-02-21 21:32:59 +00:00
|
|
|
return (newshas ++ rest)
|
2023-12-06 20:27:12 +00:00
|
|
|
mkTree hdl t'
|
Fix bug importing from a special remote into a subdirectory more than one level deep
Which generated unusual git trees that could confuse git merge,
since they incorrectly had 2 subtrees with the same name.
Root of the bug was a) not testing that at all! but also
b) confusing graftdirs, which contains eg "foo/bar" with
non-recursively read trees, which would contain eg "bar"
when reading a subtree of "foo".
It's worth noting that Annex.Import uses graftTree, but it really
shouldn't have needed to. Eg, when importing into foo/bar from a remote,
it's enough to generate a tree of foo/bar/x, foo/bar/y, and does not
include other files that are at the top of the master branch. It uses
graftTree, so it does include the other files, as well as the foo/bar
tree. git merge will do the same thing for both trees. With that said,
switching it away from graftTree would result in another import
generating a new commit that seems to delete files that were there in a
previous commit, so it probably has to keep using graftTree since it
used it before.
This commit was sponsored by Kevin Mueller on Patreon.
2021-03-26 20:01:55 +00:00
|
|
|
go _ _ [] = return subtree
|
2021-03-30 16:59:53 +00:00
|
|
|
go _ [] _ = return subtree
|
2019-02-21 21:32:59 +00:00
|
|
|
|
2019-02-22 16:41:17 +00:00
|
|
|
graftin t = recordSubTree hdl $ graftin' t
|
2019-02-21 21:32:59 +00:00
|
|
|
graftin' [] = RecordedSubTree graftloc subtree []
|
2019-02-22 02:25:42 +00:00
|
|
|
graftin' (d:rest)
|
|
|
|
| d == graftloc = graftin' []
|
|
|
|
| otherwise = NewSubTree d [graftin' rest]
|
Fix bug importing from a special remote into a subdirectory more than one level deep
Which generated unusual git trees that could confuse git merge,
since they incorrectly had 2 subtrees with the same name.
Root of the bug was a) not testing that at all! but also
b) confusing graftdirs, which contains eg "foo/bar" with
non-recursively read trees, which would contain eg "bar"
when reading a subtree of "foo".
It's worth noting that Annex.Import uses graftTree, but it really
shouldn't have needed to. Eg, when importing into foo/bar from a remote,
it's enough to generate a tree of foo/bar/x, foo/bar/y, and does not
include other files that are at the top of the master branch. It uses
graftTree, so it does include the other files, as well as the foo/bar
tree. git merge will do the same thing for both trees. With that said,
switching it away from graftTree would result in another import
generating a new commit that seems to delete files that were there in a
previous commit, so it probably has to keep using graftTree since it
used it before.
This commit was sponsored by Kevin Mueller on Patreon.
2021-03-26 20:01:55 +00:00
|
|
|
|
2021-10-05 19:42:29 +00:00
|
|
|
subdirs = P.splitDirectories $ gitPath graftloc
|
Fix bug importing from a special remote into a subdirectory more than one level deep
Which generated unusual git trees that could confuse git merge,
since they incorrectly had 2 subtrees with the same name.
Root of the bug was a) not testing that at all! but also
b) confusing graftdirs, which contains eg "foo/bar" with
non-recursively read trees, which would contain eg "bar"
when reading a subtree of "foo".
It's worth noting that Annex.Import uses graftTree, but it really
shouldn't have needed to. Eg, when importing into foo/bar from a remote,
it's enough to generate a tree of foo/bar/x, foo/bar/y, and does not
include other files that are at the top of the master branch. It uses
graftTree, so it does include the other files, as well as the foo/bar
tree. git merge will do the same thing for both trees. With that said,
switching it away from graftTree would result in another import
generating a new commit that seems to delete files that were there in a
previous commit, so it probably has to keep using graftTree since it
used it before.
This commit was sponsored by Kevin Mueller on Patreon.
2021-03-26 20:01:55 +00:00
|
|
|
|
2021-10-05 19:42:29 +00:00
|
|
|
graftdirs = map (asTopFilePath . toInternalGitPath) $
|
2024-01-16 15:52:45 +00:00
|
|
|
pathPrefixes subdirs
|
2019-02-21 21:32:59 +00:00
|
|
|
|
2016-02-24 01:35:16 +00:00
|
|
|
{- Assumes the list is ordered, with tree objects coming right before their
|
|
|
|
- contents. -}
|
|
|
|
extractTree :: [LsTree.TreeItem] -> Either String Tree
|
2016-03-11 18:08:06 +00:00
|
|
|
extractTree l = case go [] inTopTree l of
|
2016-02-24 01:35:16 +00:00
|
|
|
Right (t, []) -> Right (Tree t)
|
|
|
|
Right _ -> parseerr "unexpected tree form"
|
|
|
|
Left e -> parseerr e
|
|
|
|
where
|
|
|
|
go t _ [] = Right (t, [])
|
2016-02-24 01:56:03 +00:00
|
|
|
go t intree (i:is)
|
2016-03-11 18:46:54 +00:00
|
|
|
| intree i = case readObjectType (LsTree.typeobj i) of
|
|
|
|
Just BlobObject ->
|
|
|
|
let b = TreeBlob (LsTree.file i) (LsTree.mode i) (LsTree.sha i)
|
|
|
|
in go (b:t) intree is
|
|
|
|
Just TreeObject -> case go [] (beneathSubTree i) is of
|
|
|
|
Right (subtree, is') ->
|
|
|
|
let st = RecordedSubTree (LsTree.file i) (LsTree.sha i) subtree
|
|
|
|
in go (st:t) intree is'
|
|
|
|
Left e -> Left e
|
2017-02-20 17:44:55 +00:00
|
|
|
Just CommitObject ->
|
|
|
|
let c = TreeCommit (LsTree.file i) (LsTree.mode i) (LsTree.sha i)
|
|
|
|
in go (c:t) intree is
|
2019-11-25 20:18:19 +00:00
|
|
|
_ -> parseerr ("unexpected object type \"" ++ decodeBS (LsTree.typeobj i) ++ "\"")
|
2016-02-24 01:35:16 +00:00
|
|
|
| otherwise = Right (t, i:is)
|
|
|
|
parseerr = Left
|
2016-02-24 01:56:03 +00:00
|
|
|
|
2016-03-11 23:29:43 +00:00
|
|
|
class GitPath t where
|
2021-10-05 19:42:29 +00:00
|
|
|
gitPath :: t -> RawFilePath
|
2016-03-11 23:29:43 +00:00
|
|
|
|
2021-10-05 19:42:29 +00:00
|
|
|
instance GitPath RawFilePath where
|
2016-03-11 23:29:43 +00:00
|
|
|
gitPath = id
|
|
|
|
|
2021-10-05 19:42:29 +00:00
|
|
|
instance GitPath FilePath where
|
|
|
|
gitPath = toRawFilePath
|
|
|
|
|
2016-03-11 23:29:43 +00:00
|
|
|
instance GitPath TopFilePath where
|
2021-10-05 19:42:29 +00:00
|
|
|
gitPath = getTopFilePath
|
2016-02-24 01:56:03 +00:00
|
|
|
|
2016-03-11 23:29:43 +00:00
|
|
|
instance GitPath TreeItem where
|
|
|
|
gitPath (TreeItem f _ _) = gitPath f
|
2016-03-11 20:00:14 +00:00
|
|
|
|
2016-03-11 23:29:43 +00:00
|
|
|
instance GitPath LsTree.TreeItem where
|
|
|
|
gitPath = gitPath . LsTree.file
|
2016-02-24 01:56:03 +00:00
|
|
|
|
2016-03-11 23:29:43 +00:00
|
|
|
instance GitPath TreeContent where
|
|
|
|
gitPath (TreeBlob f _ _) = gitPath f
|
|
|
|
gitPath (RecordedSubTree f _ _) = gitPath f
|
|
|
|
gitPath (NewSubTree f _) = gitPath f
|
2017-02-20 17:44:55 +00:00
|
|
|
gitPath (TreeCommit f _ _) = gitPath f
|
2016-03-11 18:08:06 +00:00
|
|
|
|
2016-03-11 23:29:43 +00:00
|
|
|
inTopTree :: GitPath t => t -> Bool
|
2024-01-16 15:52:45 +00:00
|
|
|
inTopTree = inTree topTreePath
|
|
|
|
|
|
|
|
topTreePath :: RawFilePath
|
|
|
|
topTreePath = "."
|
2016-03-11 20:30:06 +00:00
|
|
|
|
2016-03-11 23:29:43 +00:00
|
|
|
inTree :: (GitPath t, GitPath f) => t -> f -> Bool
|
2021-10-05 19:42:29 +00:00
|
|
|
inTree t f = gitPath t == P.takeDirectory (gitPath f)
|
2016-03-11 23:29:43 +00:00
|
|
|
|
|
|
|
beneathSubTree :: (GitPath t, GitPath f) => t -> f -> Bool
|
2024-01-16 15:52:45 +00:00
|
|
|
beneathSubTree t f = subTreePrefix t `B.isPrefixOf` subTreePath f
|
|
|
|
|
|
|
|
subTreePath :: GitPath t => t -> RawFilePath
|
|
|
|
subTreePath = P.normalise . gitPath
|
|
|
|
|
|
|
|
subTreePrefix :: GitPath t => t -> RawFilePath
|
|
|
|
subTreePrefix t
|
|
|
|
| B.null tp = tp
|
|
|
|
| otherwise = P.addTrailingPathSeparator (P.normalise tp)
|
2016-03-11 23:29:43 +00:00
|
|
|
where
|
|
|
|
tp = gitPath t
|
2024-01-16 15:52:45 +00:00
|
|
|
|
|
|
|
{- Makes a Map where the keys are directories, and the values
|
|
|
|
- are the items located in that directory.
|
|
|
|
-
|
|
|
|
- Values that are not in any subdirectory are placed in
|
|
|
|
- the topTreePath key.
|
|
|
|
-}
|
|
|
|
mkPathMap :: GitPath t => [t] -> M.Map RawFilePath [t]
|
|
|
|
mkPathMap l = M.fromListWith (++) $
|
|
|
|
map (\ti -> (P.takeDirectory (gitPath ti), [ti])) l
|
|
|
|
|
|
|
|
{- Input is eg splitDirectories "foo/bar/baz",
|
|
|
|
- for which it will output ["foo", "foo/bar", "foo/bar/baz"] -}
|
|
|
|
pathPrefixes :: [RawFilePath] -> [RawFilePath]
|
|
|
|
pathPrefixes = go []
|
|
|
|
where
|
|
|
|
go _ [] = []
|
|
|
|
go base (d:rest) = (P.joinPath base P.</> d) : go (base ++ [d]) rest
|
|
|
|
|
|
|
|
{- Makes a Map where the keys are all subtree path prefixes,
|
|
|
|
- and the values are items with that subtree path prefix.
|
|
|
|
-}
|
|
|
|
mkSubTreePathPrefixMap :: GitPath t => [t] -> M.Map RawFilePath [t]
|
|
|
|
mkSubTreePathPrefixMap l = M.fromListWith (++) $ concatMap go l
|
|
|
|
where
|
|
|
|
go ti = map (\p -> (p, [ti]))
|
|
|
|
(map subTreePrefix $ pathPrefixes $ P.splitDirectories $ subTreePath ti)
|