unused: --used-refspec can now be configured to look at refs in the reflog. This provides a way to not consider old versions of files to be unused after they have reached a specified age, when the old refs in the reflog expire.
May be slow.
This commit is contained in:
parent
a51b98cdd5
commit
b11d2f5a8a
7 changed files with 40 additions and 13 deletions
|
@ -210,7 +210,7 @@ getHistorical :: RefDate -> FilePath -> Annex String
|
|||
getHistorical date file =
|
||||
-- This check avoids some ugly error messages when the reflog
|
||||
-- is empty.
|
||||
ifM (null <$> inRepo (Git.RefLog.get' [Param "-n1"] fullname))
|
||||
ifM (null <$> inRepo (Git.RefLog.get' [Param "-n1"] (Just fullname)))
|
||||
( error ("No reflog for " ++ fromRef fullname)
|
||||
, getRef (Git.Ref.dateRef fullname date) file
|
||||
)
|
||||
|
|
|
@ -21,6 +21,7 @@ import qualified Git
|
|||
import qualified Git.Command
|
||||
import qualified Git.Ref
|
||||
import qualified Git.Branch
|
||||
import qualified Git.RefLog
|
||||
import qualified Git.LsFiles as LsFiles
|
||||
import qualified Git.DiffTree as DiffTree
|
||||
import qualified Backend
|
||||
|
@ -216,8 +217,9 @@ withKeysReferencedInGit :: RefSpec -> (Key -> Annex ()) -> Annex ()
|
|||
withKeysReferencedInGit refspec a = do
|
||||
current <- inRepo Git.Branch.currentUnsafe
|
||||
shaHead <- maybe (return Nothing) (inRepo . Git.Ref.sha) current
|
||||
usedrefs <- applyRefSpec refspec . relevantrefs (shaHead, current)
|
||||
rs <- relevantrefs (shaHead, current)
|
||||
<$> inRepo (Git.Command.pipeReadStrict [Param "show-ref"])
|
||||
usedrefs <- applyRefSpec refspec rs (inRepo Git.RefLog.getAll)
|
||||
forM_ usedrefs $
|
||||
withKeysReferencedInGitRef a
|
||||
where
|
||||
|
|
|
@ -14,14 +14,18 @@ import Git.Sha
|
|||
|
||||
{- Gets the reflog for a given branch. -}
|
||||
get :: Branch -> Repo -> IO [Sha]
|
||||
get = get' []
|
||||
get b = get' [] (Just b)
|
||||
|
||||
get' :: [CommandParam] -> Branch -> Repo -> IO [Sha]
|
||||
{- Gets all reflogs for all branches. -}
|
||||
getAll :: Repo -> IO [Sha]
|
||||
getAll = get' [Param "--all"] Nothing
|
||||
|
||||
get' :: [CommandParam] -> Maybe Branch -> Repo -> IO [Sha]
|
||||
get' ps b = mapMaybe extractSha . lines <$$> pipeReadStrict ps'
|
||||
where
|
||||
ps' =
|
||||
[ Param "log"
|
||||
, Param "-g"
|
||||
, Param "--format=%H"
|
||||
, Param (fromRef b)
|
||||
ps' = catMaybes
|
||||
[ Just $ Param "log"
|
||||
, Just $ Param "-g"
|
||||
, Just $ Param "--format=%H"
|
||||
, Param . fromRef <$> b
|
||||
] ++ ps
|
||||
|
|
|
@ -15,7 +15,11 @@ import Data.Either
|
|||
|
||||
type RefSpec = [RefSpecPart]
|
||||
|
||||
data RefSpecPart = AddRef Ref | AddMatching Glob | RemoveMatching Glob
|
||||
data RefSpecPart
|
||||
= AddRef Ref
|
||||
| AddMatching Glob
|
||||
| AddRefLog
|
||||
| RemoveMatching Glob
|
||||
|
||||
allRefSpec :: RefSpec
|
||||
allRefSpec = [AddMatching $ compileGlob "*" CaseSensative]
|
||||
|
@ -30,15 +34,19 @@ parseRefSpec v = case partitionEithers (map mk $ split ":" v) of
|
|||
Right $ AddMatching $ compileGlob s CaseSensative
|
||||
| otherwise = Right $ AddRef $ Ref s
|
||||
mk ('-':s) = Right $ RemoveMatching $ compileGlob s CaseSensative
|
||||
mk "reflog" = Right AddRefLog
|
||||
mk s = Left $ "bad refspec item \"" ++ s ++ "\" (expected + or - prefix)"
|
||||
|
||||
applyRefSpec :: RefSpec -> [Ref] -> [Ref]
|
||||
applyRefSpec refspec rs = go [] refspec
|
||||
applyRefSpec :: Monad m => RefSpec -> [Ref] -> m [Sha] -> m [Ref]
|
||||
applyRefSpec refspec rs getreflog = go [] refspec
|
||||
where
|
||||
go c [] = reverse c
|
||||
go c [] = return (reverse c)
|
||||
go c (AddRef r : rest) = go (r:c) rest
|
||||
go c (AddMatching g : rest) =
|
||||
let add = filter (matchGlob g . fromRef) rs
|
||||
in go (add ++ c) rest
|
||||
go c (AddRefLog : rest) = do
|
||||
reflog <- getreflog
|
||||
go (reflog ++ c) rest
|
||||
go c (RemoveMatching g : rest) =
|
||||
go (filter (not . matchGlob g . fromRef) c) rest
|
||||
|
|
4
debian/changelog
vendored
4
debian/changelog
vendored
|
@ -27,6 +27,10 @@ git-annex (5.20150618) UNRELEASED; urgency=medium
|
|||
link to annexed content.
|
||||
* sync: When annex.autocommit=false, avoid making any commit of local
|
||||
changes, while still merging with remote to the extent possible.
|
||||
* unused: --used-refspec can now be configured to look at refs in the
|
||||
reflog. This provides a way to not consider old versions of files to be
|
||||
unused after they have reached a specified age, when the old refs in
|
||||
the reflog expire.
|
||||
|
||||
-- Joey Hess <id@joeyh.name> Thu, 02 Jul 2015 12:31:14 -0400
|
||||
|
||||
|
|
|
@ -60,6 +60,11 @@ and walking the list in order from left to right.
|
|||
For example, "+HEAD^" adds "HEAD^".
|
||||
* Each - is matched against the set of refs accumulated so far.
|
||||
Any matching refs are removed from the set.
|
||||
* "reflog" adds all the refs from the reflog. This will make past versions
|
||||
of files not be considered to be unused until the ref expires from the
|
||||
reflog (by default for 90 days). Note that this may make git-annex unused
|
||||
take some time to complete, it if needs to check every ref from the
|
||||
reflog.
|
||||
|
||||
# SEE ALSO
|
||||
|
||||
|
|
|
@ -11,3 +11,7 @@ I would like to not drop all unused files.
|
|||
> However, I think that many users expect git annex unused to be able to
|
||||
> immediately find and remove a file after it's been deleted. So this
|
||||
> probably needs to be a configurable behavior. --[[Joey]]
|
||||
|
||||
>> Implemented this, `git annex unused --used-refspec=+refs/heads/*:reflog`
|
||||
>> will consider all head refs as used (the default), plus consider all
|
||||
>> refs in the reflog as used. [[done]] --[[Joey]]
|
||||
|
|
Loading…
Reference in a new issue