whereused --historical
Does not check the reflog, but otherwise works. It's possible for it to display something that is not an annexed file, if a non-annexed file somehow ends up containing something that looks like the key's name. This seems very unlikely to happen, and it would add a lot of complexity to detect it and somehow skip over that file, since the git log would need to either be run again, or not limited to 1 result and canceled once enough results have been read. Also, it kind of seems ok, if a file refers to a key, to consider that as a place the key was used, for some definition of used. So, I punted on dealing with that. May revisit later. Sponsored-by: Brock Spratlen on Patreon
This commit is contained in:
parent
47d3dccf19
commit
fcd1b93a7d
2 changed files with 73 additions and 4 deletions
|
@ -8,10 +8,21 @@
|
||||||
module Command.WhereUsed where
|
module Command.WhereUsed where
|
||||||
|
|
||||||
import Command
|
import Command
|
||||||
|
import Git
|
||||||
|
import Git.Sha
|
||||||
import Git.FilePath
|
import Git.FilePath
|
||||||
|
import qualified Git.Ref
|
||||||
|
import qualified Git.Command
|
||||||
|
import qualified Git.DiffTree as DiffTree
|
||||||
|
import qualified Annex
|
||||||
|
import qualified Annex.Branch
|
||||||
import Annex.CatFile
|
import Annex.CatFile
|
||||||
import Database.Keys
|
import Database.Keys
|
||||||
|
|
||||||
|
import Data.Char
|
||||||
|
import qualified Data.ByteString as S
|
||||||
|
import qualified Data.ByteString.Lazy as L
|
||||||
|
|
||||||
cmd :: Command
|
cmd :: Command
|
||||||
cmd = noCommit $ withGlobalOptions [annexedMatchingOptions] $
|
cmd = noCommit $ withGlobalOptions [annexedMatchingOptions] $
|
||||||
command "whereused" SectionQuery
|
command "whereused" SectionQuery
|
||||||
|
@ -60,9 +71,62 @@ start o (_, key, _) = startingCustomOutput key $ do
|
||||||
Just k | k == key -> return True
|
Just k | k == key -> return True
|
||||||
_ -> return False
|
_ -> return False
|
||||||
|
|
||||||
display :: Key -> FilePath -> IO ()
|
display :: Key -> String -> IO ()
|
||||||
display key f = putStrLn (serializeKey key ++ " " ++ f)
|
display key loc = putStrLn (serializeKey key ++ " " ++ loc)
|
||||||
|
|
||||||
findHistorical :: Key -> Annex ()
|
findHistorical :: Key -> Annex ()
|
||||||
findHistorical key = do
|
findHistorical key = do
|
||||||
error "TODO"
|
Annex.inRepo $ \repo -> do
|
||||||
|
-- Find most recent change to the key, in all branches and
|
||||||
|
-- tags, except the git-annex branch.
|
||||||
|
(output, cleanup) <- Git.Command.pipeNullSplit
|
||||||
|
[ Param "log"
|
||||||
|
, Param "-z"
|
||||||
|
-- Don't convert pointer files.
|
||||||
|
, Param "--no-textconv"
|
||||||
|
-- Only find the most recent commit, for speed.
|
||||||
|
, Param "-n1"
|
||||||
|
-- Find commits that contain the key.
|
||||||
|
, Param ("-S" ++ fromRawFilePath (keyFile key))
|
||||||
|
-- Skip commits where the file was deleted,
|
||||||
|
-- only find those where it was added or modified.
|
||||||
|
, Param "--diff-filter=ACMRTUX"
|
||||||
|
-- Search all local branches, except git-annex branch.
|
||||||
|
, Param ("--exclude=*/" ++ fromRef (Annex.Branch.name))
|
||||||
|
, Param "--glob=*"
|
||||||
|
-- Also search remote branches
|
||||||
|
, Param ("--exclude=" ++ fromRef (Annex.Branch.name))
|
||||||
|
, Param "--remotes=*"
|
||||||
|
-- And search tags.
|
||||||
|
, Param "--tags=*"
|
||||||
|
-- Output the commit hash
|
||||||
|
, Param "--pretty=%H"
|
||||||
|
-- And the raw diff.
|
||||||
|
, Param "--raw"
|
||||||
|
-- Don't abbreviate hashes.
|
||||||
|
, Param "--no-abbrev"
|
||||||
|
] repo
|
||||||
|
found <- case output of
|
||||||
|
(h:rest) -> do
|
||||||
|
commitsha <- getSha "log" (pure (L.toStrict h))
|
||||||
|
let diff = DiffTree.parseDiffRaw rest
|
||||||
|
forM_ (map (flip fromTopFilePath repo . DiffTree.file) diff) $ \f -> do
|
||||||
|
commitdesc <- S.takeWhile (/= fromIntegral (ord '\n'))
|
||||||
|
<$> Git.Command.pipeReadStrict
|
||||||
|
[ Param "describe"
|
||||||
|
, Param "--contains"
|
||||||
|
, Param "--all"
|
||||||
|
, Param (fromRef commitsha)
|
||||||
|
] repo
|
||||||
|
if S.null commitdesc
|
||||||
|
then return False
|
||||||
|
else do
|
||||||
|
rf <- relPathCwdToFile f
|
||||||
|
let fref = Git.Ref.branchFileRef (Ref commitdesc) rf
|
||||||
|
display key (fromRef fref)
|
||||||
|
return True
|
||||||
|
_ -> return False
|
||||||
|
void cleanup
|
||||||
|
|
||||||
|
unless found $ do
|
||||||
|
error "todo reflog"
|
||||||
|
|
|
@ -15,6 +15,7 @@ module Git.DiffTree (
|
||||||
diffFiles,
|
diffFiles,
|
||||||
diffLog,
|
diffLog,
|
||||||
commitDiff,
|
commitDiff,
|
||||||
|
parseDiffRaw,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import qualified Data.ByteString as B
|
import qualified Data.ByteString as B
|
||||||
|
@ -116,9 +117,13 @@ parseDiffRaw l = go l
|
||||||
go (s:[]) = error $ "diff-tree parse error near \"" ++ decodeBL' s ++ "\""
|
go (s:[]) = error $ "diff-tree parse error near \"" ++ decodeBL' s ++ "\""
|
||||||
|
|
||||||
-- :<srcmode> SP <dstmode> SP <srcsha> SP <dstsha> SP <status>
|
-- :<srcmode> SP <dstmode> SP <srcsha> SP <dstsha> SP <status>
|
||||||
|
--
|
||||||
|
-- May be prefixed with a newline, which git log --pretty=format
|
||||||
|
-- adds to the first line of the diff, even with -z.
|
||||||
parserDiffRaw :: RawFilePath -> A.Parser DiffTreeItem
|
parserDiffRaw :: RawFilePath -> A.Parser DiffTreeItem
|
||||||
parserDiffRaw f = DiffTreeItem
|
parserDiffRaw f = DiffTreeItem
|
||||||
<$ A8.char ':'
|
<$ A.option '\n' (A8.char '\n')
|
||||||
|
<* A8.char ':'
|
||||||
<*> octal
|
<*> octal
|
||||||
<* A8.char ' '
|
<* A8.char ' '
|
||||||
<*> octal
|
<*> octal
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue