git-annex/Git/Tree.hs

263 lines
8.1 KiB
Haskell
Raw Normal View History

2016-02-23 20:36:08 +00:00
{- git trees
-
- Copyright 2016 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
2016-03-11 23:29:43 +00:00
{-# LANGUAGE BangPatterns, TypeSynonymInstances, FlexibleInstances #-}
2016-02-23 20:36:08 +00:00
module Git.Tree (
Tree(..),
TreeContent(..),
getTree,
recordTree,
TreeItem(..),
adjustTree,
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
import Numeric
import System.Posix.Types
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
2016-02-23 20:36:08 +00:00
newtype Tree = Tree [TreeContent]
deriving (Show)
data TreeContent
= 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]
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. -}
getTree :: Ref -> Repo -> IO Tree
2016-02-23 20:36:08 +00:00
getTree r repo = do
(l, cleanup) <- lsTreeWithObjects r repo
let !t = either (\e -> error ("ls-tree parse error:" ++ e)) id
(extractTree l)
void cleanup
return t
2016-02-23 20:36:08 +00:00
lsTreeWithObjects :: Ref -> Repo -> IO ([LsTree.TreeItem], IO Bool)
lsTreeWithObjects = LsTree.lsTree' [Param "-t"]
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
setup = CoProcess.rawMode =<< gitCoProcessStart False ps repo
ps = [Param "mktree", Param "--batch", Param "-z"]
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.
-}
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
2016-02-23 21:21:42 +00:00
recordTree' h (Tree l) = mkTree h =<< mapM (recordSubTree h) l
2016-02-23 20:36:08 +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
sha <- mkTree h =<< mapM (recordSubTree h) l
return (RecordedSubTree d sha [])
2016-02-23 20:36:08 +00:00
recordSubTree _ alreadyrecorded = return alreadyrecorded
2016-02-24 02:21:25 +00:00
mkTree :: MkTreeHandle -> [TreeContent] -> IO Sha
mkTree (MkTreeHandle cp) l = CoProcess.query cp send receive
2016-02-23 20:36:08 +00:00
where
send h = do
forM_ l $ \i -> hPutStr h $ case i of
TreeBlob f fm s -> mkTreeOutput fm BlobObject s f
RecordedSubTree f s _ -> mkTreeOutput 0o040000 TreeObject s f
NewSubTree _ _ -> error "recordSubTree internal error; unexpected NewSubTree"
hPutStr h "\NUL" -- signal end of tree to --batch
2016-02-23 22:30:11 +00:00
receive h = getSha "mktree" (hGetLine h)
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 ""
, " "
, show ot
, " "
, fromRef s
, "\t"
, takeFileName (getTopFilePath f)
, "\NUL"
]
data TreeItem = TreeItem TopFilePath FileMode Sha
deriving (Show, Eq)
2016-03-11 18:08:06 +00:00
treeItemToTreeContent :: TreeItem -> TreeContent
treeItemToTreeContent (TreeItem f m s) = TreeBlob f m s
2016-03-11 23:29:43 +00:00
treeItemsToTree :: [TreeItem] -> Tree
treeItemsToTree = go M.empty
where
go m [] = Tree $ filter inTopTree (M.elems m)
2016-03-11 23:29:43 +00:00
go m (i:is)
| 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
_ ->
go (addsubtree idir m (NewSubTree (asTopFilePath idir) [c])) is
where
p = gitPath i
idir = takeDirectory p
c = treeItemToTreeContent i
addsubtree d m t
| 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'))
_ -> addsubtree parent m' (NewSubTree (asTopFilePath parent) [t])
| otherwise = M.insert d t m
where
parent = takeDirectory d
2016-03-11 18:08:06 +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-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.
-> [TopFilePath]
-- ^ Files to remove from the tree.
-> Ref
-> Repo
-> m Sha
adjustTree adjusttreeitem addtreeitems removefiles r repo =
withMkTreeHandle repo $ \h -> do
(l, cleanup) <- liftIO $ lsTreeWithObjects r repo
(l', _, _) <- go h False [] inTopTree l
2016-03-11 23:29:43 +00:00
l'' <- adjustlist h inTopTree (const True) l'
2016-03-11 20:45:40 +00:00
sha <- liftIO $ mkTree h l''
2016-03-11 20:30:06 +00:00
void $ liftIO cleanup
return sha
where
go _ wasmodified c _ [] = return (c, wasmodified, [])
2016-02-24 01:56:03 +00:00
go h wasmodified c 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
Nothing -> go h True c 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
Just TreeObject -> do
(sl, modified, is') <- go h False [] (beneathSubTree i) is
2016-03-11 23:29:43 +00:00
sl' <- adjustlist h (inTree i) (beneathSubTree i) sl
2016-03-11 20:45:40 +00:00
subtree <- if modified || sl' /= sl
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) []
let !modified' = modified || wasmodified
go h modified' (subtree : c) intree is'
_ -> error ("unexpected object type \"" ++ LsTree.typeobj i ++ "\"")
| otherwise = return (c, wasmodified, i:is)
2016-03-11 23:29:43 +00:00
adjustlist h 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 $
filter (\i -> underhere i && not (inl i)) rest
addunderhere' <- liftIO $ mapM (recordSubTree h) addunderhere
return (addunderhere'++l')
removeset = S.fromList $ map (normalise . gitPath) removefiles
removed (TreeBlob f _ _) = S.member (normalise (gitPath f)) removeset
2016-03-11 20:30:06 +00:00
removed _ = False
{- 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
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
_ -> parseerr ("unexpected object type \"" ++ LsTree.typeobj i ++ "\"")
| 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
gitPath :: t -> FilePath
instance GitPath FilePath where
gitPath = id
instance GitPath TopFilePath where
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 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
2016-03-11 18:08:06 +00:00
2016-03-11 23:29:43 +00:00
inTopTree :: GitPath t => t -> Bool
inTopTree = inTree "."
2016-03-11 20:30:06 +00:00
2016-03-11 23:29:43 +00:00
inTree :: (GitPath t, GitPath f) => t -> f -> Bool
inTree t f = gitPath t == takeDirectory (gitPath f)
beneathSubTree :: (GitPath t, GitPath f) => t -> f -> Bool
beneathSubTree t f = prefix `isPrefixOf` normalise (gitPath f)
2016-03-11 23:29:43 +00:00
where
tp = gitPath t
prefix = if null tp then tp else addTrailingPathSeparator (normalise tp)