2011-06-21 16:08:09 -04:00
|
|
|
{- management of the git-annex branch
|
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.
2011-06-21 14:29:09 -04:00
|
|
|
-
|
|
|
|
- Copyright 2011 Joey Hess <joey@kitenet.net>
|
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
|
|
-}
|
|
|
|
|
2011-06-21 16:08:09 -04:00
|
|
|
module Branch (
|
2011-06-22 15:58:30 -04:00
|
|
|
create,
|
2011-06-21 16:08:09 -04:00
|
|
|
update,
|
2011-06-21 19:11:55 -04:00
|
|
|
get,
|
|
|
|
change,
|
|
|
|
commit
|
2011-06-21 16:08:09 -04:00
|
|
|
) where
|
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.
2011-06-21 14:29:09 -04:00
|
|
|
|
2011-06-22 15:58:30 -04:00
|
|
|
import Control.Monad (unless, when, liftM)
|
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.
2011-06-21 14:29:09 -04:00
|
|
|
import Control.Monad.State (liftIO)
|
2011-06-21 17:39:45 -04:00
|
|
|
import System.FilePath
|
|
|
|
import System.Directory
|
|
|
|
import Data.String.Utils
|
|
|
|
import System.Cmd.Utils
|
2011-06-21 19:52:40 -04:00
|
|
|
import Data.Maybe
|
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.
2011-06-21 14:29:09 -04:00
|
|
|
|
2011-06-22 15:58:30 -04:00
|
|
|
import Types.BranchState
|
2011-06-21 17:39:45 -04:00
|
|
|
import qualified GitRepo as Git
|
2011-06-21 19:11:55 -04:00
|
|
|
import qualified GitUnionMerge
|
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.
2011-06-21 14:29:09 -04:00
|
|
|
import qualified Annex
|
|
|
|
import Utility
|
|
|
|
import Types
|
|
|
|
import Messages
|
|
|
|
|
2011-06-21 17:39:45 -04:00
|
|
|
{- Name of the branch that is used to store git-annex's information. -}
|
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.
2011-06-21 14:29:09 -04:00
|
|
|
name :: String
|
|
|
|
name = "git-annex"
|
|
|
|
|
2011-06-21 17:39:45 -04:00
|
|
|
{- Fully qualified name of the branch. -}
|
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.
2011-06-21 14:29:09 -04:00
|
|
|
fullname :: String
|
|
|
|
fullname = "refs/heads/" ++ name
|
|
|
|
|
2011-06-21 17:39:45 -04:00
|
|
|
{- A separate index file for the branch. -}
|
|
|
|
index :: Git.Repo -> FilePath
|
|
|
|
index g = Git.workTree g </> Git.gitDir g </> "index." ++ name
|
|
|
|
|
|
|
|
{- Populates the branch's index file with the current branch contents.
|
|
|
|
-
|
|
|
|
- Usually, this is only done when the index doesn't yet exist, and
|
|
|
|
- the index is used to build up changes to be commited to the branch.
|
|
|
|
-}
|
2011-06-22 15:58:30 -04:00
|
|
|
genIndex :: Git.Repo -> IO ()
|
|
|
|
genIndex g = do
|
2011-06-21 17:39:45 -04:00
|
|
|
ls <- Git.pipeNullSplit g $
|
|
|
|
map Param ["ls-tree", "-z", "-r", "--full-tree", fullname]
|
|
|
|
forceSuccess =<< Git.pipeWrite g
|
|
|
|
(map Param ["update-index", "-z", "--index-info"])
|
|
|
|
(join "\0" ls)
|
|
|
|
|
|
|
|
{- Runs an action using the branch's index file. -}
|
|
|
|
withIndex :: Annex a -> Annex a
|
|
|
|
withIndex a = do
|
|
|
|
g <- Annex.gitRepo
|
|
|
|
let f = index g
|
|
|
|
liftIO $ Git.useIndex f
|
|
|
|
|
|
|
|
e <- liftIO $ doesFileExist f
|
2011-06-22 15:58:30 -04:00
|
|
|
unless e $ liftIO $ genIndex g
|
2011-06-21 17:39:45 -04:00
|
|
|
|
|
|
|
r <- a
|
|
|
|
liftIO $ Git.useDefaultIndex
|
|
|
|
return r
|
|
|
|
|
2011-06-22 15:58:30 -04:00
|
|
|
withIndexUpdate :: Annex a -> Annex a
|
|
|
|
withIndexUpdate a = update >> withIndex a
|
|
|
|
|
|
|
|
getState :: Annex BranchState
|
|
|
|
getState = Annex.getState Annex.branchstate
|
|
|
|
|
|
|
|
setState :: BranchState -> Annex ()
|
|
|
|
setState state = Annex.changeState $ \s -> s { Annex.branchstate = state }
|
|
|
|
|
2011-06-22 14:18:49 -04:00
|
|
|
setCache :: FilePath -> String -> Annex ()
|
2011-06-22 15:58:30 -04:00
|
|
|
setCache file content = do
|
|
|
|
state <- getState
|
|
|
|
setState state { cachedFile = Just file, cachedContent = content }
|
|
|
|
|
|
|
|
setCacheChanged :: FilePath -> String -> Annex ()
|
|
|
|
setCacheChanged file content = do
|
|
|
|
state <- getState
|
|
|
|
setState state { cachedFile = Just file, cachedContent = content, branchChanged = True }
|
2011-06-22 14:18:49 -04:00
|
|
|
|
|
|
|
invalidateCache :: Annex ()
|
2011-06-22 15:58:30 -04:00
|
|
|
invalidateCache = do
|
|
|
|
state <- getState
|
|
|
|
setState state { cachedFile = Nothing, cachedContent = "" }
|
|
|
|
|
|
|
|
getCache :: FilePath -> Annex (Maybe String)
|
|
|
|
getCache file = getState >>= handle
|
|
|
|
where
|
|
|
|
handle state
|
|
|
|
| cachedFile state == Just file =
|
|
|
|
return $ Just $ cachedContent state
|
|
|
|
| otherwise = return Nothing
|
|
|
|
|
|
|
|
{- Creates the branch, if it does not already exist. -}
|
|
|
|
create :: Annex ()
|
|
|
|
create = do
|
|
|
|
exists <- refexists fullname
|
|
|
|
unless exists $ do
|
|
|
|
g <- Annex.gitRepo
|
|
|
|
inorigin <- refexists origin
|
|
|
|
if inorigin
|
|
|
|
then liftIO $ Git.run g "branch" [Param name, Param origin]
|
|
|
|
else liftIO $ do
|
|
|
|
let f = index g
|
|
|
|
liftIO $ Git.useIndex f
|
|
|
|
GitUnionMerge.commit g "branch created" fullname []
|
|
|
|
liftIO $ Git.useDefaultIndex
|
|
|
|
where
|
|
|
|
origin = "origin/" ++ name
|
|
|
|
refexists ref = do
|
|
|
|
g <- Annex.gitRepo
|
|
|
|
liftIO $ Git.runBool g "show-ref"
|
|
|
|
[Param "--verify", Param "-q", Param ref]
|
2011-06-22 14:18:49 -04:00
|
|
|
|
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.
2011-06-21 14:29:09 -04:00
|
|
|
{- 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
|
2011-06-22 15:58:30 -04:00
|
|
|
state <- Annex.getState Annex.branchstate
|
|
|
|
unless (branchUpdated state) $ withIndex $ do
|
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.
2011-06-21 14:29:09 -04:00
|
|
|
g <- Annex.gitRepo
|
2011-06-21 19:52:40 -04:00
|
|
|
r <- liftIO $ Git.pipeRead g [Param "show-ref", Param name]
|
|
|
|
let refs = map (last . words) (lines r)
|
|
|
|
updated <- catMaybes `liftM` mapM updateRef refs
|
|
|
|
unless (null updated) $ liftIO $
|
|
|
|
GitUnionMerge.commit g "update" fullname
|
|
|
|
(fullname:updated)
|
2011-06-22 15:58:30 -04:00
|
|
|
Annex.changeState $ \s -> s { Annex.branchstate = state { branchUpdated = True } }
|
2011-06-22 14:18:49 -04:00
|
|
|
invalidateCache
|
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.
2011-06-21 14:29:09 -04:00
|
|
|
|
2011-06-21 19:52:40 -04:00
|
|
|
{- Ensures that a given ref has been merged into the index. -}
|
|
|
|
updateRef :: String -> Annex (Maybe String)
|
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.
2011-06-21 14:29:09 -04:00
|
|
|
updateRef ref
|
2011-06-21 19:52:40 -04:00
|
|
|
| ref == fullname = return Nothing
|
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.
2011-06-21 14:29:09 -04:00
|
|
|
| otherwise = do
|
|
|
|
g <- Annex.gitRepo
|
|
|
|
diffs <- liftIO $ Git.pipeRead g [
|
|
|
|
Param "log",
|
|
|
|
Param (name++".."++ref),
|
|
|
|
Params "--oneline -n1"
|
|
|
|
]
|
2011-06-21 19:52:40 -04:00
|
|
|
if (null diffs)
|
|
|
|
then return Nothing
|
|
|
|
else do
|
|
|
|
showSideAction $ "merging " ++ ref ++ " into " ++ name ++ "..."
|
|
|
|
-- By passing only one ref, it is actually
|
|
|
|
-- merged into the index, preserving any
|
|
|
|
-- changes that may already be staged.
|
|
|
|
liftIO $ GitUnionMerge.merge g [ref]
|
|
|
|
return $ Just ref
|
2011-06-21 16:08:09 -04:00
|
|
|
|
2011-06-21 17:39:45 -04:00
|
|
|
{- Stages the content of a file into the branch's index. -}
|
2011-06-21 16:08:09 -04:00
|
|
|
change :: FilePath -> String -> Annex ()
|
2011-06-21 19:11:55 -04:00
|
|
|
change file content = do
|
2011-06-21 17:39:45 -04:00
|
|
|
g <- Annex.gitRepo
|
|
|
|
sha <- liftIO $ Git.hashObject g content
|
|
|
|
withIndex $ liftIO $ Git.run g "update-index"
|
2011-06-22 14:18:49 -04:00
|
|
|
[ Param "--add", Param "--cacheinfo", Param "100644",
|
2011-06-21 17:39:45 -04:00
|
|
|
Param sha, File file]
|
2011-06-22 15:58:30 -04:00
|
|
|
setCacheChanged file content
|
2011-06-21 16:08:09 -04:00
|
|
|
|
2011-06-22 15:58:30 -04:00
|
|
|
{- Commits any staged changes to the branch. -}
|
2011-06-21 17:39:45 -04:00
|
|
|
commit :: String -> Annex ()
|
2011-06-22 15:58:30 -04:00
|
|
|
commit message = do
|
|
|
|
state <- getState
|
|
|
|
when (branchChanged state) $ do
|
|
|
|
g <- Annex.gitRepo
|
|
|
|
withIndex $ liftIO $
|
|
|
|
GitUnionMerge.commit g message fullname [fullname]
|
2011-06-21 17:39:45 -04:00
|
|
|
|
|
|
|
{- Gets the content of a file on the branch, or content staged in the index
|
|
|
|
- if it's newer. Returns an empty string if the file didn't exist yet. -}
|
|
|
|
get :: FilePath -> Annex String
|
2011-06-22 15:58:30 -04:00
|
|
|
get file = do
|
|
|
|
cached <- getCache file
|
|
|
|
case cached of
|
|
|
|
Just content -> return content
|
|
|
|
Nothing -> withIndexUpdate $ do
|
|
|
|
g <- Annex.gitRepo
|
|
|
|
content <- liftIO $ catch (cat g) (const $ return "")
|
|
|
|
setCache file content
|
|
|
|
return content
|
2011-06-21 17:39:45 -04:00
|
|
|
where
|
2011-06-22 15:58:30 -04:00
|
|
|
cat g = Git.pipeRead g [Param "cat-file", Param "blob", catfile]
|
2011-06-21 17:39:45 -04:00
|
|
|
catfile = Param $ ':':file
|