fix --branch combined with --unlocked or --locked

Since it's using git ls-tree anyway, can just look at the file modes to see
if they're unlocked or are symlinks.
This commit is contained in:
Joey Hess 2021-03-02 13:46:12 -04:00
parent cbf94fd13d
commit a14001785e
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
4 changed files with 21 additions and 14 deletions

View file

@ -7,9 +7,7 @@ git-annex (8.20210224) UNRELEASED; urgency=medium
* Prevent combinations of options such as --all with --include. * Prevent combinations of options such as --all with --include.
* Fixed handling of --mimetype or --mimeencoding combined with * Fixed handling of --mimetype or --mimeencoding combined with
options like --all or --unused. options like --all or --unused.
* Fix handling of --branch combined with --unlocked or --locked.
Also, made --mimetype combined with eg --all work, by looking at the
object file when operating on keys.
-- Joey Hess <id@joeyh.name> Wed, 24 Feb 2021 13:18:38 -0400 -- Joey Hess <id@joeyh.name> Wed, 24 Feb 2021 13:18:38 -0400

View file

@ -22,6 +22,7 @@ import qualified Git.LsFiles as LsFiles
import qualified Git.LsTree as LsTree import qualified Git.LsTree as LsTree
import qualified Git.Types as Git import qualified Git.Types as Git
import qualified Git.Ref import qualified Git.Ref
import Git.Types (toTreeItemType, TreeItemType(..))
import Git.FilePath import Git.FilePath
import qualified Limit import qualified Limit
import CmdLine.GitAnnex.Options import CmdLine.GitAnnex.Options
@ -30,6 +31,7 @@ import Logs
import Logs.Unused import Logs.Unused
import Types.Transfer import Types.Transfer
import Logs.Transfer import Logs.Transfer
import Types.Link
import Remote.List import Remote.List
import qualified Remote import qualified Remote
import Annex.CatFile import Annex.CatFile
@ -191,7 +193,7 @@ withKeyOptions ko auto seeker keyaction = withKeyOptions' ko auto mkkeyaction
where where
mkkeyaction = do mkkeyaction = do
matcher <- Limit.getMatcher matcher <- Limit.getMatcher
return $ \v@(_si, k, ai) -> checkseeker k $ return $ \lt v@(_si, k, ai) -> checkseeker k $
let i = case ai of let i = case ai of
ActionItemBranchFilePath (BranchFilePath _ topf) _ -> ActionItemBranchFilePath (BranchFilePath _ topf) _ ->
ProvidedInfo ProvidedInfo
@ -201,7 +203,7 @@ withKeyOptions ko auto seeker keyaction = withKeyOptions' ko auto mkkeyaction
, providedFileSize = Nothing , providedFileSize = Nothing
, providedMimeType = Nothing , providedMimeType = Nothing
, providedMimeEncoding = Nothing , providedMimeEncoding = Nothing
, providedLinkType = Nothing , providedLinkType = lt
} }
_ -> ProvidedInfo _ -> ProvidedInfo
{ providedFilePath = Nothing { providedFilePath = Nothing
@ -209,7 +211,7 @@ withKeyOptions ko auto seeker keyaction = withKeyOptions' ko auto mkkeyaction
, providedFileSize = Nothing , providedFileSize = Nothing
, providedMimeType = Nothing , providedMimeType = Nothing
, providedMimeEncoding = Nothing , providedMimeEncoding = Nothing
, providedLinkType = Nothing , providedLinkType = lt
} }
in whenM (matcher (MatchingInfo i)) $ in whenM (matcher (MatchingInfo i)) $
keyaction v keyaction v
@ -222,7 +224,7 @@ withKeyOptions ko auto seeker keyaction = withKeyOptions' ko auto mkkeyaction
withKeyOptions' withKeyOptions'
:: Maybe KeyOptions :: Maybe KeyOptions
-> Bool -> Bool
-> Annex ((SeekInput, Key, ActionItem) -> Annex ()) -> Annex (Maybe LinkType -> (SeekInput, Key, ActionItem) -> Annex ())
-> (WorkTreeItems -> CommandSeek) -> (WorkTreeItems -> CommandSeek)
-> WorkTreeItems -> WorkTreeItems
-> CommandSeek -> CommandSeek
@ -240,7 +242,7 @@ withKeyOptions' ko auto mkkeyaction fallbackaction worktreeitems = do
(True, Just WantFailedTransfers) -> nofilename $ noauto runfailedtransfers (True, Just WantFailedTransfers) -> nofilename $ noauto runfailedtransfers
(True, Just (WantSpecificKey k)) -> nofilename $ noauto $ runkeyaction (return [k]) (True, Just (WantSpecificKey k)) -> nofilename $ noauto $ runkeyaction (return [k])
(True, Just WantIncompleteKeys) -> nofilename $ noauto $ runkeyaction incompletekeys (True, Just WantIncompleteKeys) -> nofilename $ noauto $ runkeyaction incompletekeys
(True, Just (WantBranchKeys bs)) -> nofilename $ noauto $ runbranchkeys bs (True, Just (WantBranchKeys bs)) -> noauto $ runbranchkeys bs
(False, Just _) -> giveup "Can only specify one of file names, --all, --branch, --unused, --failed, --key, or --incomplete" (False, Just _) -> giveup "Can only specify one of file names, --all, --branch, --unused, --failed, --key, or --incomplete"
where where
noauto a noauto a
@ -286,7 +288,7 @@ withKeyOptions' ko auto mkkeyaction fallbackaction worktreeitems = do
Nothing -> return () Nothing -> return ()
Just ((k, f), content) -> checktimelimit (discard reader) $ do Just ((k, f), content) -> checktimelimit (discard reader) $ do
maybe noop (Annex.BranchState.setCache f) content maybe noop (Annex.BranchState.setCache f) content
keyaction (SeekInput [], k, mkActionItem k) keyaction Nothing (SeekInput [], k, mkActionItem k)
go reader go reader
catObjectStreamLsTree l (getk . getTopFilePath . LsTree.file) g go catObjectStreamLsTree l (getk . getTopFilePath . LsTree.file) g go
liftIO $ void cleanup liftIO $ void cleanup
@ -294,17 +296,22 @@ withKeyOptions' ko auto mkkeyaction fallbackaction worktreeitems = do
runkeyaction getks = do runkeyaction getks = do
keyaction <- mkkeyaction keyaction <- mkkeyaction
ks <- getks ks <- getks
forM_ ks $ \k -> keyaction (SeekInput [], k, mkActionItem k) forM_ ks $ \k -> keyaction Nothing (SeekInput [], k, mkActionItem k)
runbranchkeys bs = do runbranchkeys bs = do
keyaction <- mkkeyaction keyaction <- mkkeyaction
forM_ bs $ \b -> do forM_ bs $ \b -> do
(l, cleanup) <- inRepo $ LsTree.lsTree LsTree.LsTreeRecursive b (l, cleanup) <- inRepo $ LsTree.lsTree LsTree.LsTreeRecursive b
forM_ l $ \i -> catKey (LsTree.sha i) >>= \case forM_ l $ \i -> catKey (LsTree.sha i) >>= \case
Nothing -> noop
Just k -> Just k ->
let bfp = mkActionItem (BranchFilePath b (LsTree.file i), k) let bfp = mkActionItem (BranchFilePath b (LsTree.file i), k)
in keyaction (SeekInput [], k, bfp) lt = case toTreeItemType (LsTree.mode i) of
Just TreeSymlink -> Just LockedLink
Just TreeFile -> Just UnlockedLink
Just TreeExecutable -> Just UnlockedLink
_ -> Nothing
in keyaction lt (SeekInput [], k, bfp)
Nothing -> noop
unlessM (liftIO cleanup) $ unlessM (liftIO cleanup) $
error ("git ls-tree " ++ Git.fromRef b ++ " failed") error ("git ls-tree " ++ Git.fromRef b ++ " failed")
@ -313,7 +320,7 @@ withKeyOptions' ko auto mkkeyaction fallbackaction worktreeitems = do
rs <- remoteList rs <- remoteList
ts <- concat <$> mapM (getFailedTransfers . Remote.uuid) rs ts <- concat <$> mapM (getFailedTransfers . Remote.uuid) rs
forM_ ts $ \(t, i) -> forM_ ts $ \(t, i) ->
keyaction (SeekInput [], transferKey t, mkActionItem (t, i)) keyaction Nothing (SeekInput [], transferKey t, mkActionItem (t, i))
seekFiltered :: ((SeekInput, RawFilePath) -> Annex Bool) -> ((SeekInput, RawFilePath) -> CommandSeek) -> Annex ([(SeekInput, RawFilePath)], IO Bool) -> Annex () seekFiltered :: ((SeekInput, RawFilePath) -> Annex Bool) -> ((SeekInput, RawFilePath) -> CommandSeek) -> Annex ([(SeekInput, RawFilePath)], IO Bool) -> Annex ()
seekFiltered prefilter a listfs = do seekFiltered prefilter a listfs = do

View file

@ -711,7 +711,7 @@ seekSyncContent o rs currbranch = do
pure Nothing pure Nothing
waitForAllRunningCommandActions waitForAllRunningCommandActions
withKeyOptions' (keyOptions o) False withKeyOptions' (keyOptions o) False
(return (commandAction . gokey mvar bloom)) (return (const (commandAction . gokey mvar bloom)))
(const noop) (const noop)
(WorkTreeItems []) (WorkTreeItems [])
waitForAllRunningCommandActions waitForAllRunningCommandActions

View file

@ -80,3 +80,5 @@ Thanks in advance.
[[!meta author=kyle]] [[!meta author=kyle]]
[[!tag projects/datalad]] [[!tag projects/datalad]]
> [[fixed|done]] --[[Joey]]