1d1054faa6
Added -z option to git-annex commands that use --batch, useful for supporting filenames containing newlines. It only controls input to --batch, the output will still be line delimited unless --json or etc is used to get some other output. While git often makes -z affect both input and output, I don't like trying them together, and making it affect output would have been a significant complication, and also git-annex output is generally not intended to be machine parsed, unless using --json or a format option. Commands that take pairs like "file key" still separate them with a space in --batch mode. All such commands take care to support filenames with spaces when parsing that, so there was no need to change it, and it would have needed significant changes to the batch machinery to separate tose with a null. To make fromkey and registerurl support -z, I had to give them a --batch option. The implicit batch mode they enter when not provided with input parameters does not support -z as that would have complicated option parsing. Seemed better to move these toward using the same --batch as everything else, though the implicit batch mode can still be used. This commit was sponsored by Ole-Morten Duesund on Patreon.
156 lines
3.9 KiB
Haskell
156 lines
3.9 KiB
Haskell
{- git-annex command
|
|
-
|
|
- Copyright 2010-2017 Joey Hess <id@joeyh.name>
|
|
-
|
|
- Licensed under the GNU GPL version 3 or higher.
|
|
-}
|
|
|
|
module Command.Add where
|
|
|
|
import Command
|
|
import Annex.Ingest
|
|
import Logs.Location
|
|
import Annex.Content
|
|
import Annex.Content.Direct
|
|
import qualified Annex
|
|
import qualified Annex.Queue
|
|
import qualified Database.Keys
|
|
import Config
|
|
import Annex.FileMatcher
|
|
import Annex.Link
|
|
import Annex.Version
|
|
import Git.FilePath
|
|
|
|
cmd :: Command
|
|
cmd = notBareRepo $
|
|
withGlobalOptions [jobsOption, jsonOptions, fileMatchingOptions] $
|
|
command "add" SectionCommon "add files to annex"
|
|
paramPaths (seek <$$> optParser)
|
|
|
|
data AddOptions = AddOptions
|
|
{ addThese :: CmdParams
|
|
, includeDotFiles :: Bool
|
|
, batchOption :: BatchMode
|
|
, updateOnly :: Bool
|
|
}
|
|
|
|
optParser :: CmdParamsDesc -> Parser AddOptions
|
|
optParser desc = AddOptions
|
|
<$> cmdParams desc
|
|
<*> switch
|
|
( long "include-dotfiles"
|
|
<> help "don't skip dotfiles"
|
|
)
|
|
<*> parseBatchOption
|
|
<*> switch
|
|
( long "update"
|
|
<> short 'u'
|
|
<> help "only update tracked files"
|
|
)
|
|
|
|
seek :: AddOptions -> CommandSeek
|
|
seek o = allowConcurrentOutput $ do
|
|
matcher <- largeFilesMatcher
|
|
let gofile file = ifM (checkFileMatcher matcher file <||> Annex.getState Annex.force)
|
|
( start file
|
|
, ifM (annexAddSmallFiles <$> Annex.getGitConfig)
|
|
( startSmall file
|
|
, stop
|
|
)
|
|
)
|
|
case batchOption o of
|
|
Batch fmt
|
|
| updateOnly o ->
|
|
giveup "--update --batch is not supported"
|
|
| otherwise -> batchFilesMatching fmt gofile
|
|
NoBatch -> do
|
|
l <- workTreeItems (addThese o)
|
|
let go a = a gofile l
|
|
unless (updateOnly o) $
|
|
go (withFilesNotInGit (not $ includeDotFiles o))
|
|
go withFilesMaybeModified
|
|
ifM versionSupportsUnlockedPointers
|
|
( go withUnmodifiedUnlockedPointers
|
|
, unlessM isDirect $
|
|
go withFilesOldUnlocked
|
|
)
|
|
|
|
{- Pass file off to git-add. -}
|
|
startSmall :: FilePath -> CommandStart
|
|
startSmall file = do
|
|
showStart "add" file
|
|
next $ next $ addSmall file
|
|
|
|
addSmall :: FilePath -> Annex Bool
|
|
addSmall file = do
|
|
showNote "non-large file; adding content to git repository"
|
|
addFile file
|
|
|
|
addFile :: FilePath -> Annex Bool
|
|
addFile file = do
|
|
ps <- forceParams
|
|
Annex.Queue.addCommand "add" (ps++[Param "--"]) [file]
|
|
return True
|
|
|
|
start :: FilePath -> CommandStart
|
|
start file = do
|
|
ifM versionSupportsUnlockedPointers
|
|
( do
|
|
mk <- liftIO $ isPointerFile file
|
|
maybe go fixuppointer mk
|
|
, go
|
|
)
|
|
where
|
|
go = ifAnnexed file addpresent add
|
|
add = liftIO (catchMaybeIO $ getSymbolicLinkStatus file) >>= \case
|
|
Nothing -> stop
|
|
Just s
|
|
| not (isRegularFile s) && not (isSymbolicLink s) -> stop
|
|
| otherwise -> do
|
|
showStart "add" file
|
|
next $ if isSymbolicLink s
|
|
then next $ addFile file
|
|
else perform file
|
|
addpresent key = ifM versionSupportsUnlockedPointers
|
|
( liftIO (catchMaybeIO $ getSymbolicLinkStatus file) >>= \case
|
|
Just s | isSymbolicLink s -> fixuplink key
|
|
_ -> add
|
|
, ifM isDirect
|
|
( liftIO (catchMaybeIO $ getSymbolicLinkStatus file) >>= \case
|
|
Just s | isSymbolicLink s -> fixuplink key
|
|
_ -> ifM (goodContent key file)
|
|
( stop , add )
|
|
, fixuplink key
|
|
)
|
|
)
|
|
fixuplink key = do
|
|
-- the annexed symlink is present but not yet added to git
|
|
showStart "add" file
|
|
liftIO $ removeFile file
|
|
addLink file key Nothing
|
|
next $ next $
|
|
cleanup key =<< inAnnex key
|
|
fixuppointer key = do
|
|
-- the pointer file is present, but not yet added to git
|
|
showStart "add" file
|
|
Database.Keys.addAssociatedFile key =<< inRepo (toTopFilePath file)
|
|
next $ next $ addFile file
|
|
|
|
perform :: FilePath -> CommandPerform
|
|
perform file = do
|
|
lockingfile <- not <$> addUnlocked
|
|
let cfg = LockDownConfig
|
|
{ lockingFile = lockingfile
|
|
, hardlinkFileTmp = True
|
|
}
|
|
lockDown cfg file >>= ingestAdd >>= finish
|
|
where
|
|
finish (Just key) = next $ cleanup key True
|
|
finish Nothing = stop
|
|
|
|
cleanup :: Key -> Bool -> CommandCleanup
|
|
cleanup key hascontent = do
|
|
maybeShowJSON $ JSONChunk [("key", key2file key)]
|
|
when hascontent $
|
|
logStatus key InfoPresent
|
|
return True
|