code to update a git-annex branch

There is no suitable git hook to run code when pulling changes that
might need to be merged into the git-annex branch. The post-merge hook
is only run when changes are merged into HEAD, and it's possible,
and indeed likely that many pulls will only have changes in git-annex,
but not in HEAD, and not trigger it.

So, git-annex will have to take care to update the branch before reading
from it, to make sure it has merged in current info from remotes. Happily,
this can be done quite inexpensively, just a git-show-ref to list
branches, and a minimalized git-log to see if there are unmerged changes
on the branches. To further speed up, it will be done only once per
git-annex run, max.
This commit is contained in:
Joey Hess 2011-06-21 14:29:09 -04:00
parent e735d459b5
commit c03af0ed0c
2 changed files with 52 additions and 0 deletions

View file

@ -39,6 +39,7 @@ data AnnexState = AnnexState
, quiet :: Bool , quiet :: Bool
, force :: Bool , force :: Bool
, fast :: Bool , fast :: Bool
, updated :: Bool
, forcebackend :: Maybe String , forcebackend :: Maybe String
, forcenumcopies :: Maybe Int , forcenumcopies :: Maybe Int
, defaultkey :: Maybe String , defaultkey :: Maybe String
@ -59,6 +60,7 @@ newState allbackends gitrepo = AnnexState
, quiet = False , quiet = False
, force = False , force = False
, fast = False , fast = False
, updated = False
, forcebackend = Nothing , forcebackend = Nothing
, forcenumcopies = Nothing , forcenumcopies = Nothing
, defaultkey = Nothing , defaultkey = Nothing

50
Branch.hs Normal file
View file

@ -0,0 +1,50 @@
{- git-annex branch management
-
- Copyright 2011 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Branch where
import Control.Monad (unless)
import Control.Monad.State (liftIO)
import GitUnionMerge
import GitRepo as Git
import qualified Annex
import Utility
import Types
import Messages
name :: String
name = "git-annex"
fullname :: String
fullname = "refs/heads/" ++ name
{- Ensures that the branch is up-to-date; should be called before
- data is read from it. Runs only once per git-annex run. -}
update :: Annex ()
update = do
updated <- Annex.getState Annex.updated
unless updated $ do
g <- Annex.gitRepo
refs <- liftIO $ Git.pipeRead g [Param "show-ref", Param name]
mapM_ updateRef $ map (last . words) (lines refs)
Annex.changeState $ \s -> s { Annex.updated = True }
{- Ensures that a given ref has been merged into the local git-annex branch. -}
updateRef :: String -> Annex ()
updateRef ref
| ref == fullname = return ()
| otherwise = do
g <- Annex.gitRepo
diffs <- liftIO $ Git.pipeRead g [
Param "log",
Param (name++".."++ref),
Params "--oneline -n1"
]
unless (null diffs) $ do
showSideAction "merging " ++ ref ++ " into " ++ name ++ "..."
liftIO $ unionMerge g fullname ref fullname