--auto is no longer a global option; only get, drop, and copy accept it.

Not a behavior change unless you were passing it to a command that ignored it.
This commit is contained in:
Joey Hess 2015-03-25 17:06:14 -04:00
parent 59e0df02ec
commit cd6b62f35e
19 changed files with 86 additions and 69 deletions

View file

@ -100,7 +100,6 @@ data AnnexState = AnnexState
, output :: MessageState , output :: MessageState
, force :: Bool , force :: Bool
, fast :: Bool , fast :: Bool
, auto :: Bool
, daemon :: Bool , daemon :: Bool
, branchstate :: BranchState , branchstate :: BranchState
, repoqueue :: Maybe Git.Queue.Queue , repoqueue :: Maybe Git.Queue.Queue
@ -146,7 +145,6 @@ newState c r = AnnexState
, output = defaultMessageState , output = defaultMessageState
, force = False , force = False
, fast = False , fast = False
, auto = False
, daemon = False , daemon = False
, branchstate = startBranchState , branchstate = startBranchState
, repoqueue = Nothing , repoqueue = Nothing

View file

@ -142,3 +142,6 @@ timeLimitOption :: Option
timeLimitOption = Option ['T'] ["time-limit"] timeLimitOption = Option ['T'] ["time-limit"]
(ReqArg Limit.addTimeLimit paramTime) (ReqArg Limit.addTimeLimit paramTime)
"stop after the specified amount of time" "stop after the specified amount of time"
autoOption :: Option
autoOption = flagOption ['a'] "auto" "automatic mode"

View file

@ -30,8 +30,6 @@ commonOptions =
"allow actions that may lose annexed data" "allow actions that may lose annexed data"
, Option ['F'] ["fast"] (NoArg (setfast True)) , Option ['F'] ["fast"] (NoArg (setfast True))
"avoid slow operations" "avoid slow operations"
, Option ['a'] ["auto"] (NoArg (setauto True))
"automatic mode"
, Option ['q'] ["quiet"] (NoArg (Annex.setOutput QuietOutput)) , Option ['q'] ["quiet"] (NoArg (Annex.setOutput QuietOutput))
"avoid verbose output" "avoid verbose output"
, Option ['v'] ["verbose"] (NoArg (Annex.setOutput NormalOutput)) , Option ['v'] ["verbose"] (NoArg (Annex.setOutput NormalOutput))
@ -50,7 +48,6 @@ commonOptions =
where where
setforce v = Annex.changeState $ \s -> s { Annex.force = v } setforce v = Annex.changeState $ \s -> s { Annex.force = v }
setfast v = Annex.changeState $ \s -> s { Annex.fast = v } setfast v = Annex.changeState $ \s -> s { Annex.fast = v }
setauto v = Annex.changeState $ \s -> s { Annex.auto = v }
setforcebackend v = Annex.changeState $ \s -> s { Annex.forcebackend = Just v } setforcebackend v = Annex.changeState $ \s -> s { Annex.forcebackend = Just v }
setdebug = Annex.changeGitConfig $ \c -> c { annexDebug = True } setdebug = Annex.changeGitConfig $ \c -> c { annexDebug = True }
unsetdebug = Annex.changeGitConfig $ \c -> c { annexDebug = False } unsetdebug = Annex.changeGitConfig $ \c -> c { annexDebug = False }

View file

@ -173,13 +173,12 @@ withNothing _ _ = error "This command takes no parameters."
- -
- Otherwise, fall back to a regular CommandSeek action on - Otherwise, fall back to a regular CommandSeek action on
- whatever params were passed. -} - whatever params were passed. -}
withKeyOptions :: (Key -> CommandStart) -> CommandSeek -> CommandSeek withKeyOptions :: Bool -> (Key -> CommandStart) -> CommandSeek -> CommandSeek
withKeyOptions keyop fallbackop params = do withKeyOptions auto keyop fallbackop params = do
bare <- fromRepo Git.repoIsLocalBare bare <- fromRepo Git.repoIsLocalBare
allkeys <- Annex.getFlag "all" allkeys <- Annex.getFlag "all"
unused <- Annex.getFlag "unused" unused <- Annex.getFlag "unused"
specifickey <- Annex.getField "key" specifickey <- Annex.getField "key"
auto <- Annex.getState Annex.auto
when (auto && bare) $ when (auto && bare) $
error "Cannot use --auto in a bare repository" error "Cannot use --auto in a bare repository"
case (allkeys, unused, null params, specifickey) of case (allkeys, unused, null params, specifickey) of

View file

@ -17,13 +17,11 @@ module Command (
whenAnnexed, whenAnnexed,
ifAnnexed, ifAnnexed,
isBareRepo, isBareRepo,
checkAuto,
module ReExported module ReExported
) where ) where
import Common.Annex import Common.Annex
import qualified Backend import qualified Backend
import qualified Annex
import qualified Git import qualified Git
import Types.Command as ReExported import Types.Command as ReExported
import Types.Option as ReExported import Types.Option as ReExported
@ -79,7 +77,3 @@ ifAnnexed file yes no = maybe no yes =<< Backend.lookupFile file
isBareRepo :: Annex Bool isBareRepo :: Annex Bool
isBareRepo = fromRepo Git.repoIsLocalBare isBareRepo = fromRepo Git.repoIsLocalBare
checkAuto :: Annex Bool -> Annex Bool
checkAuto checker = ifM (Annex.getState Annex.auto)
( checker , return True )

View file

@ -15,26 +15,32 @@ import Annex.Wanted
import Config.NumCopies import Config.NumCopies
cmd :: [Command] cmd :: [Command]
cmd = [withOptions Command.Move.moveOptions $ command "copy" paramPaths seek cmd = [withOptions copyOptions $ command "copy" paramPaths seek
SectionCommon "copy content of files to/from another repository"] SectionCommon "copy content of files to/from another repository"]
copyOptions :: [Option]
copyOptions = Command.Move.moveOptions ++ [autoOption]
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do
to <- getOptionField toOption Remote.byNameWithUUID to <- getOptionField toOption Remote.byNameWithUUID
from <- getOptionField fromOption Remote.byNameWithUUID from <- getOptionField fromOption Remote.byNameWithUUID
withKeyOptions auto <- getOptionFlag autoOption
withKeyOptions auto
(Command.Move.startKey to from False) (Command.Move.startKey to from False)
(withFilesInGit $ whenAnnexed $ start to from) (withFilesInGit $ whenAnnexed $ start auto to from)
ps ps
{- 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
- sending non-preferred content. -} - sending non-preferred content. -}
start :: Maybe Remote -> Maybe Remote -> FilePath -> Key -> CommandStart start :: Bool -> Maybe Remote -> Maybe Remote -> FilePath -> Key -> CommandStart
start to from file key = stopUnless shouldCopy $ start auto to from file key = stopUnless shouldCopy $
Command.Move.start to from False file key Command.Move.start to from False file key
where where
shouldCopy = checkAuto (check <||> numCopiesCheck file key (<)) shouldCopy
check = case to of | auto = want <||> numCopiesCheck file key (<)
| otherwise = return True
want = case to of
Nothing -> wantGet False (Just key) (Just file) Nothing -> wantGet False (Just key) (Just file)
Just r -> wantSend False (Just key) (Just file) (Remote.uuid r) Just r -> wantSend False (Just key) (Just file) (Remote.uuid r)

View file

@ -27,7 +27,7 @@ cmd = [withOptions (dropOptions) $ command "drop" paramPaths seek
SectionCommon "indicate content of files not currently wanted"] SectionCommon "indicate content of files not currently wanted"]
dropOptions :: [Option] dropOptions :: [Option]
dropOptions = dropFromOption : annexedMatchingOptions dropOptions = dropFromOption : annexedMatchingOptions ++ [autoOption]
dropFromOption :: Option dropFromOption :: Option
dropFromOption = fieldOption ['f'] "from" paramRemote "drop content from a remote" dropFromOption = fieldOption ['f'] "from" paramRemote "drop content from a remote"
@ -35,11 +35,12 @@ dropFromOption = fieldOption ['f'] "from" paramRemote "drop content from a remot
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do
from <- getOptionField dropFromOption Remote.byNameWithUUID from <- getOptionField dropFromOption Remote.byNameWithUUID
withFilesInGit (whenAnnexed $ start from) ps auto <- getOptionFlag autoOption
withFilesInGit (whenAnnexed $ start auto from) ps
start :: Maybe Remote -> FilePath -> Key -> CommandStart start :: Bool -> Maybe Remote -> FilePath -> Key -> CommandStart
start from file key = checkDropAuto from file key $ \numcopies -> start auto from file key = checkDropAuto auto from file key $ \numcopies ->
stopUnless (checkAuto $ wantDrop False (Remote.uuid <$> from) (Just key) (Just file)) $ stopUnless want $
case from of case from of
Nothing -> startLocal (Just file) numcopies key Nothing Nothing -> startLocal (Just file) numcopies key Nothing
Just remote -> do Just remote -> do
@ -47,6 +48,10 @@ start from file key = checkDropAuto from file key $ \numcopies ->
if Remote.uuid remote == u if Remote.uuid remote == u
then startLocal (Just file) numcopies key Nothing then startLocal (Just file) numcopies key Nothing
else startRemote (Just file) numcopies key remote else startRemote (Just file) numcopies key remote
where
want
| auto = wantDrop False (Remote.uuid <$> from) (Just key) (Just file)
| otherwise = return True
startLocal :: AssociatedFile -> NumCopies -> Key -> Maybe Remote -> CommandStart startLocal :: AssociatedFile -> NumCopies -> Key -> Maybe Remote -> CommandStart
startLocal afile numcopies key knownpresentremote = stopUnless (inAnnex key) $ do startLocal afile numcopies key knownpresentremote = stopUnless (inAnnex key) $ do
@ -182,17 +187,16 @@ requiredContent = do
{- In auto mode, only runs the action if there are enough {- In auto mode, only runs the action if there are enough
- copies on other semitrusted repositories. -} - copies on other semitrusted repositories. -}
checkDropAuto :: Maybe Remote -> FilePath -> Key -> (NumCopies -> CommandStart) -> CommandStart checkDropAuto :: Bool -> Maybe Remote -> FilePath -> Key -> (NumCopies -> CommandStart) -> CommandStart
checkDropAuto mremote file key a = do checkDropAuto auto mremote file key a = go =<< getFileNumCopies file
numcopies <- getFileNumCopies file
Annex.getState Annex.auto >>= auto numcopies
where where
auto numcopies False = a numcopies go numcopies
auto numcopies True = do | auto = do
locs <- Remote.keyLocations key locs <- Remote.keyLocations key
uuid <- getUUID uuid <- getUUID
let remoteuuid = fromMaybe uuid $ Remote.uuid <$> mremote let remoteuuid = fromMaybe uuid $ Remote.uuid <$> mremote
locs' <- trustExclude UnTrusted $ filter (/= remoteuuid) locs locs' <- trustExclude UnTrusted $ filter (/= remoteuuid) locs
if NumCopies (length locs') >= numcopies if NumCopies (length locs') >= numcopies
then a numcopies then a numcopies
else stop else stop
| otherwise = a numcopies

View file

@ -69,7 +69,7 @@ seek ps = do
from <- getOptionField fsckFromOption Remote.byNameWithUUID from <- getOptionField fsckFromOption Remote.byNameWithUUID
u <- maybe getUUID (pure . Remote.uuid) from u <- maybe getUUID (pure . Remote.uuid) from
i <- getIncremental u i <- getIncremental u
withKeyOptions withKeyOptions False
(\k -> startKey i k =<< getNumCopies) (\k -> startKey i k =<< getNumCopies)
(withFilesInGit $ whenAnnexed $ start from i) (withFilesInGit $ whenAnnexed $ start from i)
ps ps

View file

@ -21,20 +21,23 @@ cmd = [withOptions getOptions $ command "get" paramPaths seek
SectionCommon "make content of annexed files available"] SectionCommon "make content of annexed files available"]
getOptions :: [Option] getOptions :: [Option]
getOptions = fromOption : annexedMatchingOptions ++ keyOptions getOptions = fromOption : annexedMatchingOptions ++ keyOptions ++ [autoOption]
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do
from <- getOptionField fromOption Remote.byNameWithUUID from <- getOptionField fromOption Remote.byNameWithUUID
withKeyOptions auto <- getOptionFlag autoOption
withKeyOptions auto
(startKeys from) (startKeys from)
(withFilesInGit $ whenAnnexed $ start from) (withFilesInGit $ whenAnnexed $ start auto from)
ps ps
start :: Maybe Remote -> FilePath -> Key -> CommandStart start :: Bool -> Maybe Remote -> FilePath -> Key -> CommandStart
start from file key = start' expensivecheck from key (Just file) start auto from file key = start' expensivecheck from key (Just file)
where where
expensivecheck = checkAuto (numCopiesCheck file key (<) <||> wantGet False (Just key) (Just file)) expensivecheck
| auto = numCopiesCheck file key (<) <||> wantGet False (Just key) (Just file)
| otherwise = return True
startKeys :: Maybe Remote -> Key -> CommandStart startKeys :: Maybe Remote -> Key -> CommandStart
startKeys from key = start' (return True) from key Nothing startKeys from key = start' (return True) from key Nothing

View file

@ -61,7 +61,7 @@ seek ps = do
let seeker = if null modmeta let seeker = if null modmeta
then withFilesInGit then withFilesInGit
else withFilesInGitNonRecursive else withFilesInGitNonRecursive
withKeyOptions withKeyOptions False
(startKeys now getfield modmeta) (startKeys now getfield modmeta)
(seeker $ whenAnnexed $ start now getfield modmeta) (seeker $ whenAnnexed $ start now getfield modmeta)
ps ps

View file

@ -14,19 +14,20 @@ import qualified Command.Drop
import qualified Command.Get import qualified Command.Get
import qualified Remote import qualified Remote
import Annex.Content import Annex.Content
import qualified Annex
import Config.NumCopies import Config.NumCopies
cmd :: [Command] cmd :: [Command]
cmd = [withOptions (fromToOptions ++ annexedMatchingOptions ++ keyOptions) $ cmd = [withOptions mirrorOptions $ command "mirror" paramPaths seek
command "mirror" paramPaths seek SectionCommon "mirror content of files to/from another repository"]
SectionCommon "mirror content of files to/from another repository"]
mirrorOptions :: [Option]
mirrorOptions = fromToOptions ++ annexedMatchingOptions ++ keyOptions
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do
to <- getOptionField toOption Remote.byNameWithUUID to <- getOptionField toOption Remote.byNameWithUUID
from <- getOptionField fromOption Remote.byNameWithUUID from <- getOptionField fromOption Remote.byNameWithUUID
withKeyOptions withKeyOptions False
(startKey to from Nothing) (startKey to from Nothing)
(withFilesInGit $ whenAnnexed $ start to from) (withFilesInGit $ whenAnnexed $ start to from)
ps ps
@ -35,16 +36,13 @@ start :: Maybe Remote -> Maybe Remote -> FilePath -> Key -> CommandStart
start to from file = startKey to from (Just file) start to from file = startKey to from (Just file)
startKey :: Maybe Remote -> Maybe Remote -> Maybe FilePath -> Key -> CommandStart startKey :: Maybe Remote -> Maybe Remote -> Maybe FilePath -> Key -> CommandStart
startKey to from afile key = do startKey to from afile key =
noAuto
case (from, to) of case (from, to) of
(Nothing, Nothing) -> error "specify either --from or --to" (Nothing, Nothing) -> error "specify either --from or --to"
(Nothing, Just r) -> mirrorto r (Nothing, Just r) -> mirrorto r
(Just r, Nothing) -> mirrorfrom r (Just r, Nothing) -> mirrorfrom r
_ -> error "only one of --from or --to can be specified" _ -> error "only one of --from or --to can be specified"
where where
noAuto = whenM (Annex.getState Annex.auto) $
error "--auto is not supported for mirror"
mirrorto r = ifM (inAnnex key) mirrorto r = ifM (inAnnex key)
( Command.Move.toStart r False afile key ( Command.Move.toStart r False afile key
, do , do

View file

@ -28,7 +28,7 @@ seek :: CommandSeek
seek ps = do seek ps = do
to <- getOptionField toOption Remote.byNameWithUUID to <- getOptionField toOption Remote.byNameWithUUID
from <- getOptionField fromOption Remote.byNameWithUUID from <- getOptionField fromOption Remote.byNameWithUUID
withKeyOptions withKeyOptions False
(startKey to from True) (startKey to from True)
(withFilesInGit $ whenAnnexed $ start to from True) (withFilesInGit $ whenAnnexed $ start to from True)
ps ps
@ -41,15 +41,11 @@ startKey to from move = start' to from move Nothing
start' :: Maybe Remote -> Maybe Remote -> Bool -> AssociatedFile -> Key -> CommandStart start' :: Maybe Remote -> Maybe Remote -> Bool -> AssociatedFile -> Key -> CommandStart
start' to from move afile key = do start' to from move afile key = do
noAuto
case (from, to) of case (from, to) of
(Nothing, Nothing) -> error "specify either --from or --to" (Nothing, Nothing) -> error "specify either --from or --to"
(Nothing, Just dest) -> toStart dest move afile key (Nothing, Just dest) -> toStart dest move afile key
(Just src, Nothing) -> fromStart src move afile key (Just src, Nothing) -> fromStart src move afile key
_ -> error "only one of --from or --to can be specified" _ -> error "only one of --from or --to can be specified"
where
noAuto = when move $ whenM (Annex.getState Annex.auto) $ error
"--auto is not supported for move"
showMoveAction :: Bool -> Key -> AssociatedFile -> Annex () showMoveAction :: Bool -> Key -> AssociatedFile -> Annex ()
showMoveAction move = showStart' (if move then "move" else "copy") showMoveAction move = showStart' (if move then "move" else "copy")

View file

@ -23,7 +23,7 @@ cmd = [noCommit $ withOptions (jsonOption : annexedMatchingOptions ++ keyOptions
seek :: CommandSeek seek :: CommandSeek
seek ps = do seek ps = do
m <- remoteMap id m <- remoteMap id
withKeyOptions withKeyOptions False
(startKeys m) (startKeys m)
(withFilesInGit $ whenAnnexed $ start m) (withFilesInGit $ whenAnnexed $ start m)
ps ps

3
debian/changelog vendored
View file

@ -9,6 +9,9 @@ git-annex (5.20150318) UNRELEASED; urgency=medium
destination backend. Useful in rare cases. destination backend. Useful in rare cases.
* Man pages for individual commands now available, and can be * Man pages for individual commands now available, and can be
opened using "git annex help <command>" opened using "git annex help <command>"
* --auto is no longer a global option; only get, drop, and copy
accept it. (Not a behavior change unless you were passing it to a
command that ignored it.)
-- Joey Hess <id@joeyh.name> Thu, 19 Mar 2015 17:05:32 -0400 -- Joey Hess <id@joeyh.name> Thu, 19 Mar 2015 17:05:32 -0400

View file

@ -22,6 +22,12 @@ Copies the content of files from or to another remote.
Use this option to copy the content of files from the local repository Use this option to copy the content of files from the local repository
to the specified remote. to the specified remote.
* `--auto`
Rather than copying all files, only copy files that don't yet have
the desired number of copies, or that are preferred content of the
destination repository. See [[git-annex-preferred-content]](1)
* `--fast` * `--fast`
Avoid contacting the remote to check if it has every file when copying Avoid contacting the remote to check if it has every file when copying

View file

@ -22,6 +22,12 @@ safe to do so.
this option can specifiy a remote from which the files' this option can specifiy a remote from which the files'
contents should be removed. contents should be removed.
* `--auto`
Rather than trying to drop all specified files, drop only files that
are not preferred content of the repository.
See [[git-annex-preferred-content]](1)
* `--force` * `--force`
Use this option with care! It bypasses safety checks, and forces Use this option with care! It bypasses safety checks, and forces

View file

@ -14,6 +14,12 @@ or transferring them from some kind of key-value store.
# OPTIONS # OPTIONS
* `--auto`
Rather than getting all files, get only files that don't yet have
the desired number of copies, or that are preferred content of the
repository. See [[git-annex-preferred-content]](1)
* `--from=remote` * `--from=remote`
Normally git-annex will choose which remotes to get the content Normally git-annex will choose which remotes to get the content

View file

@ -36,6 +36,10 @@ when a repository in the group has its preferred content set to
[[git-annex]](1) [[git-annex]](1)
[[git-annex-vicfg]](1)
[[git-annex-wanted]](1)
# AUTHOR # AUTHOR
Joey Hess <id@joeyh.name> Joey Hess <id@joeyh.name>

View file

@ -653,12 +653,6 @@ may not be explicitly listed on their individual man pages.
Enable less expensive, but also less thorough versions of some commands. Enable less expensive, but also less thorough versions of some commands.
What is avoided depends on the command. What is avoided depends on the command.
* `--auto`
Enable automatic mode. Commands that get, drop, or move file contents
will only do so when needed to help satisfy the setting of numcopies,
and preferred content configuration.
* `--quiet` * `--quiet`
Avoid the default verbose display of what is done; only show errors Avoid the default verbose display of what is done; only show errors