unannex, uninit: Avoid committing after every file is unannexed, for massive speedup.
pre-commit hook lock added, so unannex can prevent the hook from running in a confusing state. This commit was sponsored by Fredrik Hammar
This commit is contained in:
parent
4ae2c99da8
commit
7dc6804154
4 changed files with 74 additions and 22 deletions
|
@ -5,6 +5,8 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
|
{-# LANGUAGE CPP #-}
|
||||||
|
|
||||||
module Command.PreCommit where
|
module Command.PreCommit where
|
||||||
|
|
||||||
import Common.Annex
|
import Common.Annex
|
||||||
|
@ -16,11 +18,17 @@ import Annex.Direct
|
||||||
import Annex.Hook
|
import Annex.Hook
|
||||||
import Annex.View
|
import Annex.View
|
||||||
import Annex.View.ViewedFile
|
import Annex.View.ViewedFile
|
||||||
|
import Annex.Perms
|
||||||
|
import Annex.Exception
|
||||||
import Logs.View
|
import Logs.View
|
||||||
import Logs.MetaData
|
import Logs.MetaData
|
||||||
import Types.View
|
import Types.View
|
||||||
import Types.MetaData
|
import Types.MetaData
|
||||||
|
|
||||||
|
#ifdef mingw32_HOST_OS
|
||||||
|
import Utility.WinLock
|
||||||
|
#endif
|
||||||
|
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
|
|
||||||
def :: [Command]
|
def :: [Command]
|
||||||
|
@ -28,7 +36,7 @@ def = [command "pre-commit" paramPaths seek SectionPlumbing
|
||||||
"run by git pre-commit hook"]
|
"run by git pre-commit hook"]
|
||||||
|
|
||||||
seek :: CommandSeek
|
seek :: CommandSeek
|
||||||
seek ps = ifM isDirect
|
seek ps = lockPreCommitHook $ ifM isDirect
|
||||||
( do
|
( do
|
||||||
-- update direct mode mappings for committed files
|
-- update direct mode mappings for committed files
|
||||||
withWords startDirect ps
|
withWords startDirect ps
|
||||||
|
@ -82,3 +90,22 @@ showMetaDataChange = showLongNote . unlines . concatMap showmeta . fromMetaData
|
||||||
showset v
|
showset v
|
||||||
| isSet v = "+"
|
| isSet v = "+"
|
||||||
| otherwise = "-"
|
| otherwise = "-"
|
||||||
|
|
||||||
|
{- Takes exclusive lock; blocks until available. -}
|
||||||
|
lockPreCommitHook :: Annex a -> Annex a
|
||||||
|
lockPreCommitHook a = do
|
||||||
|
lockfile <- fromRepo gitAnnexPreCommitLock
|
||||||
|
createAnnexDirectory $ takeDirectory lockfile
|
||||||
|
mode <- annexFileMode
|
||||||
|
bracketIO (lock lockfile mode) unlock (const a)
|
||||||
|
where
|
||||||
|
#ifndef mingw32_HOST_OS
|
||||||
|
lock lockfile mode = do
|
||||||
|
l <- liftIO $ noUmask mode $ createFile lockfile mode
|
||||||
|
liftIO $ waitToSetLock l (WriteLock, AbsoluteSeek, 0, 0)
|
||||||
|
return l
|
||||||
|
unlock = closeFd
|
||||||
|
#else
|
||||||
|
lock lockfile _mode = liftIO $ waitToLock $ lockExclusive lockfile
|
||||||
|
unlock = dropLock
|
||||||
|
#endif
|
||||||
|
|
|
@ -16,15 +16,47 @@ import qualified Annex
|
||||||
import Annex.Content
|
import Annex.Content
|
||||||
import Annex.Content.Direct
|
import Annex.Content.Direct
|
||||||
import qualified Git.Command
|
import qualified Git.Command
|
||||||
import qualified Git.LsFiles as LsFiles
|
import qualified Git.Ref
|
||||||
|
import qualified Git.DiffTree as DiffTree
|
||||||
import Utility.CopyFile
|
import Utility.CopyFile
|
||||||
|
import Command.PreCommit (lockPreCommitHook)
|
||||||
|
|
||||||
def :: [Command]
|
def :: [Command]
|
||||||
def = [command "unannex" paramPaths seek SectionUtility
|
def = [command "unannex" paramPaths seek SectionUtility
|
||||||
"undo accidential add command"]
|
"undo accidential add command"]
|
||||||
|
|
||||||
seek :: CommandSeek
|
seek :: CommandSeek
|
||||||
seek = withFilesInGit $ whenAnnexed start
|
seek = wrapUnannex . (withFilesInGit $ whenAnnexed start)
|
||||||
|
|
||||||
|
wrapUnannex :: Annex a -> Annex a
|
||||||
|
wrapUnannex a = ifM isDirect
|
||||||
|
( a
|
||||||
|
{- Run with the pre-commit hook disabled, to avoid confusing
|
||||||
|
- behavior if an unannexed file is added back to git as
|
||||||
|
- a normal, non-annexed file and then committed.
|
||||||
|
- Otherwise, the pre-commit hook would think that the file
|
||||||
|
- has been unlocked and needs to be re-annexed.
|
||||||
|
-
|
||||||
|
- At the end, make a commit removing the unannexed files.
|
||||||
|
-}
|
||||||
|
, ifM cleanindex
|
||||||
|
( lockPreCommitHook $ commit `after` a
|
||||||
|
, error "Cannot proceed with uncommitted changes staged in the index. Recommend you: git commit"
|
||||||
|
)
|
||||||
|
)
|
||||||
|
where
|
||||||
|
commit = inRepo $ Git.Command.run
|
||||||
|
[ Param "commit"
|
||||||
|
, Param "-q"
|
||||||
|
, Param "--allow-empty"
|
||||||
|
, Param "--no-verify"
|
||||||
|
, Param "-m", Param "content removed from git annex"
|
||||||
|
]
|
||||||
|
cleanindex = do
|
||||||
|
(diff, cleanup) <- inRepo $ DiffTree.diffIndex Git.Ref.headRef
|
||||||
|
if null diff
|
||||||
|
then void (liftIO cleanup) >> return True
|
||||||
|
else void (liftIO cleanup) >> return False
|
||||||
|
|
||||||
start :: FilePath -> (Key, Backend) -> CommandStart
|
start :: FilePath -> (Key, Backend) -> CommandStart
|
||||||
start file (key, _) = stopUnless (inAnnex key) $ do
|
start file (key, _) = stopUnless (inAnnex key) $ do
|
||||||
|
@ -36,26 +68,7 @@ start file (key, _) = stopUnless (inAnnex key) $ do
|
||||||
performIndirect :: FilePath -> Key -> CommandPerform
|
performIndirect :: FilePath -> Key -> CommandPerform
|
||||||
performIndirect file key = do
|
performIndirect file key = do
|
||||||
liftIO $ removeFile file
|
liftIO $ removeFile file
|
||||||
|
|
||||||
-- git rm deletes empty directory without --cached
|
|
||||||
inRepo $ Git.Command.run [Params "rm --cached --force --quiet --", File file]
|
inRepo $ Git.Command.run [Params "rm --cached --force --quiet --", File file]
|
||||||
|
|
||||||
-- If the file was already committed, it is now staged for removal.
|
|
||||||
-- Commit that removal now, to avoid later confusing the
|
|
||||||
-- pre-commit hook, if this file is later added back to
|
|
||||||
-- git as a normal non-annexed file, to thinking that the
|
|
||||||
-- file has been unlocked and needs to be re-annexed.
|
|
||||||
(s, reap) <- inRepo $ LsFiles.staged [file]
|
|
||||||
unless (null s) $
|
|
||||||
inRepo $ Git.Command.run
|
|
||||||
[ Param "commit"
|
|
||||||
, Param "-q"
|
|
||||||
, Param "--no-verify"
|
|
||||||
, Param "-m", Param "content removed from git annex"
|
|
||||||
, Param "--", File file
|
|
||||||
]
|
|
||||||
void $ liftIO reap
|
|
||||||
|
|
||||||
next $ cleanupIndirect file key
|
next $ cleanupIndirect file key
|
||||||
|
|
||||||
cleanupIndirect :: FilePath -> Key -> CommandCleanup
|
cleanupIndirect :: FilePath -> Key -> CommandCleanup
|
||||||
|
|
|
@ -41,6 +41,7 @@ module Locations (
|
||||||
gitAnnexMergeDir,
|
gitAnnexMergeDir,
|
||||||
gitAnnexJournalDir,
|
gitAnnexJournalDir,
|
||||||
gitAnnexJournalLock,
|
gitAnnexJournalLock,
|
||||||
|
gitAnnexPreCommitLock,
|
||||||
gitAnnexIndex,
|
gitAnnexIndex,
|
||||||
gitAnnexIndexStatus,
|
gitAnnexIndexStatus,
|
||||||
gitAnnexViewIndex,
|
gitAnnexViewIndex,
|
||||||
|
@ -257,6 +258,10 @@ gitAnnexJournalDir r = addTrailingPathSeparator $ gitAnnexDir r </> "journal"
|
||||||
gitAnnexJournalLock :: Git.Repo -> FilePath
|
gitAnnexJournalLock :: Git.Repo -> FilePath
|
||||||
gitAnnexJournalLock r = gitAnnexDir r </> "journal.lck"
|
gitAnnexJournalLock r = gitAnnexDir r </> "journal.lck"
|
||||||
|
|
||||||
|
{- Lock file for the pre-commit hook. -}
|
||||||
|
gitAnnexPreCommitLock :: Git.Repo -> FilePath
|
||||||
|
gitAnnexPreCommitLock r = gitAnnexDir r </> "precommit.lck"
|
||||||
|
|
||||||
{- .git/annex/index is used to stage changes to the git-annex branch -}
|
{- .git/annex/index is used to stage changes to the git-annex branch -}
|
||||||
gitAnnexIndex :: Git.Repo -> FilePath
|
gitAnnexIndex :: Git.Repo -> FilePath
|
||||||
gitAnnexIndex r = gitAnnexDir r </> "index"
|
gitAnnexIndex r = gitAnnexDir r </> "index"
|
||||||
|
|
7
debian/changelog
vendored
7
debian/changelog
vendored
|
@ -1,3 +1,10 @@
|
||||||
|
git-annex (5.20140321) UNRELEASED; urgency=medium
|
||||||
|
|
||||||
|
* unannex, uninit: Avoid committing after every file is unannexed,
|
||||||
|
for massive speedup.
|
||||||
|
|
||||||
|
-- Joey Hess <joeyh@debian.org> Fri, 21 Mar 2014 14:08:41 -0400
|
||||||
|
|
||||||
git-annex (5.20140320) unstable; urgency=medium
|
git-annex (5.20140320) unstable; urgency=medium
|
||||||
|
|
||||||
* Fix zombie leak and general inneficiency when copying files to a
|
* Fix zombie leak and general inneficiency when copying files to a
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue