support findred and --branch with file matching options

* findref: Support file matching options: --include, --exclude,
  --want-get, --want-drop, --largerthan, --smallerthan, --accessedwithin
* Commands supporting --branch now apply file matching options --include,
  --exclude, --want-get, --want-drop to filenames from the branch.
  Previously, combining --branch with those would fail to match anything.
* add, import, findref: Support --time-limit.

This commit was sponsored by Jake Vosloo on Patreon.
This commit is contained in:
Joey Hess 2018-12-09 13:38:35 -04:00
parent 61b1f9deaf
commit 029ae8d4db
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
10 changed files with 54 additions and 26 deletions

View file

@ -60,7 +60,7 @@ checkMatcher matcher mkey afile notpresent notconfigured d
| isEmpty matcher = notconfigured
| otherwise = case (mkey, afile) of
(_, AssociatedFile (Just file)) -> go =<< fileMatchInfo file
(Just key, _) -> go (MatchingKey key)
(Just key, _) -> go (MatchingKey key afile)
_ -> d
where
go mi = matchMrun matcher $ \a -> a notpresent mi

View file

@ -2,6 +2,12 @@ git-annex (7.20181206) UNRELEASED; urgency=medium
* S3: Improve diagnostics when a remote is configured with exporttree and
versioning, but no S3 version id has been recorded for a key.
* findref: Support file matching options: --include, --exclude,
--want-get, --want-drop, --largerthan, --smallerthan, --accessedwithin
* Commands supporting --branch now apply file matching options --include,
--exclude, --want-get, --want-drop to filenames from the branch.
Previously, combining --branch with those would fail to match anything.
* add, import, findref: Support --time-limit.
-- Joey Hess <id@joeyh.name> Thu, 06 Dec 2018 13:39:16 -0400

View file

@ -211,18 +211,18 @@ parseKey = maybe (fail "invalid key") return . file2key
-- Options to match properties of annexed files.
annexedMatchingOptions :: [GlobalOption]
annexedMatchingOptions = concat
[ nonWorkTreeMatchingOptions'
[ keyMatchingOptions'
, fileMatchingOptions'
, combiningOptions
, timeLimitOption
]
-- Matching options that don't need to examine work tree files.
nonWorkTreeMatchingOptions :: [GlobalOption]
nonWorkTreeMatchingOptions = nonWorkTreeMatchingOptions' ++ combiningOptions
-- Matching options that can operate on keys as well as files.
keyMatchingOptions :: [GlobalOption]
keyMatchingOptions = keyMatchingOptions' ++ combiningOptions ++ timeLimitOption
nonWorkTreeMatchingOptions' :: [GlobalOption]
nonWorkTreeMatchingOptions' =
keyMatchingOptions' :: [GlobalOption]
keyMatchingOptions' =
[ globalSetter Limit.addIn $ strOption
( long "in" <> short 'i' <> metavar paramRemote
<> help "match files present in a remote"
@ -285,7 +285,7 @@ nonWorkTreeMatchingOptions' =
-- Options to match files which may not yet be annexed.
fileMatchingOptions :: [GlobalOption]
fileMatchingOptions = fileMatchingOptions' ++ combiningOptions
fileMatchingOptions = fileMatchingOptions' ++ combiningOptions ++ timeLimitOption
fileMatchingOptions' :: [GlobalOption]
fileMatchingOptions' =

View file

@ -24,6 +24,7 @@ import qualified Limit
import CmdLine.GitAnnex.Options
import Logs.Location
import Logs.Unused
import Types.ActionItem
import Types.Transfer
import Logs.Transfer
import Remote.List
@ -84,12 +85,14 @@ withFilesInRefs a = mapM_ go
go r = do
matcher <- Limit.getMatcher
(l, cleanup) <- inRepo $ LsTree.lsTree r
forM_ l $ \i -> do
let f = getTopFilePath $ LsTree.file i
catKey (LsTree.sha i) >>= \case
forM_ l $ \ti -> do
let f = getTopFilePath $ LsTree.file ti
catKey (LsTree.sha ti) >>= \case
Nothing -> noop
Just k -> whenM (matcher $ MatchingKey k) $
a (f, k)
Just k ->
let i = MatchingKey k (AssociatedFile (Just f))
in whenM (matcher i) $
a (f, k)
liftIO $ void cleanup
withPathContents :: ((FilePath, FilePath) -> CommandSeek) -> CmdParams -> CommandSeek
@ -197,8 +200,12 @@ withKeyOptions ko auto keyaction = withKeyOptions' ko auto mkkeyaction
where
mkkeyaction = do
matcher <- Limit.getMatcher
return $ \v ->
whenM (matcher $ MatchingKey $ fst v) $
return $ \v@(k, ai) ->
let i = case ai of
ActionItemBranchFilePath (BranchFilePath _ topf) ->
MatchingKey k (AssociatedFile $ Just $ getTopFilePath topf)
_ -> MatchingKey k (AssociatedFile Nothing)
in whenM (matcher i) $
keyaction v
withKeyOptions'

View file

@ -12,7 +12,7 @@ import qualified Command.Find as Find
import qualified Git
cmd :: Command
cmd = withGlobalOptions [nonWorkTreeMatchingOptions] $ Find.mkCommand $
cmd = withGlobalOptions [annexedMatchingOptions] $ Find.mkCommand $
command "findref" SectionPlumbing
"lists files in a git ref"
paramRef (seek <$$> Find.optParser)

View file

@ -94,16 +94,17 @@ matchGlobFile :: String -> MatchInfo -> Annex Bool
matchGlobFile glob = go
where
cglob = compileGlob glob CaseSensative -- memoized
go (MatchingKey _) = pure False
go (MatchingFile fi) = pure $ matchGlob cglob (matchFile fi)
go (MatchingInfo af _ _ _) = matchGlob cglob <$> getInfo af
go (MatchingKey _ (AssociatedFile Nothing)) = pure False
go (MatchingKey _ (AssociatedFile (Just af))) = pure $ matchGlob cglob af
#ifdef WITH_MAGICMIME
matchMagic :: Maybe Magic -> MkLimit Annex
matchMagic (Just magic) glob = Right $ const go
where
cglob = compileGlob glob CaseSensative -- memoized
go (MatchingKey _) = pure False
go (MatchingKey _ _) = pure False
go (MatchingFile fi) = liftIO $ catchBoolIO $
matchGlob cglob <$> magicFile magic (currFile fi)
go (MatchingInfo _ _ _ mimeval) = matchGlob cglob <$> getInfo mimeval
@ -152,7 +153,8 @@ limitInDir :: FilePath -> MatchFiles Annex
limitInDir dir = const go
where
go (MatchingFile fi) = checkf $ matchFile fi
go (MatchingKey _) = return False
go (MatchingKey _ (AssociatedFile Nothing)) = return False
go (MatchingKey _ (AssociatedFile (Just af))) = checkf af
go (MatchingInfo af _ _ _) = checkf =<< getInfo af
checkf = return . elem dir . splitPath . takeDirectory
@ -200,7 +202,7 @@ limitLackingCopies approx want = case readish want of
then approxNumCopies
else case mi of
MatchingFile fi -> getGlobalFileNumCopies $ matchFile fi
MatchingKey _ -> approxNumCopies
MatchingKey _ _ -> approxNumCopies
MatchingInfo _ _ _ _ -> approxNumCopies
us <- filter (`S.notMember` notpresent)
<$> (trustExclude UnTrusted =<< Remote.keyLocations key)
@ -214,7 +216,7 @@ limitLackingCopies approx want = case readish want of
-}
limitUnused :: MatchFiles Annex
limitUnused _ (MatchingFile _) = return False
limitUnused _ (MatchingKey k) = S.member k <$> unusedKeys
limitUnused _ (MatchingKey k _) = S.member k <$> unusedKeys
limitUnused _ (MatchingInfo _ ak _ _) = do
k <- getInfo ak
S.member k <$> unusedKeys
@ -277,7 +279,7 @@ limitSize vs s = case readSize dataUnits s of
Just sz -> Right $ go sz
where
go sz _ (MatchingFile fi) = lookupFileKey fi >>= check fi sz
go sz _ (MatchingKey key) = checkkey sz key
go sz _ (MatchingKey key _) = checkkey sz key
go sz _ (MatchingInfo _ _ as _) =
getInfo as >>= \sz' -> return (Just sz' `vs` Just sz)
checkkey sz key = return $ keySize key `vs` Just sz
@ -329,5 +331,5 @@ lookupFileKey = lookupFile . currFile
checkKey :: (Key -> Annex Bool) -> MatchInfo -> Annex Bool
checkKey a (MatchingFile fi) = lookupFileKey fi >>= maybe (return False) a
checkKey a (MatchingKey k) = a k
checkKey a (MatchingKey k _) = a k
checkKey a (MatchingInfo _ ak _ _) = a =<< getInfo ak

View file

@ -22,5 +22,5 @@ addWantDrop = addLimit $ Right $ const $ checkWant $
checkWant :: (AssociatedFile -> Annex Bool) -> MatchInfo -> Annex Bool
checkWant a (MatchingFile fi) = a (AssociatedFile (Just $ matchFile fi))
checkWant _ (MatchingKey _) = return False
checkWant a (MatchingKey _ af) = a af
checkWant _ (MatchingInfo {}) = return False

View file

@ -8,7 +8,7 @@
module Types.FileMatcher where
import Types.UUID (UUID)
import Types.Key (Key)
import Types.Key (Key, AssociatedFile)
import Utility.Matcher (Matcher, Token)
import Utility.FileSize
@ -18,7 +18,7 @@ import qualified Data.Set as S
data MatchInfo
= MatchingFile FileInfo
| MatchingKey Key
| MatchingKey Key AssociatedFile
| MatchingInfo (OptInfo FilePath) (OptInfo Key) (OptInfo FileSize) (OptInfo MimeType)
type MimeType = String

View file

@ -3,3 +3,5 @@ The documentation for `findref` says it accepts the same options as `find` but t
This leads to the confusing behavior where `findref` is sensitive to the presence of content, but you can't tell it not to be in the same manner as `find`.
Could the difference be removed by adding support for `--include`?
> [[done]] --[[Joey]]

View file

@ -0,0 +1,11 @@
[[!comment format=mdwn
username="joey"
subject="""comment 1"""
date="2018-12-09T16:27:14Z"
content="""
Relatedly, commands that support --branch and file matching options
silently fail to match the file matching options. Eg, this does not copy
anything:
git annex copy --branch master --to origin --include='*'
"""]]