89b2542d3c
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.
57 lines
1.4 KiB
Haskell
57 lines
1.4 KiB
Haskell
{- git-annex command
|
|
-
|
|
- Copyright 2017 Joey Hess <id@joeyh.name>
|
|
-
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
|
-}
|
|
|
|
module Command.Inprogress where
|
|
|
|
import Command
|
|
import Annex.Transfer
|
|
|
|
import qualified Data.Set as S
|
|
|
|
cmd :: Command
|
|
cmd = noCommit $ noMessages $ command "inprogress" SectionQuery
|
|
"access files while they're being downloaded"
|
|
paramPaths (seek <$$> optParser)
|
|
|
|
data InprogressOptions = InprogressOptions
|
|
{ inprogressFiles :: CmdParams
|
|
, keyOptions :: Maybe KeyOptions
|
|
}
|
|
|
|
optParser :: CmdParamsDesc -> Parser InprogressOptions
|
|
optParser desc = InprogressOptions
|
|
<$> cmdParams desc
|
|
<*> optional (parseAllOption <|> parseSpecificKeyOption)
|
|
|
|
seek :: InprogressOptions -> CommandSeek
|
|
seek o = do
|
|
ts <- map (transferKey . fst) <$> getTransfers
|
|
case keyOptions o of
|
|
Just WantAllKeys ->
|
|
forM_ ts $ commandAction . start'
|
|
Just (WantSpecificKey k)
|
|
| k `elem` ts -> commandAction (start' k)
|
|
| otherwise -> commandAction stop
|
|
_ -> do
|
|
let s = S.fromList ts
|
|
withFilesInGit ww
|
|
(commandAction . (whenAnnexed (start s)))
|
|
=<< workTreeItems ww (inprogressFiles o)
|
|
where
|
|
ww = WarnUnmatchLsFiles
|
|
|
|
start :: S.Set Key -> RawFilePath -> Key -> CommandStart
|
|
start s _file k
|
|
| S.member k s = start' k
|
|
| otherwise = stop
|
|
|
|
start' :: Key -> CommandStart
|
|
start' k = startingCustomOutput k $ do
|
|
tmpf <- fromRepo $ gitAnnexTmpObjectLocation k
|
|
whenM (liftIO $ doesFileExist tmpf) $
|
|
liftIO $ putStrLn tmpf
|
|
next $ return True
|