annex.skipunknown with transition plan
Added annex.skipunknown git config, that can be set to false to change the behavior of commands like `git annex get foo*`, to not skip over files/dirs that are not checked into git and are explicitly listed in the command line. Significant complexity was needed to handle git-annex add, which uses some git ls-files calls, but needs to not use --error-unmatch because of course the files are not known to git. annex.skipunknown is planned to change to default to false in a git-annex release in early 2022. There's a todo for that.
This commit is contained in:
parent
5b28a37ea1
commit
89b2542d3c
42 changed files with 271 additions and 169 deletions
|
@ -120,7 +120,7 @@ resolveMerge us them inoverlay = do
|
||||||
void $ liftIO cleanup
|
void $ liftIO cleanup
|
||||||
|
|
||||||
unless inoverlay $ do
|
unless inoverlay $ do
|
||||||
(deleted, cleanup2) <- inRepo (LsFiles.deleted [top])
|
(deleted, cleanup2) <- inRepo (LsFiles.deleted [] [top])
|
||||||
unless (null deleted) $
|
unless (null deleted) $
|
||||||
Annex.Queue.addCommand "rm"
|
Annex.Queue.addCommand "rm"
|
||||||
[Param "--quiet", Param "-f", Param "--"]
|
[Param "--quiet", Param "-f", Param "--"]
|
||||||
|
@ -130,7 +130,8 @@ resolveMerge us them inoverlay = do
|
||||||
when merged $ do
|
when merged $ do
|
||||||
Annex.Queue.flush
|
Annex.Queue.flush
|
||||||
unless inoverlay $ do
|
unless inoverlay $ do
|
||||||
unstagedmap <- inodeMap $ inRepo $ LsFiles.notInRepo False [top]
|
unstagedmap <- inodeMap $ inRepo $
|
||||||
|
LsFiles.notInRepo [] False [top]
|
||||||
cleanConflictCruft mergedks' mergedfs' unstagedmap
|
cleanConflictCruft mergedks' mergedfs' unstagedmap
|
||||||
showLongNote "Merge conflict was automatically resolved; you may want to examine the result."
|
showLongNote "Merge conflict was automatically resolved; you may want to examine the result."
|
||||||
return merged
|
return merged
|
||||||
|
|
|
@ -152,7 +152,7 @@ dailyCheck urlrenderer = do
|
||||||
batchmaker <- liftIO getBatchCommandMaker
|
batchmaker <- liftIO getBatchCommandMaker
|
||||||
|
|
||||||
-- Find old unstaged symlinks, and add them to git.
|
-- Find old unstaged symlinks, and add them to git.
|
||||||
(unstaged, cleanup) <- liftIO $ Git.LsFiles.notInRepo False ["."] g
|
(unstaged, cleanup) <- liftIO $ Git.LsFiles.notInRepo [] False ["."] g
|
||||||
now <- liftIO getPOSIXTime
|
now <- liftIO getPOSIXTime
|
||||||
forM_ unstaged $ \file -> do
|
forM_ unstaged $ \file -> do
|
||||||
let file' = fromRawFilePath file
|
let file' = fromRawFilePath file
|
||||||
|
|
|
@ -128,7 +128,7 @@ expensiveScan urlrenderer rs = batch <~> do
|
||||||
<$> filterM inUnwantedGroup us
|
<$> filterM inUnwantedGroup us
|
||||||
|
|
||||||
g <- liftAnnex gitRepo
|
g <- liftAnnex gitRepo
|
||||||
(files, cleanup) <- liftIO $ LsFiles.inRepo [] g
|
(files, cleanup) <- liftIO $ LsFiles.inRepo [] [] g
|
||||||
removablers <- scan unwantedrs files
|
removablers <- scan unwantedrs files
|
||||||
void $ liftIO cleanup
|
void $ liftIO cleanup
|
||||||
|
|
||||||
|
|
|
@ -136,7 +136,7 @@ startupScan scanner = do
|
||||||
-- Notice any files that were deleted before
|
-- Notice any files that were deleted before
|
||||||
-- watching was started.
|
-- watching was started.
|
||||||
top <- liftAnnex $ fromRepo Git.repoPath
|
top <- liftAnnex $ fromRepo Git.repoPath
|
||||||
(fs, cleanup) <- liftAnnex $ inRepo $ LsFiles.deleted [top]
|
(fs, cleanup) <- liftAnnex $ inRepo $ LsFiles.deleted [] [top]
|
||||||
forM_ fs $ \f -> do
|
forM_ fs $ \f -> do
|
||||||
let f' = fromRawFilePath f
|
let f' = fromRawFilePath f
|
||||||
liftAnnex $ onDel' f'
|
liftAnnex $ onDel' f'
|
||||||
|
@ -362,7 +362,7 @@ onDel' file = do
|
||||||
onDelDir :: Handler
|
onDelDir :: Handler
|
||||||
onDelDir dir _ = do
|
onDelDir dir _ = do
|
||||||
debug ["directory deleted", dir]
|
debug ["directory deleted", dir]
|
||||||
(fs, clean) <- liftAnnex $ inRepo $ LsFiles.deleted [toRawFilePath dir]
|
(fs, clean) <- liftAnnex $ inRepo $ LsFiles.deleted [] [toRawFilePath dir]
|
||||||
let fs' = map fromRawFilePath fs
|
let fs' = map fromRawFilePath fs
|
||||||
|
|
||||||
liftAnnex $ mapM_ onDel' fs'
|
liftAnnex $ mapM_ onDel' fs'
|
||||||
|
|
|
@ -1,5 +1,12 @@
|
||||||
git-annex (8.20200523) UNRELEASED; urgency=medium
|
git-annex (8.20200523) UNRELEASED; urgency=medium
|
||||||
|
|
||||||
|
* Added annex.skipunknown git config, that can be set to false to change
|
||||||
|
the behavior of commands like `git annex get foo*`, to not skip
|
||||||
|
over files/dirs that are not checked into git and are explicitly listed in
|
||||||
|
the command line.
|
||||||
|
* annex.skipunknown is planned to change to default to false in a
|
||||||
|
git-annex release in early 2022. If you prefer the current behavior,
|
||||||
|
you can explicitly set it to true.
|
||||||
* Try to enable special remotes configured with autoenable=yes
|
* Try to enable special remotes configured with autoenable=yes
|
||||||
when git-annex auto-initialization happens in a new clone of an
|
when git-annex auto-initialization happens in a new clone of an
|
||||||
existing repo. Previously, git-annex init had to be explicitly run to
|
existing repo. Previously, git-annex init had to be explicitly run to
|
||||||
|
@ -14,7 +21,7 @@ git-annex (8.20200523) UNRELEASED; urgency=medium
|
||||||
sync -J --content is used with an export remote.
|
sync -J --content is used with an export remote.
|
||||||
* export: Let concurrent transfers be done with -J or annex.jobs.
|
* export: Let concurrent transfers be done with -J or annex.jobs.
|
||||||
* move --to, copy --to, mirror --to: When concurrency is enabled, run
|
* move --to, copy --to, mirror --to: When concurrency is enabled, run
|
||||||
cleanup actions in separate job pool from uploads.
|
cleanup actions in separate job pool from uploads.
|
||||||
|
|
||||||
-- Joey Hess <id@joeyh.name> Tue, 26 May 2020 10:20:52 -0400
|
-- Joey Hess <id@joeyh.name> Tue, 26 May 2020 10:20:52 -0400
|
||||||
|
|
||||||
|
|
105
CmdLine/Seek.hs
105
CmdLine/Seek.hs
|
@ -4,7 +4,7 @@
|
||||||
- the values a user passes to a command, and prepare actions operating
|
- the values a user passes to a command, and prepare actions operating
|
||||||
- on them.
|
- on them.
|
||||||
-
|
-
|
||||||
- Copyright 2010-2018 Joey Hess <id@joeyh.name>
|
- Copyright 2010-2020 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU AGPL version 3 or higher.
|
- Licensed under the GNU AGPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
@ -35,13 +35,13 @@ import Annex.InodeSentinal
|
||||||
import qualified Database.Keys
|
import qualified Database.Keys
|
||||||
import qualified Utility.RawFilePath as R
|
import qualified Utility.RawFilePath as R
|
||||||
|
|
||||||
withFilesInGit :: (RawFilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
|
withFilesInGit :: WarnUnmatchWhen -> (RawFilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
|
||||||
withFilesInGit a l = seekActions $ prepFiltered a $
|
withFilesInGit ww a l = seekActions $ prepFiltered a $
|
||||||
seekHelper LsFiles.inRepo l
|
seekHelper ww LsFiles.inRepo l
|
||||||
|
|
||||||
withFilesInGitNonRecursive :: String -> (RawFilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
|
withFilesInGitNonRecursive :: WarnUnmatchWhen -> String -> (RawFilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
|
||||||
withFilesInGitNonRecursive needforce a l = ifM (Annex.getState Annex.force)
|
withFilesInGitNonRecursive ww needforce a l = ifM (Annex.getState Annex.force)
|
||||||
( withFilesInGit a l
|
( withFilesInGit ww a l
|
||||||
, if null l
|
, if null l
|
||||||
then giveup needforce
|
then giveup needforce
|
||||||
else seekActions $ prepFiltered a (getfiles [] l)
|
else seekActions $ prepFiltered a (getfiles [] l)
|
||||||
|
@ -49,7 +49,8 @@ withFilesInGitNonRecursive needforce a l = ifM (Annex.getState Annex.force)
|
||||||
where
|
where
|
||||||
getfiles c [] = return (reverse c)
|
getfiles c [] = return (reverse c)
|
||||||
getfiles c ((WorkTreeItem p):ps) = do
|
getfiles c ((WorkTreeItem p):ps) = do
|
||||||
(fs, cleanup) <- inRepo $ LsFiles.inRepo [toRawFilePath p]
|
os <- seekOptions ww
|
||||||
|
(fs, cleanup) <- inRepo $ LsFiles.inRepo os [toRawFilePath p]
|
||||||
case fs of
|
case fs of
|
||||||
[f] -> do
|
[f] -> do
|
||||||
void $ liftIO $ cleanup
|
void $ liftIO $ cleanup
|
||||||
|
@ -66,7 +67,7 @@ withFilesNotInGit a l = go =<< seek
|
||||||
force <- Annex.getState Annex.force
|
force <- Annex.getState Annex.force
|
||||||
g <- gitRepo
|
g <- gitRepo
|
||||||
liftIO $ Git.Command.leaveZombie
|
liftIO $ Git.Command.leaveZombie
|
||||||
<$> LsFiles.notInRepo force (map (\(WorkTreeItem f) -> toRawFilePath f) l) g
|
<$> LsFiles.notInRepo [] force (map (\(WorkTreeItem f) -> toRawFilePath f) l) g
|
||||||
go fs = seekActions $ prepFiltered a $
|
go fs = seekActions $ prepFiltered a $
|
||||||
return $ concat $ segmentPaths (map (\(WorkTreeItem f) -> toRawFilePath f) l) fs
|
return $ concat $ segmentPaths (map (\(WorkTreeItem f) -> toRawFilePath f) l) fs
|
||||||
|
|
||||||
|
@ -104,7 +105,7 @@ withPairs a params = seekActions $ return $ map a $ pairs [] params
|
||||||
|
|
||||||
withFilesToBeCommitted :: (RawFilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
|
withFilesToBeCommitted :: (RawFilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
|
||||||
withFilesToBeCommitted a l = seekActions $ prepFiltered a $
|
withFilesToBeCommitted a l = seekActions $ prepFiltered a $
|
||||||
seekHelper LsFiles.stagedNotDeleted l
|
seekHelper WarnUnmatchWorkTreeItems (const LsFiles.stagedNotDeleted) l
|
||||||
|
|
||||||
isOldUnlocked :: RawFilePath -> Annex Bool
|
isOldUnlocked :: RawFilePath -> Annex Bool
|
||||||
isOldUnlocked f = liftIO (notSymlink f) <&&>
|
isOldUnlocked f = liftIO (notSymlink f) <&&>
|
||||||
|
@ -112,12 +113,12 @@ isOldUnlocked f = liftIO (notSymlink f) <&&>
|
||||||
|
|
||||||
{- unlocked pointer files that are staged, and whose content has not been
|
{- unlocked pointer files that are staged, and whose content has not been
|
||||||
- modified-}
|
- modified-}
|
||||||
withUnmodifiedUnlockedPointers :: (RawFilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
|
withUnmodifiedUnlockedPointers :: WarnUnmatchWhen -> (RawFilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
|
||||||
withUnmodifiedUnlockedPointers a l = seekActions $
|
withUnmodifiedUnlockedPointers ww a l = seekActions $
|
||||||
prepFiltered a unlockedfiles
|
prepFiltered a unlockedfiles
|
||||||
where
|
where
|
||||||
unlockedfiles = filterM isUnmodifiedUnlocked
|
unlockedfiles = filterM isUnmodifiedUnlocked
|
||||||
=<< seekHelper LsFiles.typeChangedStaged l
|
=<< seekHelper ww (const LsFiles.typeChangedStaged) l
|
||||||
|
|
||||||
isUnmodifiedUnlocked :: RawFilePath -> Annex Bool
|
isUnmodifiedUnlocked :: RawFilePath -> Annex Bool
|
||||||
isUnmodifiedUnlocked f = catKeyFile f >>= \case
|
isUnmodifiedUnlocked f = catKeyFile f >>= \case
|
||||||
|
@ -125,9 +126,9 @@ isUnmodifiedUnlocked f = catKeyFile f >>= \case
|
||||||
Just k -> sameInodeCache f =<< Database.Keys.getInodeCaches k
|
Just k -> sameInodeCache f =<< Database.Keys.getInodeCaches k
|
||||||
|
|
||||||
{- Finds files that may be modified. -}
|
{- Finds files that may be modified. -}
|
||||||
withFilesMaybeModified :: (RawFilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
|
withFilesMaybeModified :: WarnUnmatchWhen -> (RawFilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
|
||||||
withFilesMaybeModified a params = seekActions $
|
withFilesMaybeModified ww a params = seekActions $
|
||||||
prepFiltered a $ seekHelper LsFiles.modified params
|
prepFiltered a $ seekHelper ww LsFiles.modified params
|
||||||
|
|
||||||
withKeys :: (Key -> CommandSeek) -> CmdParams -> CommandSeek
|
withKeys :: (Key -> CommandSeek) -> CmdParams -> CommandSeek
|
||||||
withKeys a l = seekActions $ return $ map (a . parse) l
|
withKeys a l = seekActions $ return $ map (a . parse) l
|
||||||
|
@ -228,13 +229,25 @@ prepFiltered a fs = do
|
||||||
seekActions :: Annex [CommandSeek] -> Annex ()
|
seekActions :: Annex [CommandSeek] -> Annex ()
|
||||||
seekActions gen = sequence_ =<< gen
|
seekActions gen = sequence_ =<< gen
|
||||||
|
|
||||||
seekHelper :: ([RawFilePath] -> Git.Repo -> IO ([RawFilePath], IO Bool)) -> [WorkTreeItem] -> Annex [RawFilePath]
|
seekHelper :: WarnUnmatchWhen -> ([LsFiles.Options] -> [RawFilePath] -> Git.Repo -> IO ([RawFilePath], IO Bool)) -> [WorkTreeItem] -> Annex [RawFilePath]
|
||||||
seekHelper a l = inRepo $ \g ->
|
seekHelper ww a l = do
|
||||||
concat . concat <$> forM (segmentXargsOrdered l')
|
os <- seekOptions ww
|
||||||
(runSegmentPaths (\fs -> Git.Command.leaveZombie <$> a fs g) . map toRawFilePath)
|
inRepo $ \g ->
|
||||||
|
concat . concat <$> forM (segmentXargsOrdered l')
|
||||||
|
(runSegmentPaths (\fs -> Git.Command.leaveZombie <$> a os fs g) . map toRawFilePath)
|
||||||
where
|
where
|
||||||
l' = map (\(WorkTreeItem f) -> f) l
|
l' = map (\(WorkTreeItem f) -> f) l
|
||||||
|
|
||||||
|
data WarnUnmatchWhen = WarnUnmatchLsFiles | WarnUnmatchWorkTreeItems
|
||||||
|
|
||||||
|
seekOptions :: WarnUnmatchWhen -> Annex [LsFiles.Options]
|
||||||
|
seekOptions WarnUnmatchLsFiles =
|
||||||
|
ifM (annexSkipUnknown <$> Annex.getGitConfig)
|
||||||
|
( return []
|
||||||
|
, return [LsFiles.ErrorUnmatch]
|
||||||
|
)
|
||||||
|
seekOptions WarnUnmatchWorkTreeItems = return []
|
||||||
|
|
||||||
-- An item in the work tree, which may be a file or a directory.
|
-- An item in the work tree, which may be a file or a directory.
|
||||||
newtype WorkTreeItem = WorkTreeItem FilePath
|
newtype WorkTreeItem = WorkTreeItem FilePath
|
||||||
|
|
||||||
|
@ -243,30 +256,42 @@ newtype WorkTreeItem = WorkTreeItem FilePath
|
||||||
-- seeking for such files.
|
-- seeking for such files.
|
||||||
newtype AllowHidden = AllowHidden Bool
|
newtype AllowHidden = AllowHidden Bool
|
||||||
|
|
||||||
-- Many git commands like ls-files seek work tree items matching some criteria,
|
-- git ls-files without --error-unmatch seeks work tree items matching
|
||||||
-- and silently skip over anything that does not exist. But users expect
|
-- some criteria, and silently skips over anything that does not exist.
|
||||||
-- an error message when one of the files they provided as a command-line
|
|
||||||
-- parameter doesn't exist, so this checks that each exists.
|
|
||||||
--
|
|
||||||
-- Also, when two directories are symlinked, referring to a file
|
-- Also, when two directories are symlinked, referring to a file
|
||||||
-- inside the symlinked directory will be silently skipped by git commands
|
-- inside the symlinked directory will be silently skipped by
|
||||||
-- like ls-files. But, the user would be surprised for it to be skipped, so
|
-- git ls-files without --error-unmatch.
|
||||||
-- check if the parent directories are symlinks.
|
--
|
||||||
workTreeItems :: CmdParams -> Annex [WorkTreeItem]
|
-- Sometimes a command needs to use git-lsfiles that way, perhaps repeatedly.
|
||||||
|
-- But users expect an error message when one of the files they provided
|
||||||
|
-- as a command-line parameter doesn't exist, so this checks that each
|
||||||
|
-- exists when run with WarnUnmatchWorkTreeItems.
|
||||||
|
--
|
||||||
|
-- Note that, unlike --error-unmatch, using this does not warn
|
||||||
|
-- about command-line parameters that exist, but are not checked into git.
|
||||||
|
workTreeItems :: WarnUnmatchWhen -> CmdParams -> Annex [WorkTreeItem]
|
||||||
workTreeItems = workTreeItems' (AllowHidden False)
|
workTreeItems = workTreeItems' (AllowHidden False)
|
||||||
|
|
||||||
workTreeItems' :: AllowHidden -> CmdParams -> Annex [WorkTreeItem]
|
workTreeItems' :: AllowHidden -> WarnUnmatchWhen -> CmdParams -> Annex [WorkTreeItem]
|
||||||
workTreeItems' (AllowHidden allowhidden) ps = do
|
workTreeItems' (AllowHidden allowhidden) ww ps = do
|
||||||
currbranch <- getCurrentBranch
|
case ww of
|
||||||
forM_ ps $ \p -> do
|
WarnUnmatchWorkTreeItems -> runcheck
|
||||||
relf <- liftIO $ relPathCwdToFile p
|
WarnUnmatchLsFiles ->
|
||||||
ifM (not <$> (exists p <||> hidden currbranch relf))
|
whenM (annexSkipUnknown <$> Annex.getGitConfig)
|
||||||
( prob (p ++ " not found")
|
runcheck
|
||||||
, whenM (viasymlink (upFrom relf)) $
|
return (map WorkTreeItem ps)
|
||||||
prob (p ++ " is beyond a symbolic link")
|
|
||||||
)
|
|
||||||
return (map (WorkTreeItem) ps)
|
|
||||||
where
|
where
|
||||||
|
runcheck = do
|
||||||
|
currbranch <- getCurrentBranch
|
||||||
|
forM_ ps $ \p -> do
|
||||||
|
relf <- liftIO $ relPathCwdToFile p
|
||||||
|
ifM (not <$> (exists p <||> hidden currbranch relf))
|
||||||
|
( prob (p ++ " not found")
|
||||||
|
, whenM (viasymlink (upFrom relf)) $
|
||||||
|
prob (p ++ " is beyond a symbolic link")
|
||||||
|
)
|
||||||
|
|
||||||
exists p = isJust <$> liftIO (catchMaybeIO $ getSymbolicLinkStatus p)
|
exists p = isJust <$> liftIO (catchMaybeIO $ getSymbolicLinkStatus p)
|
||||||
|
|
||||||
viasymlink Nothing = return False
|
viasymlink Nothing = return False
|
||||||
|
|
|
@ -82,10 +82,15 @@ seek o = startConcurrency commandStages $ do
|
||||||
giveup "--update --batch is not supported"
|
giveup "--update --batch is not supported"
|
||||||
| otherwise -> batchFilesMatching fmt (gofile . toRawFilePath)
|
| otherwise -> batchFilesMatching fmt (gofile . toRawFilePath)
|
||||||
NoBatch -> do
|
NoBatch -> do
|
||||||
l <- workTreeItems (addThese o)
|
-- Avoid git ls-files complaining about files that
|
||||||
let go a = a (commandAction . gofile) l
|
-- are not known to git yet, since this will add
|
||||||
|
-- them. Instead, have workTreeItems warn about other
|
||||||
|
-- problems, like files that don't exist.
|
||||||
|
let ww = WarnUnmatchWorkTreeItems
|
||||||
|
l <- workTreeItems ww (addThese o)
|
||||||
|
let go a = a ww (commandAction . gofile) l
|
||||||
unless (updateOnly o) $
|
unless (updateOnly o) $
|
||||||
go withFilesNotInGit
|
go (const withFilesNotInGit)
|
||||||
go withFilesMaybeModified
|
go withFilesMaybeModified
|
||||||
go withUnmodifiedUnlockedPointers
|
go withUnmodifiedUnlockedPointers
|
||||||
|
|
||||||
|
|
|
@ -51,8 +51,10 @@ seek o = startConcurrency commandStages $ do
|
||||||
NoBatch -> withKeyOptions
|
NoBatch -> withKeyOptions
|
||||||
(keyOptions o) (autoMode o)
|
(keyOptions o) (autoMode o)
|
||||||
(commandAction . Command.Move.startKey (fromToOptions o) Command.Move.RemoveNever)
|
(commandAction . Command.Move.startKey (fromToOptions o) Command.Move.RemoveNever)
|
||||||
(withFilesInGit $ commandAction . go)
|
(withFilesInGit ww $ commandAction . go)
|
||||||
=<< workTreeItems (copyFiles o)
|
=<< workTreeItems ww (copyFiles o)
|
||||||
|
where
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
{- A copy is just a move that does not delete the source file.
|
{- A copy is just a move that does not delete the source file.
|
||||||
- However, auto mode avoids unnecessary copies, and avoids getting or
|
- However, auto mode avoids unnecessary copies, and avoids getting or
|
||||||
|
|
|
@ -57,10 +57,11 @@ seek o = startConcurrency commandStages $
|
||||||
Batch fmt -> batchFilesMatching fmt (go . toRawFilePath)
|
Batch fmt -> batchFilesMatching fmt (go . toRawFilePath)
|
||||||
NoBatch -> withKeyOptions (keyOptions o) (autoMode o)
|
NoBatch -> withKeyOptions (keyOptions o) (autoMode o)
|
||||||
(commandAction . startKeys o)
|
(commandAction . startKeys o)
|
||||||
(withFilesInGit (commandAction . go))
|
(withFilesInGit ww (commandAction . go))
|
||||||
=<< workTreeItems (dropFiles o)
|
=<< workTreeItems ww (dropFiles o)
|
||||||
where
|
where
|
||||||
go = whenAnnexed $ start o
|
go = whenAnnexed $ start o
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
start :: DropOptions -> RawFilePath -> Key -> CommandStart
|
start :: DropOptions -> RawFilePath -> Key -> CommandStart
|
||||||
start o file key = start' o key afile ai
|
start o file key = start' o key afile ai
|
||||||
|
|
|
@ -57,11 +57,12 @@ seek :: FindOptions -> CommandSeek
|
||||||
seek o = case batchOption o of
|
seek o = case batchOption o of
|
||||||
NoBatch -> withKeyOptions (keyOptions o) False
|
NoBatch -> withKeyOptions (keyOptions o) False
|
||||||
(commandAction . startKeys o)
|
(commandAction . startKeys o)
|
||||||
(withFilesInGit (commandAction . go))
|
(withFilesInGit ww (commandAction . go))
|
||||||
=<< workTreeItems (findThese o)
|
=<< workTreeItems ww (findThese o)
|
||||||
Batch fmt -> batchFilesMatching fmt (go . toRawFilePath)
|
Batch fmt -> batchFilesMatching fmt (go . toRawFilePath)
|
||||||
where
|
where
|
||||||
go = whenAnnexed $ start o
|
go = whenAnnexed $ start o
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
-- only files inAnnex are shown, unless the user has requested
|
-- only files inAnnex are shown, unless the user has requested
|
||||||
-- others via a limit
|
-- others via a limit
|
||||||
|
|
|
@ -32,9 +32,11 @@ cmd = noCommit $ withGlobalOptions [annexedMatchingOptions] $
|
||||||
|
|
||||||
seek :: CmdParams -> CommandSeek
|
seek :: CmdParams -> CommandSeek
|
||||||
seek ps = unlessM crippledFileSystem $ do
|
seek ps = unlessM crippledFileSystem $ do
|
||||||
withFilesInGit
|
withFilesInGit ww
|
||||||
(commandAction . (whenAnnexed $ start FixAll))
|
(commandAction . (whenAnnexed $ start FixAll))
|
||||||
=<< workTreeItems ps
|
=<< workTreeItems ww ps
|
||||||
|
where
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
data FixWhat = FixSymlinks | FixAll
|
data FixWhat = FixSymlinks | FixAll
|
||||||
|
|
||||||
|
|
|
@ -94,10 +94,12 @@ seek o = startConcurrency commandStages $ do
|
||||||
i <- prepIncremental u (incrementalOpt o)
|
i <- prepIncremental u (incrementalOpt o)
|
||||||
withKeyOptions (keyOptions o) False
|
withKeyOptions (keyOptions o) False
|
||||||
(\kai -> commandAction . startKey from i kai =<< getNumCopies)
|
(\kai -> commandAction . startKey from i kai =<< getNumCopies)
|
||||||
(withFilesInGit $ commandAction . (whenAnnexed (start from i)))
|
(withFilesInGit ww $ commandAction . (whenAnnexed (start from i)))
|
||||||
=<< workTreeItems (fsckFiles o)
|
=<< workTreeItems ww (fsckFiles o)
|
||||||
cleanupIncremental i
|
cleanupIncremental i
|
||||||
void $ tryIO $ recordActivity Fsck u
|
void $ tryIO $ recordActivity Fsck u
|
||||||
|
where
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
checkDeadRepo :: UUID -> Annex ()
|
checkDeadRepo :: UUID -> Annex ()
|
||||||
checkDeadRepo u =
|
checkDeadRepo u =
|
||||||
|
|
|
@ -45,8 +45,10 @@ seek o = startConcurrency downloadStages $ do
|
||||||
Batch fmt -> batchFilesMatching fmt (go . toRawFilePath)
|
Batch fmt -> batchFilesMatching fmt (go . toRawFilePath)
|
||||||
NoBatch -> withKeyOptions (keyOptions o) (autoMode o)
|
NoBatch -> withKeyOptions (keyOptions o) (autoMode o)
|
||||||
(commandAction . startKeys from)
|
(commandAction . startKeys from)
|
||||||
(withFilesInGit (commandAction . go))
|
(withFilesInGit ww (commandAction . go))
|
||||||
=<< workTreeItems (getFiles o)
|
=<< workTreeItems ww (getFiles o)
|
||||||
|
where
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
start :: GetOptions -> Maybe Remote -> RawFilePath -> Key -> CommandStart
|
start :: GetOptions -> Maybe Remote -> RawFilePath -> Key -> CommandStart
|
||||||
start o from file key = start' expensivecheck from key afile ai
|
start o from file key = start' expensivecheck from key afile ai
|
||||||
|
|
|
@ -38,9 +38,11 @@ seek o = do
|
||||||
| otherwise -> commandAction stop
|
| otherwise -> commandAction stop
|
||||||
_ -> do
|
_ -> do
|
||||||
let s = S.fromList ts
|
let s = S.fromList ts
|
||||||
withFilesInGit
|
withFilesInGit ww
|
||||||
(commandAction . (whenAnnexed (start s)))
|
(commandAction . (whenAnnexed (start s)))
|
||||||
=<< workTreeItems (inprogressFiles o)
|
=<< workTreeItems ww (inprogressFiles o)
|
||||||
|
where
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
start :: S.Set Key -> RawFilePath -> Key -> CommandStart
|
start :: S.Set Key -> RawFilePath -> Key -> CommandStart
|
||||||
start s _file k
|
start s _file k
|
||||||
|
|
|
@ -44,9 +44,10 @@ seek :: ListOptions -> CommandSeek
|
||||||
seek o = do
|
seek o = do
|
||||||
list <- getList o
|
list <- getList o
|
||||||
printHeader list
|
printHeader list
|
||||||
withFilesInGit
|
withFilesInGit ww (commandAction . (whenAnnexed $ start list))
|
||||||
(commandAction . (whenAnnexed $ start list))
|
=<< workTreeItems ww (listThese o)
|
||||||
=<< workTreeItems (listThese o)
|
where
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
getList :: ListOptions -> Annex [(UUID, RemoteName, TrustLevel)]
|
getList :: ListOptions -> Annex [(UUID, RemoteName, TrustLevel)]
|
||||||
getList o
|
getList o
|
||||||
|
|
|
@ -30,8 +30,10 @@ cmd = withGlobalOptions [jsonOptions, annexedMatchingOptions] $
|
||||||
|
|
||||||
seek :: CmdParams -> CommandSeek
|
seek :: CmdParams -> CommandSeek
|
||||||
seek ps = do
|
seek ps = do
|
||||||
l <- workTreeItems ps
|
l <- workTreeItems ww ps
|
||||||
withFilesInGit (commandAction . (whenAnnexed startNew)) l
|
withFilesInGit ww (commandAction . (whenAnnexed startNew)) l
|
||||||
|
where
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
startNew :: RawFilePath -> Key -> CommandStart
|
startNew :: RawFilePath -> Key -> CommandStart
|
||||||
startNew file key = ifM (isJust <$> isAnnexLink file)
|
startNew file key = ifM (isJust <$> isAnnexLink file)
|
||||||
|
|
|
@ -86,11 +86,13 @@ seek o = do
|
||||||
zone <- liftIO getCurrentTimeZone
|
zone <- liftIO getCurrentTimeZone
|
||||||
let outputter = mkOutputter m zone o
|
let outputter = mkOutputter m zone o
|
||||||
case (logFiles o, allOption o) of
|
case (logFiles o, allOption o) of
|
||||||
(fs, False) -> withFilesInGit
|
(fs, False) -> withFilesInGit ww
|
||||||
(commandAction . (whenAnnexed $ start o outputter))
|
(commandAction . (whenAnnexed $ start o outputter))
|
||||||
=<< workTreeItems fs
|
=<< workTreeItems ww fs
|
||||||
([], True) -> commandAction (startAll o outputter)
|
([], True) -> commandAction (startAll o outputter)
|
||||||
(_, True) -> giveup "Cannot specify both files and --all"
|
(_, True) -> giveup "Cannot specify both files and --all"
|
||||||
|
where
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
start :: LogOptions -> (FilePath -> Outputter) -> RawFilePath -> Key -> CommandStart
|
start :: LogOptions -> (FilePath -> Outputter) -> RawFilePath -> Key -> CommandStart
|
||||||
start o outputter file key = do
|
start o outputter file key = do
|
||||||
|
|
|
@ -31,7 +31,7 @@ run _ file = seekSingleGitFile file >>= \case
|
||||||
-- But, this plumbing command does not recurse through directories.
|
-- But, this plumbing command does not recurse through directories.
|
||||||
seekSingleGitFile :: FilePath -> Annex (Maybe RawFilePath)
|
seekSingleGitFile :: FilePath -> Annex (Maybe RawFilePath)
|
||||||
seekSingleGitFile file = do
|
seekSingleGitFile file = do
|
||||||
(l, cleanup) <- inRepo (Git.LsFiles.inRepo [toRawFilePath file])
|
(l, cleanup) <- inRepo (Git.LsFiles.inRepo [] [toRawFilePath file])
|
||||||
r <- case l of
|
r <- case l of
|
||||||
(f:[]) | takeFileName (fromRawFilePath f) == takeFileName file ->
|
(f:[]) | takeFileName (fromRawFilePath f) == takeFileName file ->
|
||||||
return (Just f)
|
return (Just f)
|
||||||
|
|
|
@ -75,15 +75,16 @@ seek :: MetaDataOptions -> CommandSeek
|
||||||
seek o = case batchOption o of
|
seek o = case batchOption o of
|
||||||
NoBatch -> do
|
NoBatch -> do
|
||||||
c <- liftIO currentVectorClock
|
c <- liftIO currentVectorClock
|
||||||
|
let ww = WarnUnmatchLsFiles
|
||||||
let seeker = case getSet o of
|
let seeker = case getSet o of
|
||||||
Get _ -> withFilesInGit
|
Get _ -> withFilesInGit ww
|
||||||
GetAll -> withFilesInGit
|
GetAll -> withFilesInGit ww
|
||||||
Set _ -> withFilesInGitNonRecursive
|
Set _ -> withFilesInGitNonRecursive ww
|
||||||
"Not recursively setting metadata. Use --force to do that."
|
"Not recursively setting metadata. Use --force to do that."
|
||||||
withKeyOptions (keyOptions o) False
|
withKeyOptions (keyOptions o) False
|
||||||
(commandAction . startKeys c o)
|
(commandAction . startKeys c o)
|
||||||
(seeker (commandAction . (whenAnnexed (start c o))))
|
(seeker (commandAction . (whenAnnexed (start c o))))
|
||||||
=<< workTreeItems (forFiles o)
|
=<< workTreeItems ww (forFiles o)
|
||||||
Batch fmt -> withMessageState $ \s -> case outputType s of
|
Batch fmt -> withMessageState $ \s -> case outputType s of
|
||||||
JSONOutput _ -> ifM limited
|
JSONOutput _ -> ifM limited
|
||||||
( giveup "combining --batch with file matching options is not currently supported"
|
( giveup "combining --batch with file matching options is not currently supported"
|
||||||
|
|
|
@ -26,7 +26,10 @@ cmd = withGlobalOptions [annexedMatchingOptions] $
|
||||||
paramPaths (withParams seek)
|
paramPaths (withParams seek)
|
||||||
|
|
||||||
seek :: CmdParams -> CommandSeek
|
seek :: CmdParams -> CommandSeek
|
||||||
seek = withFilesInGit (commandAction . (whenAnnexed start)) <=< workTreeItems
|
seek = withFilesInGit ww (commandAction . (whenAnnexed start))
|
||||||
|
<=< workTreeItems ww
|
||||||
|
where
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
start :: RawFilePath -> Key -> CommandStart
|
start :: RawFilePath -> Key -> CommandStart
|
||||||
start file key = do
|
start file key = do
|
||||||
|
|
|
@ -44,12 +44,13 @@ seek :: MirrorOptions -> CommandSeek
|
||||||
seek o = startConcurrency stages $
|
seek o = startConcurrency stages $
|
||||||
withKeyOptions (keyOptions o) False
|
withKeyOptions (keyOptions o) False
|
||||||
(commandAction . startKey o (AssociatedFile Nothing))
|
(commandAction . startKey o (AssociatedFile Nothing))
|
||||||
(withFilesInGit (commandAction . (whenAnnexed $ start o)))
|
(withFilesInGit ww (commandAction . (whenAnnexed $ start o)))
|
||||||
=<< workTreeItems (mirrorFiles o)
|
=<< workTreeItems ww (mirrorFiles o)
|
||||||
where
|
where
|
||||||
stages = case fromToOptions o of
|
stages = case fromToOptions o of
|
||||||
FromRemote _ -> downloadStages
|
FromRemote _ -> downloadStages
|
||||||
ToRemote _ -> commandStages
|
ToRemote _ -> commandStages
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
start :: MirrorOptions -> RawFilePath -> Key -> CommandStart
|
start :: MirrorOptions -> RawFilePath -> Key -> CommandStart
|
||||||
start o file k = startKey o afile (k, ai)
|
start o file k = startKey o afile (k, ai)
|
||||||
|
|
|
@ -60,13 +60,14 @@ seek o = startConcurrency stages $ do
|
||||||
Batch fmt -> batchFilesMatching fmt (go . toRawFilePath)
|
Batch fmt -> batchFilesMatching fmt (go . toRawFilePath)
|
||||||
NoBatch -> withKeyOptions (keyOptions o) False
|
NoBatch -> withKeyOptions (keyOptions o) False
|
||||||
(commandAction . startKey (fromToOptions o) (removeWhen o))
|
(commandAction . startKey (fromToOptions o) (removeWhen o))
|
||||||
(withFilesInGit (commandAction . go))
|
(withFilesInGit ww (commandAction . go))
|
||||||
=<< workTreeItems (moveFiles o)
|
=<< workTreeItems ww (moveFiles o)
|
||||||
where
|
where
|
||||||
stages = case fromToOptions o of
|
stages = case fromToOptions o of
|
||||||
Right (FromRemote _) -> downloadStages
|
Right (FromRemote _) -> downloadStages
|
||||||
Right (ToRemote _) -> commandStages
|
Right (ToRemote _) -> commandStages
|
||||||
Left ToHere -> downloadStages
|
Left ToHere -> downloadStages
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
start :: FromToHereOptions -> RemoveWhen -> RawFilePath -> Key -> CommandStart
|
start :: FromToHereOptions -> RemoveWhen -> RawFilePath -> Key -> CommandStart
|
||||||
start fromto removewhen f k = start' fromto removewhen afile k ai
|
start fromto removewhen f k = start' fromto removewhen afile k ai
|
||||||
|
|
|
@ -129,7 +129,9 @@ send ups fs = do
|
||||||
-- expensive.
|
-- expensive.
|
||||||
starting "sending files" (ActionItemOther Nothing) $
|
starting "sending files" (ActionItemOther Nothing) $
|
||||||
withTmpFile "send" $ \t h -> do
|
withTmpFile "send" $ \t h -> do
|
||||||
fs' <- seekHelper LsFiles.inRepo =<< workTreeItems fs
|
let ww = WarnUnmatchLsFiles
|
||||||
|
fs' <- seekHelper ww LsFiles.inRepo
|
||||||
|
=<< workTreeItems ww fs
|
||||||
matcher <- Limit.getMatcher
|
matcher <- Limit.getMatcher
|
||||||
let addlist f o = whenM (matcher $ MatchingFile $ FileInfo f f) $
|
let addlist f o = whenM (matcher $ MatchingFile $ FileInfo f f) $
|
||||||
liftIO $ hPutStrLn h o
|
liftIO $ hPutStrLn h o
|
||||||
|
|
|
@ -32,7 +32,8 @@ cmd = command "pre-commit" SectionPlumbing
|
||||||
|
|
||||||
seek :: CmdParams -> CommandSeek
|
seek :: CmdParams -> CommandSeek
|
||||||
seek ps = do
|
seek ps = do
|
||||||
l <- workTreeItems ps
|
let ww = WarnUnmatchWorkTreeItems
|
||||||
|
l <- workTreeItems ww ps
|
||||||
-- fix symlinks to files being committed
|
-- fix symlinks to files being committed
|
||||||
flip withFilesToBeCommitted l $ \f -> commandAction $
|
flip withFilesToBeCommitted l $ \f -> commandAction $
|
||||||
maybe stop (Command.Fix.start Command.Fix.FixSymlinks f)
|
maybe stop (Command.Fix.start Command.Fix.FixSymlinks f)
|
||||||
|
|
|
@ -636,11 +636,11 @@ seekSyncContent o rs currbranch = do
|
||||||
Just WantAllKeys -> Just <$> genBloomFilter (seekworktree mvar [])
|
Just WantAllKeys -> Just <$> genBloomFilter (seekworktree mvar [])
|
||||||
_ -> case currbranch of
|
_ -> case currbranch of
|
||||||
(Just origbranch, Just adj) | adjustmentHidesFiles adj -> do
|
(Just origbranch, Just adj) | adjustmentHidesFiles adj -> do
|
||||||
l <- workTreeItems' (AllowHidden True) (contentOfOption o)
|
l <- workTreeItems' (AllowHidden True) ww (contentOfOption o)
|
||||||
seekincludinghidden origbranch mvar l (const noop)
|
seekincludinghidden origbranch mvar l (const noop)
|
||||||
pure Nothing
|
pure Nothing
|
||||||
_ -> do
|
_ -> do
|
||||||
l <- workTreeItems (contentOfOption o)
|
l <- workTreeItems ww (contentOfOption o)
|
||||||
seekworktree mvar l (const noop)
|
seekworktree mvar l (const noop)
|
||||||
pure Nothing
|
pure Nothing
|
||||||
withKeyOptions' (keyOptions o) False
|
withKeyOptions' (keyOptions o) False
|
||||||
|
@ -651,13 +651,15 @@ seekSyncContent o rs currbranch = do
|
||||||
liftIO $ not <$> isEmptyMVar mvar
|
liftIO $ not <$> isEmptyMVar mvar
|
||||||
where
|
where
|
||||||
seekworktree mvar l bloomfeeder =
|
seekworktree mvar l bloomfeeder =
|
||||||
seekHelper LsFiles.inRepo l
|
seekHelper ww LsFiles.inRepo l
|
||||||
>>= gofiles bloomfeeder mvar
|
>>= gofiles bloomfeeder mvar
|
||||||
|
|
||||||
seekincludinghidden origbranch mvar l bloomfeeder =
|
seekincludinghidden origbranch mvar l bloomfeeder =
|
||||||
seekHelper (LsFiles.inRepoOrBranch origbranch) l
|
seekHelper ww (LsFiles.inRepoOrBranch origbranch) l
|
||||||
>>= gofiles bloomfeeder mvar
|
>>= gofiles bloomfeeder mvar
|
||||||
|
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
gofiles bloomfeeder mvar = mapM_ $ \f ->
|
gofiles bloomfeeder mvar = mapM_ $ \f ->
|
||||||
ifAnnexed f
|
ifAnnexed f
|
||||||
(go (Right bloomfeeder) mvar (AssociatedFile (Just f)))
|
(go (Right bloomfeeder) mvar (AssociatedFile (Just f)))
|
||||||
|
|
|
@ -23,7 +23,10 @@ cmd = withGlobalOptions [annexedMatchingOptions] $
|
||||||
paramPaths (withParams seek)
|
paramPaths (withParams seek)
|
||||||
|
|
||||||
seek :: CmdParams -> CommandSeek
|
seek :: CmdParams -> CommandSeek
|
||||||
seek ps = (withFilesInGit $ commandAction . whenAnnexed start) =<< workTreeItems ps
|
seek ps = (withFilesInGit ww $ commandAction . whenAnnexed start)
|
||||||
|
=<< workTreeItems ww ps
|
||||||
|
where
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
start :: RawFilePath -> Key -> CommandStart
|
start :: RawFilePath -> Key -> CommandStart
|
||||||
start file key = stopUnless (inAnnex key) $
|
start file key = stopUnless (inAnnex key) $
|
||||||
|
|
|
@ -27,7 +27,7 @@ seek :: CmdParams -> CommandSeek
|
||||||
seek ps = do
|
seek ps = do
|
||||||
-- Safety first; avoid any undo that would touch files that are not
|
-- Safety first; avoid any undo that would touch files that are not
|
||||||
-- in the index.
|
-- in the index.
|
||||||
(fs, cleanup) <- inRepo $ LsFiles.notInRepo False (map toRawFilePath ps)
|
(fs, cleanup) <- inRepo $ LsFiles.notInRepo [] False (map toRawFilePath ps)
|
||||||
unless (null fs) $
|
unless (null fs) $
|
||||||
giveup $ "Cannot undo changes to files that are not checked into git: " ++ unwords (map fromRawFilePath fs)
|
giveup $ "Cannot undo changes to files that are not checked into git: " ++ unwords (map fromRawFilePath fs)
|
||||||
void $ liftIO $ cleanup
|
void $ liftIO $ cleanup
|
||||||
|
|
|
@ -41,11 +41,13 @@ check = do
|
||||||
|
|
||||||
seek :: CmdParams -> CommandSeek
|
seek :: CmdParams -> CommandSeek
|
||||||
seek ps = do
|
seek ps = do
|
||||||
l <- workTreeItems ps
|
l <- workTreeItems ww ps
|
||||||
withFilesNotInGit (commandAction . whenAnnexed (startCheckIncomplete . fromRawFilePath)) l
|
withFilesNotInGit (commandAction . whenAnnexed (startCheckIncomplete . fromRawFilePath)) l
|
||||||
Annex.changeState $ \s -> s { Annex.fast = True }
|
Annex.changeState $ \s -> s { Annex.fast = True }
|
||||||
withFilesInGit (commandAction . whenAnnexed Command.Unannex.start) l
|
withFilesInGit ww (commandAction . whenAnnexed Command.Unannex.start) l
|
||||||
finish
|
finish
|
||||||
|
where
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
{- git annex symlinks that are not checked into git could be left by an
|
{- git annex symlinks that are not checked into git could be left by an
|
||||||
- interrupted add. -}
|
- interrupted add. -}
|
||||||
|
|
|
@ -27,7 +27,10 @@ mkcmd n d = withGlobalOptions [jsonOptions, annexedMatchingOptions] $
|
||||||
command n SectionCommon d paramPaths (withParams seek)
|
command n SectionCommon d paramPaths (withParams seek)
|
||||||
|
|
||||||
seek :: CmdParams -> CommandSeek
|
seek :: CmdParams -> CommandSeek
|
||||||
seek ps = withFilesInGit (commandAction . whenAnnexed start) =<< workTreeItems ps
|
seek ps = withFilesInGit ww (commandAction . whenAnnexed start)
|
||||||
|
=<< workTreeItems ww ps
|
||||||
|
where
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
start :: RawFilePath -> Key -> CommandStart
|
start :: RawFilePath -> Key -> CommandStart
|
||||||
start file key = ifM (isJust <$> isAnnexLink file)
|
start file key = ifM (isJust <$> isAnnexLink file)
|
||||||
|
|
|
@ -210,9 +210,9 @@ withKeysReferenced' mdir initial a = do
|
||||||
( return ([], return True)
|
( return ([], return True)
|
||||||
, do
|
, do
|
||||||
top <- fromRepo Git.repoPath
|
top <- fromRepo Git.repoPath
|
||||||
inRepo $ LsFiles.allFiles [top]
|
inRepo $ LsFiles.allFiles [] [top]
|
||||||
)
|
)
|
||||||
Just dir -> inRepo $ LsFiles.inRepo [toRawFilePath dir]
|
Just dir -> inRepo $ LsFiles.inRepo [] [toRawFilePath dir]
|
||||||
go v [] = return v
|
go v [] = return v
|
||||||
go v (f:fs) = do
|
go v (f:fs) = do
|
||||||
mk <- lookupFile f
|
mk <- lookupFile f
|
||||||
|
|
|
@ -101,7 +101,7 @@ checkoutViewBranch view mkbranch = do
|
||||||
- removed.) -}
|
- removed.) -}
|
||||||
top <- liftIO . absPath . fromRawFilePath =<< fromRepo Git.repoPath
|
top <- liftIO . absPath . fromRawFilePath =<< fromRepo Git.repoPath
|
||||||
(l, cleanup) <- inRepo $
|
(l, cleanup) <- inRepo $
|
||||||
LsFiles.notInRepoIncludingEmptyDirectories False
|
LsFiles.notInRepoIncludingEmptyDirectories [] False
|
||||||
[toRawFilePath top]
|
[toRawFilePath top]
|
||||||
forM_ l (removeemptydir top)
|
forM_ l (removeemptydir top)
|
||||||
liftIO $ void cleanup
|
liftIO $ void cleanup
|
||||||
|
|
|
@ -57,8 +57,10 @@ seek o = do
|
||||||
NoBatch ->
|
NoBatch ->
|
||||||
withKeyOptions (keyOptions o) False
|
withKeyOptions (keyOptions o) False
|
||||||
(commandAction . startKeys o m)
|
(commandAction . startKeys o m)
|
||||||
(withFilesInGit (commandAction . go))
|
(withFilesInGit ww (commandAction . go))
|
||||||
=<< workTreeItems (whereisFiles o)
|
=<< workTreeItems ww (whereisFiles o)
|
||||||
|
where
|
||||||
|
ww = WarnUnmatchLsFiles
|
||||||
|
|
||||||
start :: WhereisOptions -> M.Map UUID Remote -> RawFilePath -> Key -> CommandStart
|
start :: WhereisOptions -> M.Map UUID Remote -> RawFilePath -> Key -> CommandStart
|
||||||
start o remotemap file key =
|
start o remotemap file key =
|
||||||
|
|
|
@ -1,11 +1,12 @@
|
||||||
{- git ls-files interface
|
{- git ls-files interface
|
||||||
-
|
-
|
||||||
- Copyright 2010-2019 Joey Hess <id@joeyh.name>
|
- Copyright 2010-2020 Joey Hess <id@joeyh.name>
|
||||||
-
|
-
|
||||||
- Licensed under the GNU AGPL version 3 or higher.
|
- Licensed under the GNU AGPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Git.LsFiles (
|
module Git.LsFiles (
|
||||||
|
Options(..),
|
||||||
inRepo,
|
inRepo,
|
||||||
inRepoOrBranch,
|
inRepoOrBranch,
|
||||||
notInRepo,
|
notInRepo,
|
||||||
|
@ -13,10 +14,8 @@ module Git.LsFiles (
|
||||||
allFiles,
|
allFiles,
|
||||||
deleted,
|
deleted,
|
||||||
modified,
|
modified,
|
||||||
modifiedOthers,
|
|
||||||
staged,
|
staged,
|
||||||
stagedNotDeleted,
|
stagedNotDeleted,
|
||||||
stagedOthersDetails,
|
|
||||||
stagedDetails,
|
stagedDetails,
|
||||||
typeChanged,
|
typeChanged,
|
||||||
typeChangedStaged,
|
typeChangedStaged,
|
||||||
|
@ -63,101 +62,63 @@ guardSafeForLsFiles r a
|
||||||
| safeForLsFiles r = a
|
| safeForLsFiles r = a
|
||||||
| otherwise = error $ "git ls-files is unsafe to run on repository " ++ repoDescribe r
|
| otherwise = error $ "git ls-files is unsafe to run on repository " ++ repoDescribe r
|
||||||
|
|
||||||
|
data Options = ErrorUnmatch
|
||||||
|
|
||||||
{- Lists files that are checked into git's index at the specified paths.
|
{- Lists files that are checked into git's index at the specified paths.
|
||||||
- With no paths, all files are listed.
|
- With no paths, all files are listed.
|
||||||
-}
|
-}
|
||||||
inRepo :: [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
inRepo :: [Options] -> [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
||||||
inRepo = inRepo' []
|
inRepo = inRepo' [Param "--cached"]
|
||||||
|
|
||||||
inRepo' :: [CommandParam] -> [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
inRepo' :: [CommandParam] -> [Options] -> [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
||||||
inRepo' ps l repo = guardSafeForLsFiles repo $ pipeNullSplit' params repo
|
inRepo' ps os l repo = guardSafeForLsFiles repo $ pipeNullSplit' params repo
|
||||||
where
|
where
|
||||||
params =
|
params =
|
||||||
Param "ls-files" :
|
Param "ls-files" :
|
||||||
Param "--cached" :
|
|
||||||
Param "-z" :
|
Param "-z" :
|
||||||
ps ++
|
map op os ++ ps ++
|
||||||
(Param "--" : map (File . fromRawFilePath) l)
|
(Param "--" : map (File . fromRawFilePath) l)
|
||||||
|
op ErrorUnmatch = Param "--error-unmatch"
|
||||||
|
|
||||||
{- Files that are checked into the index or have been committed to a
|
{- Files that are checked into the index or have been committed to a
|
||||||
- branch. -}
|
- branch. -}
|
||||||
inRepoOrBranch :: Branch -> [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
inRepoOrBranch :: Branch -> [Options] -> [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
||||||
inRepoOrBranch b = inRepo' [Param $ "--with-tree=" ++ fromRef b]
|
inRepoOrBranch b = inRepo'
|
||||||
|
[ Param "--cached"
|
||||||
|
, Param ("--with-tree=" ++ fromRef b)
|
||||||
|
]
|
||||||
|
|
||||||
{- Scans for files at the specified locations that are not checked into git. -}
|
{- Scans for files at the specified locations that are not checked into git. -}
|
||||||
notInRepo :: Bool -> [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
notInRepo :: [Options] -> Bool -> [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
||||||
notInRepo = notInRepo' []
|
notInRepo = notInRepo' []
|
||||||
|
|
||||||
notInRepo' :: [CommandParam] -> Bool -> [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
notInRepo' :: [CommandParam] -> [Options] -> Bool -> [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
||||||
notInRepo' ps include_ignored l repo = guardSafeForLsFiles repo $
|
notInRepo' ps os include_ignored =
|
||||||
pipeNullSplit' params repo
|
inRepo' (Param "--others" : ps ++ exclude) os
|
||||||
where
|
where
|
||||||
params = concat
|
|
||||||
[ [ Param "ls-files", Param "--others"]
|
|
||||||
, ps
|
|
||||||
, exclude
|
|
||||||
, [ Param "-z", Param "--" ]
|
|
||||||
, map (File . fromRawFilePath) l
|
|
||||||
]
|
|
||||||
exclude
|
exclude
|
||||||
| include_ignored = []
|
| include_ignored = []
|
||||||
| otherwise = [Param "--exclude-standard"]
|
| otherwise = [Param "--exclude-standard"]
|
||||||
|
|
||||||
{- Scans for files at the specified locations that are not checked into
|
{- Scans for files at the specified locations that are not checked into
|
||||||
- git. Empty directories are included in the result. -}
|
- git. Empty directories are included in the result. -}
|
||||||
notInRepoIncludingEmptyDirectories :: Bool -> [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
notInRepoIncludingEmptyDirectories :: [Options] -> Bool -> [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
||||||
notInRepoIncludingEmptyDirectories = notInRepo' [Param "--directory"]
|
notInRepoIncludingEmptyDirectories = notInRepo' [Param "--directory"]
|
||||||
|
|
||||||
{- Finds all files in the specified locations, whether checked into git or
|
{- Finds all files in the specified locations, whether checked into git or
|
||||||
- not. -}
|
- not. -}
|
||||||
allFiles :: [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
allFiles :: [Options] -> [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
||||||
allFiles l repo = guardSafeForLsFiles repo $ pipeNullSplit' params repo
|
allFiles = inRepo' [Param "--cached", Param "--others"]
|
||||||
where
|
|
||||||
params =
|
|
||||||
Param "ls-files" :
|
|
||||||
Param "--cached" :
|
|
||||||
Param "--others" :
|
|
||||||
Param "-z" :
|
|
||||||
Param "--" :
|
|
||||||
map (File . fromRawFilePath) l
|
|
||||||
|
|
||||||
{- Returns a list of files in the specified locations that have been
|
{- Returns a list of files in the specified locations that have been
|
||||||
- deleted. -}
|
- deleted. -}
|
||||||
deleted :: [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
deleted :: [Options] -> [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
||||||
deleted l repo = guardSafeForLsFiles repo $ pipeNullSplit' params repo
|
deleted = inRepo' [Param "--deleted"]
|
||||||
where
|
|
||||||
params =
|
|
||||||
Param "ls-files" :
|
|
||||||
Param "--deleted" :
|
|
||||||
Param "-z" :
|
|
||||||
Param "--" :
|
|
||||||
map (File . fromRawFilePath) l
|
|
||||||
|
|
||||||
{- Returns a list of files in the specified locations that have been
|
{- Returns a list of files in the specified locations that have been
|
||||||
- modified. -}
|
- modified. -}
|
||||||
modified :: [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
modified :: [Options] -> [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
||||||
modified l repo = guardSafeForLsFiles repo $ pipeNullSplit' params repo
|
modified = inRepo' [Param "--modified"]
|
||||||
where
|
|
||||||
params =
|
|
||||||
Param "ls-files" :
|
|
||||||
Param "--modified" :
|
|
||||||
Param "-z" :
|
|
||||||
Param "--" :
|
|
||||||
map (File . fromRawFilePath) l
|
|
||||||
|
|
||||||
{- Files that have been modified or are not checked into git (and are not
|
|
||||||
- ignored). -}
|
|
||||||
modifiedOthers :: [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
|
||||||
modifiedOthers l repo = guardSafeForLsFiles repo $ pipeNullSplit' params repo
|
|
||||||
where
|
|
||||||
params =
|
|
||||||
Param "ls-files" :
|
|
||||||
Param "--modified" :
|
|
||||||
Param "--others" :
|
|
||||||
Param "--exclude-standard" :
|
|
||||||
Param "-z" :
|
|
||||||
Param "--" :
|
|
||||||
map (File . fromRawFilePath) l
|
|
||||||
|
|
||||||
{- Returns a list of all files that are staged for commit. -}
|
{- Returns a list of all files that are staged for commit. -}
|
||||||
staged :: [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
staged :: [RawFilePath] -> Repo -> IO ([RawFilePath], IO Bool)
|
||||||
|
@ -177,11 +138,6 @@ staged' ps l repo = guardSafeForLsFiles repo $
|
||||||
|
|
||||||
type StagedDetails = (RawFilePath, Maybe Sha, Maybe FileMode)
|
type StagedDetails = (RawFilePath, Maybe Sha, Maybe FileMode)
|
||||||
|
|
||||||
{- Returns details about files that are staged in the index,
|
|
||||||
- as well as files not yet in git. Skips ignored files. -}
|
|
||||||
stagedOthersDetails :: [RawFilePath] -> Repo -> IO ([StagedDetails], IO Bool)
|
|
||||||
stagedOthersDetails = stagedDetails' [Param "--others", Param "--exclude-standard"]
|
|
||||||
|
|
||||||
{- Returns details about all files that are staged in the index. -}
|
{- Returns details about all files that are staged in the index. -}
|
||||||
stagedDetails :: [RawFilePath] -> Repo -> IO ([StagedDetails], IO Bool)
|
stagedDetails :: [RawFilePath] -> Repo -> IO ([StagedDetails], IO Bool)
|
||||||
stagedDetails = stagedDetails' []
|
stagedDetails = stagedDetails' []
|
||||||
|
|
11
NEWS
11
NEWS
|
@ -1,3 +1,14 @@
|
||||||
|
git-annex (8.20200523) UNRELEASED; urgency=medium
|
||||||
|
|
||||||
|
Transition notice: Commands like `git-annex get foo*` silently skip over
|
||||||
|
files that are not checked into git. Since that can be surprising in many
|
||||||
|
cases, the behavior will change to erroring out when one of the listed
|
||||||
|
files is not checked into git. This change is planned for a git-annex
|
||||||
|
release in early 2022. If you would like to keep the current
|
||||||
|
behavior, use git config to set annex.skipunknown to true.
|
||||||
|
|
||||||
|
-- Joey Hess <id@joeyh.name> Thu, 28 May 2020 13:23:40 -0400
|
||||||
|
|
||||||
git-annex (8.20200226) upstream; urgency=medium
|
git-annex (8.20200226) upstream; urgency=medium
|
||||||
|
|
||||||
This version of git-annex uses repository version 8 for all repositories.
|
This version of git-annex uses repository version 8 for all repositories.
|
||||||
|
|
|
@ -123,6 +123,7 @@ data GitConfig = GitConfig
|
||||||
, annexCacheCreds :: Bool
|
, annexCacheCreds :: Bool
|
||||||
, annexAutoUpgradeRepository :: Bool
|
, annexAutoUpgradeRepository :: Bool
|
||||||
, annexCommitMode :: CommitMode
|
, annexCommitMode :: CommitMode
|
||||||
|
, annexSkipUnknown :: Bool
|
||||||
, coreSymlinks :: Bool
|
, coreSymlinks :: Bool
|
||||||
, coreSharedRepository :: SharedRepository
|
, coreSharedRepository :: SharedRepository
|
||||||
, receiveDenyCurrentBranch :: DenyCurrentBranch
|
, receiveDenyCurrentBranch :: DenyCurrentBranch
|
||||||
|
@ -214,6 +215,7 @@ extractGitConfig configsource r = GitConfig
|
||||||
, annexCommitMode = if getbool (annexConfig "allowsign") False
|
, annexCommitMode = if getbool (annexConfig "allowsign") False
|
||||||
then ManualCommit
|
then ManualCommit
|
||||||
else AutomaticCommit
|
else AutomaticCommit
|
||||||
|
, annexSkipUnknown = getbool (annexConfig "skipunknown") True
|
||||||
, coreSymlinks = getbool "core.symlinks" True
|
, coreSymlinks = getbool "core.symlinks" True
|
||||||
, coreSharedRepository = getSharedRepository r
|
, coreSharedRepository = getSharedRepository r
|
||||||
, receiveDenyCurrentBranch = getDenyCurrentBranch r
|
, receiveDenyCurrentBranch = getDenyCurrentBranch r
|
||||||
|
|
|
@ -85,7 +85,7 @@ updateSymlinks :: Annex ()
|
||||||
updateSymlinks = do
|
updateSymlinks = do
|
||||||
showAction "updating symlinks"
|
showAction "updating symlinks"
|
||||||
top <- fromRepo Git.repoPath
|
top <- fromRepo Git.repoPath
|
||||||
(files, cleanup) <- inRepo $ LsFiles.inRepo [top]
|
(files, cleanup) <- inRepo $ LsFiles.inRepo [] [top]
|
||||||
forM_ files (fixlink . fromRawFilePath)
|
forM_ files (fixlink . fromRawFilePath)
|
||||||
void $ liftIO cleanup
|
void $ liftIO cleanup
|
||||||
where
|
where
|
||||||
|
|
|
@ -35,3 +35,12 @@ P.S. It might be a related observation that git-annex metadata does exit with n
|
||||||
[[!tag projects/datalad]]
|
[[!tag projects/datalad]]
|
||||||
|
|
||||||
[[!meta title="silently skipping files that are not in git or not annexed is sometimes surprising to some"]]
|
[[!meta title="silently skipping files that are not in git or not annexed is sometimes surprising to some"]]
|
||||||
|
|
||||||
|
> annex.skipunknown false will make git-annex error out in this situation.
|
||||||
|
> That will become the default in a couple of years, but can be set already
|
||||||
|
> by those who don't like the behavior of skipping.
|
||||||
|
>
|
||||||
|
> In the case of addurl --batch though, do see my first comment for a way to
|
||||||
|
> avoid any errors.
|
||||||
|
>
|
||||||
|
> [[done]] --[[Joey]]
|
||||||
|
|
|
@ -27,7 +27,8 @@ temp file that is not in git, then they would have to change scripts
|
||||||
and workflows.
|
and workflows.
|
||||||
|
|
||||||
Implementing it may be as simple as passing --error-unmatch to git
|
Implementing it may be as simple as passing --error-unmatch to git
|
||||||
ls-files.
|
ls-files. (And disable git-annex's code that checks for parameters that are
|
||||||
|
not existing files.)
|
||||||
|
|
||||||
It could be an option, but I don't really consider an option as fixing the
|
It could be an option, but I don't really consider an option as fixing the
|
||||||
surprising behavior. And once you know git-annex behaves this way, I think
|
surprising behavior. And once you know git-annex behaves this way, I think
|
||||||
|
|
|
@ -0,0 +1,17 @@
|
||||||
|
[[!comment format=mdwn
|
||||||
|
username="joey"
|
||||||
|
subject="""comment 3"""
|
||||||
|
date="2020-05-28T19:49:58Z"
|
||||||
|
content="""
|
||||||
|
Implemented annex.skipunknown git config, that will make it error out when
|
||||||
|
given a file that git doesn't know about.
|
||||||
|
|
||||||
|
Not default yet, will be in a couple of years.
|
||||||
|
[[todo/complete_annex.skipunknown_transition_in_2022]]
|
||||||
|
|
||||||
|
As to git-annex skipping non-annexed files, I'm leaning toward keeping it
|
||||||
|
the way it is, and it's not really the subject of this bug report, except
|
||||||
|
maybe that it's not entirely consistent with the annex.skipunknown
|
||||||
|
behavior for non-git files. If users complain about it, I'll consider it
|
||||||
|
again.
|
||||||
|
"""]]
|
|
@ -51,3 +51,7 @@ It would be nice if git-annex could give an error to explain why the unlock fail
|
||||||
### Have you had any luck using git-annex before? (Sometimes we get tired of reading bug reports all day and a lil' positive end note does wonders)
|
### Have you had any luck using git-annex before? (Sometimes we get tired of reading bug reports all day and a lil' positive end note does wonders)
|
||||||
|
|
||||||
git-annex is amazing, I use it all the time. Thanks!
|
git-annex is amazing, I use it all the time. Thanks!
|
||||||
|
|
||||||
|
> annex.skipunknown false will make git-annex error out in this situation.
|
||||||
|
> That will become the default in a couple of years, but can be set already
|
||||||
|
> by those who don't like the behavior of skipping. [[done]] --[[Joey]]
|
||||||
|
|
|
@ -880,6 +880,28 @@ Like other git commands, git-annex is configured via `.git/config`.
|
||||||
|
|
||||||
The default reserve is 1 megabyte.
|
The default reserve is 1 megabyte.
|
||||||
|
|
||||||
|
* `annex.skipunknown`
|
||||||
|
|
||||||
|
Set to true to make commands like "git-annex get" silently skip over
|
||||||
|
items that are listed in the command line, but are not checked into git.
|
||||||
|
|
||||||
|
Set to false to make it an error for commands like "git-annex get"
|
||||||
|
to be asked to operate on files that are not checked into git.
|
||||||
|
|
||||||
|
The default is currently true, but is planned to change to false in a
|
||||||
|
release in 2022.
|
||||||
|
|
||||||
|
Note that, when annex.skipunknown is false, a command like "git-annex get ."
|
||||||
|
will fail if no files in the current directory are checked into git,
|
||||||
|
but a command like "git-annex get" will not fail, because the current
|
||||||
|
directory is not listed, but is implicit. Commands like "git-annex get foo/"
|
||||||
|
will fail if no files in the directory are checked into git, but if
|
||||||
|
at least one file is, it will ignore other files that are not. This is
|
||||||
|
all the same as the behavior of "git-ls files --error-unmatch".
|
||||||
|
|
||||||
|
Also note that git-annex skips files that are checked into git, but are
|
||||||
|
not annexed files, this setting does not affect that.
|
||||||
|
|
||||||
* `annex.largefiles`
|
* `annex.largefiles`
|
||||||
|
|
||||||
Used to configure which files are large enough to be added to the annex.
|
Used to configure which files are large enough to be added to the annex.
|
||||||
|
|
|
@ -0,0 +1,4 @@
|
||||||
|
annex.skipunknown should be changed to default to false in early 2022.
|
||||||
|
This transition was started in mid 2020 and there should have been plenty
|
||||||
|
of time for people to learn about it and either set their preferred
|
||||||
|
behavior or change workflows for the new behavior.
|
Loading…
Reference in a new issue