buildImportTrees is fully working

buildImportCommit not yet tested
This commit is contained in:
Joey Hess 2019-02-22 12:41:17 -04:00
parent 7af55de83c
commit bab6c570b0
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
4 changed files with 104 additions and 39 deletions

View file

@ -5,15 +5,22 @@
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
module Annex.Import (buildImportCommit) where module Annex.Import (buildImportCommit, buildImportTrees) where
import Annex.Common import Annex.Common
import Types.Import import Types.Import
import Types.Remote (uuid)
import Git.Types import Git.Types
import Git.Tree import Git.Tree
import Git.Branch import Git.Sha
import Git.FilePath import Git.FilePath
import qualified Git.Ref
import qualified Git.Branch
import qualified Annex
import Annex.Link import Annex.Link
import Annex.LockFile
import Logs.Export
import Database.Export
{- Builds a commit on top of a basecommit that reflects changes to the {- Builds a commit on top of a basecommit that reflects changes to the
- content of a remote. When there are no changes to commit, returns Nothing. - content of a remote. When there are no changes to commit, returns Nothing.
@ -22,50 +29,94 @@ import Annex.Link
- builds a corresponding tree of git commits. - builds a corresponding tree of git commits.
- -
- After importing from a remote, exporting the same thing back to the - After importing from a remote, exporting the same thing back to the
- remote should be a no-op. So, the export log is updated to reflect the - remote should be a no-op. So, the export log and database are
- imported tree. - updated to reflect the imported tree.
- -
- The files are imported to the top of the git repository, unless a - The files are imported to the top of the git repository, unless a
- subdir is specified, then the import will only affect the contents of - subdir is specified, then the import will only affect the contents of
- the subdir. - the subdir.
- -
- This does not import any content from a remote. But since it needs the - This does not import any content from a remote. But since it needs the
- Key of imported files to be known, its caller will have to download - Key of imported files to be known, its caller will have to first download
- new files in order to generate keys for them. - new files in order to generate keys for them.
-} -}
buildImportCommit buildImportCommit
:: Ref :: Remote
-> Maybe FilePath -> Ref
-> Maybe TopFilePath
-> ImportableContents Key -> ImportableContents Key
-> CommitMode -> Git.Branch.CommitMode
-> String -> String
-> Annex (Maybe Ref) -> Annex (Either String (Maybe Ref))
buildImportCommit basecommit subdir importable commitmode commitmessage = do buildImportCommit remote basecommit subdir importable commitmode commitmessage =
go =<< buildImportTrees basetree importable inRepo (Git.Ref.tree basecommit) >>= \case
Nothing -> return $
Left $ "Cannot find tree for " ++ fromRef basecommit
Just basetree -> do
imported@(History finaltree _) <-
buildImportTrees basetree subdir importable
mkcommits basetree imported >>= \case
Nothing -> return (Right Nothing)
Just finalcommit -> do
updateexportdb finaltree
updateexportlog finaltree
return (Right (Just finalcommit))
where where
go (History importedtree hs) = do mkcommits basetree (History importedtree hs) = do
parents <- mapM go hs parents <- catMaybes <$> mapM (mkcommits basetree) hs
if basetree == importedtree && null parents
inRepo $ commitTree commitmode commitmessage parents tree then return Nothing
else do
commit <- inRepo $ Git.Branch.commitTree commitmode commitmessage parents importedtree
return (Just commit)
updateexportdb importedtree =
withExclusiveLock (gitAnnexExportLock (uuid remote)) $ do
db <- openDb (uuid remote)
prevtree <- liftIO $ fromMaybe emptyTree
<$> getExportTreeCurrent db
when (importedtree /= prevtree) $ do
updateExportTree db prevtree importedtree
liftIO $ recordExportTreeCurrent db importedtree
-- TODO: addExportedLocation etc
liftIO $ flushDbQueue db
updateexportlog importedtree = do
old <- getExport (uuid remote)
recordExport (uuid remote) $ ExportChange
{ oldTreeish = exportedTreeishes old
, newTreeish = importedtree
}
data History t = History t [History t] data History t = History t [History t]
deriving (Show)
{- Builds a history of git trees reflecting the ImportableContents. -} {- Builds a history of git trees reflecting the ImportableContents.
-
- When a subdir is provided, imported tree is grafted into the basetree at
- that location, replacing any object that was there.
-}
buildImportTrees buildImportTrees
:: Maybe FilePath :: Ref
-> Maybe TopFilePath
-> ImportableContents Key -> ImportableContents Key
-> Annex (History Sha) -> Annex (History Sha)
buildImportTrees subdir i = History buildImportTrees basetree msubdir importable = History
<$> go (importableContents i) <$> (go (importableContents importable) =<< Annex.gitRepo)
<*> mapM (buildImportTrees subdir basetree) (importableHistory i) <*> mapM (buildImportTrees basetree msubdir) (importableHistory importable)
where where
go ls = do go ls repo = withMkTreeHandle repo $ \hdl -> do
is <- mapM mktreeitem ls importtree <- liftIO . recordTree' hdl
inRepo $ recordTree (treeItemsToTree is) . treeItemsToTree
=<< mapM mktreeitem ls
case msubdir of
Nothing -> return importtree
Just subdir -> liftIO $
graftTree' importtree subdir basetree repo hdl
mktreeitem (loc, k) = do mktreeitem (loc, k) = do
let lf = fromImportLocation loc let lf = fromImportLocation loc
let topf = asTopFilePath $ maybe lf (</> lf) subdir let treepath = asTopFilePath lf
let topf = asTopFilePath $
maybe lf (\sd -> getTopFilePath sd </> lf) msubdir
relf <- fromRepo $ fromTopFilePath topf relf <- fromRepo $ fromTopFilePath topf
symlink <- calcRepo $ gitAnnexLink relf k symlink <- calcRepo $ gitAnnexLink relf k
linksha <- hashSymlink symlink linksha <- hashSymlink symlink
return $ TreeItem topf (fromTreeItemType TreeSymlink) linksha return $ TreeItem treepath (fromTreeItemType TreeSymlink) linksha

View file

@ -42,12 +42,12 @@ lsTree :: LsTreeMode -> Ref -> Repo -> IO ([TreeItem], IO Bool)
lsTree = lsTree' [] lsTree = lsTree' []
lsTree' :: [CommandParam] -> LsTreeMode -> Ref -> Repo -> IO ([TreeItem], IO Bool) lsTree' :: [CommandParam] -> LsTreeMode -> Ref -> Repo -> IO ([TreeItem], IO Bool)
lsTree' ps mode t repo = do lsTree' ps lsmode t repo = do
(l, cleanup) <- pipeNullSplit (lsTreeParams mode t ps) repo (l, cleanup) <- pipeNullSplit (lsTreeParams lsmode t ps) repo
return (map parseLsTree l, cleanup) return (map parseLsTree l, cleanup)
lsTreeParams :: LsTreeMode -> Ref -> [CommandParam] -> [CommandParam] lsTreeParams :: LsTreeMode -> Ref -> [CommandParam] -> [CommandParam]
lsTreeParams mode r ps = lsTreeParams lsmode r ps =
[ Param "ls-tree" [ Param "ls-tree"
, Param "--full-tree" , Param "--full-tree"
, Param "-z" , Param "-z"
@ -56,7 +56,7 @@ lsTreeParams mode r ps =
, File $ fromRef r , File $ fromRef r
] ]
where where
recursiveparams = case mode of recursiveparams = case lsmode of
LsTreeRecursive -> [ Param "-r" ] LsTreeRecursive -> [ Param "-r" ]
LsTreeNonRecursive -> [] LsTreeNonRecursive -> []

View file

@ -1,6 +1,6 @@
{- git trees {- git trees
- -
- Copyright 2016 Joey Hess <id@joeyh.name> - Copyright 2016-2019 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU GPL version 3 or higher. - Licensed under the GNU GPL version 3 or higher.
-} -}
@ -12,10 +12,13 @@ module Git.Tree (
TreeContent(..), TreeContent(..),
getTree, getTree,
recordTree, recordTree,
recordTree',
TreeItem(..), TreeItem(..),
treeItemsToTree, treeItemsToTree,
adjustTree, adjustTree,
graftTree, graftTree,
graftTree',
withMkTreeHandle,
treeMode, treeMode,
) where ) where
@ -245,14 +248,22 @@ graftTree
-> Repo -> Repo
-> IO Sha -> IO Sha
graftTree subtree graftloc basetree repo = graftTree subtree graftloc basetree repo =
withMkTreeHandle repo $ withMkTreeHandle repo $ graftTree' subtree graftloc basetree repo
go basetree graftdirs
graftTree'
:: Sha
-> TopFilePath
-> Sha
-> Repo
-> MkTreeHandle
-> IO Sha
graftTree' subtree graftloc basetree repo hdl = go basetree graftdirs
where where
go tsha (topmostgraphdir:restgraphdirs) h = do go tsha (topmostgraphdir:restgraphdirs) = do
Tree t <- getTree LsTree.LsTreeNonRecursive tsha repo Tree t <- getTree LsTree.LsTreeNonRecursive tsha repo
t' <- case partition isabovegraft t of t' <- case partition isabovegraft t of
([], _) -> do ([], _) -> do
graft <- graftin h (topmostgraphdir:restgraphdirs) graft <- graftin (topmostgraphdir:restgraphdirs)
return (graft:t) return (graft:t)
-- normally there can only be one matching item -- normally there can only be one matching item
-- in the tree, but it's theoretically possible -- in the tree, but it's theoretically possible
@ -264,16 +275,16 @@ graftTree subtree graftloc basetree repo =
| null restgraphdirs -> return $ | null restgraphdirs -> return $
RecordedSubTree tloc subtree [] RecordedSubTree tloc subtree []
| otherwise -> do | otherwise -> do
tsha'' <- go tsha' restgraphdirs h tsha'' <- go tsha' restgraphdirs
return $ RecordedSubTree tloc tsha'' [] return $ RecordedSubTree tloc tsha'' []
_ -> graftin h (topmostgraphdir:restgraphdirs) _ -> graftin (topmostgraphdir:restgraphdirs)
return (newshas ++ rest) return (newshas ++ rest)
mkTree h t' mkTree hdl t'
go tsha [] h = return subtree go _ [] = return subtree
isabovegraft i = beneathSubTree i graftloc || gitPath i == gitPath graftloc isabovegraft i = beneathSubTree i graftloc || gitPath i == gitPath graftloc
graftin h t = recordSubTree h $ graftin' t graftin t = recordSubTree hdl $ graftin' t
graftin' [] = RecordedSubTree graftloc subtree [] graftin' [] = RecordedSubTree graftloc subtree []
graftin' (d:rest) graftin' (d:rest)
| d == graftloc = graftin' [] | d == graftloc = graftin' []

View file

@ -19,6 +19,9 @@ import Utility.FileSystemEncoding
- location on the remote. -} - location on the remote. -}
type ImportLocation = ExportLocation type ImportLocation = ExportLocation
mkImportLocation :: FilePath -> ImportLocation
mkImportLocation = mkExportLocation
fromImportLocation :: ImportLocation -> FilePath fromImportLocation :: ImportLocation -> FilePath
fromImportLocation = fromExportLocation fromImportLocation = fromExportLocation