summaryrefslogtreecommitdiff
path: root/Branch.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2011-06-21 14:29:09 -0400
committerGravatar Joey Hess <joey@kitenet.net>2011-06-21 14:33:59 -0400
commitc03af0ed0c6530742206740e8b3fc75f5f959325 (patch)
tree344320bec4d9e83e901e00f3ed99aea368f16a0d /Branch.hs
parente735d459b531246798622994718eaccfcf0086ab (diff)
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.
Diffstat (limited to 'Branch.hs')
-rw-r--r--Branch.hs50
1 files changed, 50 insertions, 0 deletions
diff --git a/Branch.hs b/Branch.hs
new file mode 100644
index 000000000..db8dc23da
--- /dev/null
+++ b/Branch.hs
@@ -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