summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJoey Hess <joeyh@joeyh.name>2021-01-06 14:11:08 -0400
committerJoey Hess <joeyh@joeyh.name>2021-01-06 14:15:19 -0400
commitcc896994572f19e0df77314c0cce7c3e88268322 (patch)
tree06dcd96d4a2d530c2c6b1b862bc2464ec517beac
parent428d228ee5d3a6c5c9a8802285f2d3269049a5dd (diff)
mincopies
This is conceptually very simple, just making a 1 that was hard coded be exposed as a config option. The hard part was plumbing all that, and dealing with complexities like reading it from git attributes at the same time that numcopies is read. Behavior change: When numcopies is set to 0, git-annex used to drop content without requiring any copies. Now to get that (highly unsafe) behavior, mincopies also needs to be set to 0. It seemed better to remove that edge case, than complicate mincopies by ignoring it when numcopies is 0. This commit was sponsored by Denis Dzyubenko on Patreon.
-rw-r--r--Annex.hs4
-rw-r--r--Annex/CheckAttr.hs10
-rw-r--r--Annex/Drop.hs41
-rw-r--r--Annex/NumCopies.hs127
-rw-r--r--Assistant/Threads/ConfigMonitor.hs1
-rw-r--r--CHANGELOG10
-rw-r--r--CmdLine/GitAnnex.hs2
-rw-r--r--CmdLine/GitAnnex/Options.hs8
-rw-r--r--Command/Drop.hs47
-rw-r--r--Command/DropUnused.hs17
-rw-r--r--Command/Fsck.hs2
-rw-r--r--Command/Import.hs4
-rw-r--r--Command/MinCopies.hs39
-rw-r--r--Command/Mirror.hs14
-rw-r--r--Command/Move.hs8
-rw-r--r--Command/NumCopies.hs17
-rw-r--r--Git/CheckAttr.hs31
-rw-r--r--Logs.hs4
-rw-r--r--Logs/NumCopies.hs26
-rw-r--r--Types/NumCopies.hs48
-rw-r--r--doc/copies.mdwn33
-rw-r--r--doc/git-annex-mincopies.mdwn41
-rw-r--r--doc/git-annex-numcopies.mdwn13
-rw-r--r--doc/git-annex-requirednumcopies.mdwn43
-rw-r--r--doc/git-annex.mdwn26
-rw-r--r--doc/internals.mdwn6
-rw-r--r--doc/todo/lockContent_for_special_remotes.mdwn5
-rw-r--r--doc/trust.mdwn7
-rw-r--r--git-annex.cabal1
29 files changed, 414 insertions, 221 deletions
diff --git a/Annex.hs b/Annex.hs
index bbdee2f060..dc3466e3ee 100644
--- a/Annex.hs
+++ b/Annex.hs
@@ -133,7 +133,9 @@ data AnnexState = AnnexState
, checkignorehandle :: Maybe (ResourcePool CheckIgnoreHandle)
, forcebackend :: Maybe String
, globalnumcopies :: Maybe NumCopies
+ , globalmincopies :: Maybe MinCopies
, forcenumcopies :: Maybe NumCopies
+ , forcemincopies :: Maybe MinCopies
, limit :: ExpandableMatcher Annex
, timelimit :: Maybe (Duration, POSIXTime)
, uuiddescmap :: Maybe UUIDDescMap
@@ -202,7 +204,9 @@ newState c r = do
, checkignorehandle = Nothing
, forcebackend = Nothing
, globalnumcopies = Nothing
+ , globalmincopies = Nothing
, forcenumcopies = Nothing
+ , forcemincopies = Nothing
, limit = BuildingMatcher []
, timelimit = Nothing
, uuiddescmap = Nothing
diff --git a/Annex/CheckAttr.hs b/Annex/CheckAttr.hs
index a532c76df5..2de4fbc8a6 100644
--- a/Annex/CheckAttr.hs
+++ b/Annex/CheckAttr.hs
@@ -1,4 +1,4 @@
-{- git check-attr interface, with handle automatically stored in the Annex monad
+{- git check-attr interface
-
- Copyright 2012-2020 Joey Hess <id@joeyh.name>
-
@@ -7,6 +7,7 @@
module Annex.CheckAttr (
checkAttr,
+ checkAttrs,
checkAttrStop,
mkConcurrentCheckAttrHandle,
) where
@@ -22,14 +23,19 @@ import Annex.Concurrent.Utility
annexAttrs :: [Git.Attr]
annexAttrs =
[ "annex.backend"
- , "annex.numcopies"
, "annex.largefiles"
+ , "annex.numcopies"
+ , "annex.mincopies"
]
checkAttr :: Git.Attr -> RawFilePath -> Annex String
checkAttr attr file = withCheckAttrHandle $ \h ->
liftIO $ Git.checkAttr h attr file
+checkAttrs :: [Git.Attr] -> RawFilePath -> Annex [String]
+checkAttrs attrs file = withCheckAttrHandle $ \h ->
+ liftIO $ Git.checkAttrs h attrs file
+
withCheckAttrHandle :: (Git.CheckAttrHandle -> Annex a) -> Annex a
withCheckAttrHandle a =
maybe mkpool go =<< Annex.getState Annex.checkattrhandle
diff --git a/Annex/Drop.hs b/Annex/Drop.hs
index 00ca4d88a4..08654ff221 100644
--- a/Annex/Drop.hs
+++ b/Annex/Drop.hs
@@ -1,6 +1,6 @@
{- dropping of unwanted content
-
- - Copyright 2012-2014 Joey Hess <id@joeyh.name>
+ - Copyright 2012-2021 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
@@ -63,23 +63,30 @@ handleDropsFrom locs rs reason fromhere key afile si preverified runner = do
where
getcopies fs = do
(untrusted, have) <- trustPartition UnTrusted locs
- numcopies <- if null fs
- then getNumCopies
- else maximum <$> mapM getFileNumCopies fs
- return (NumCopies (length have), numcopies, S.fromList untrusted)
+ (numcopies, mincopies) <- if null fs
+ then (,) <$> getNumCopies <*> getMinCopies
+ else do
+ l <- mapM getFileNumMinCopies fs
+ return (maximum $ map fst l, maximum $ map snd l)
+ return (NumCopies (length have), numcopies, mincopies, S.fromList untrusted)
{- Check that we have enough copies still to drop the content.
- When the remote being dropped from is untrusted, it was not
- counted as a copy, so having only numcopies suffices. Otherwise,
- - we need more than numcopies to safely drop. -}
- checkcopies (have, numcopies, _untrusted) Nothing = have > numcopies
- checkcopies (have, numcopies, untrusted) (Just u)
+ - we need more than numcopies to safely drop.
+ -
+ - This is not the final check that it's safe to drop, but it
+ - avoids doing extra work to do that check later in cases where it
+ - will surely fail.
+ -}
+ checkcopies (have, numcopies, _mincopies, _untrusted) Nothing = have > numcopies
+ checkcopies (have, numcopies, _mincopies, untrusted) (Just u)
| S.member u untrusted = have >= numcopies
| otherwise = have > numcopies
- decrcopies (have, numcopies, untrusted) Nothing =
- (NumCopies (fromNumCopies have - 1), numcopies, untrusted)
- decrcopies v@(_have, _numcopies, untrusted) (Just u)
+ decrcopies (have, numcopies, mincopies, untrusted) Nothing =
+ (NumCopies (fromNumCopies have - 1), numcopies, mincopies, untrusted)
+ decrcopies v@(_have, _numcopies, _mincopies, untrusted) (Just u)
| S.member u untrusted = v
| otherwise = decrcopies v Nothing
@@ -105,8 +112,8 @@ handleDropsFrom locs rs reason fromhere key afile si preverified runner = do
, return n
)
- dodrop n@(have, numcopies, _untrusted) u a =
- ifM (safely $ runner $ a numcopies)
+ dodrop n@(have, numcopies, mincopies, _untrusted) u a =
+ ifM (safely $ runner $ a numcopies mincopies)
( do
liftIO $ debugM "drop" $ unwords
[ "dropped"
@@ -121,12 +128,12 @@ handleDropsFrom locs rs reason fromhere key afile si preverified runner = do
, return n
)
- dropl fs n = checkdrop fs n Nothing $ \numcopies ->
+ dropl fs n = checkdrop fs n Nothing $ \numcopies mincopies ->
stopUnless (inAnnex key) $
- Command.Drop.startLocal afile ai si numcopies key preverified
+ Command.Drop.startLocal afile ai si numcopies mincopies key preverified
- dropr fs r n = checkdrop fs n (Just $ Remote.uuid r) $ \numcopies ->
- Command.Drop.startRemote afile ai si numcopies key r
+ dropr fs r n = checkdrop fs n (Just $ Remote.uuid r) $ \numcopies mincopies ->
+ Command.Drop.startRemote afile ai si numcopies mincopies key r
ai = mkActionItem (key, afile)
diff --git a/Annex/NumCopies.hs b/Annex/NumCopies.hs
index 7b80e4c486..b76d71bda2 100644
--- a/Annex/NumCopies.hs
+++ b/Annex/NumCopies.hs
@@ -1,6 +1,6 @@
{- git-annex numcopies configuration and checking
-
- - Copyright 2014-2015 Joey Hess <id@joeyh.name>
+ - Copyright 2014-2021 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
@@ -10,10 +10,11 @@
module Annex.NumCopies (
module Types.NumCopies,
module Logs.NumCopies,
- getFileNumCopies,
- getAssociatedFileNumCopies,
+ getFileNumMinCopies,
+ getAssociatedFileNumMinCopies,
getGlobalFileNumCopies,
getNumCopies,
+ getMinCopies,
deprecatedNumCopies,
defaultNumCopies,
numCopiesCheck,
@@ -41,8 +42,11 @@ import Data.Typeable
defaultNumCopies :: NumCopies
defaultNumCopies = NumCopies 1
-fromSources :: [Annex (Maybe NumCopies)] -> Annex NumCopies
-fromSources = fromMaybe defaultNumCopies <$$> getM id
+defaultMinCopies :: MinCopies
+defaultMinCopies = MinCopies 1
+
+fromSourcesOr :: v -> [Annex (Maybe v)] -> Annex v
+fromSourcesOr v = fromMaybe v <$$> getM id
{- The git config annex.numcopies is deprecated. -}
deprecatedNumCopies :: Annex (Maybe NumCopies)
@@ -52,41 +56,93 @@ deprecatedNumCopies = annexNumCopies <$> Annex.getGitConfig
getForcedNumCopies :: Annex (Maybe NumCopies)
getForcedNumCopies = Annex.getState Annex.forcenumcopies
-{- Numcopies value from any of the non-.gitattributes configuration
+{- Value forced on the command line by --mincopies. -}
+getForcedMinCopies :: Annex (Maybe MinCopies)
+getForcedMinCopies = Annex.getState Annex.forcemincopies
+
+{- NumCopies value from any of the non-.gitattributes configuration
- sources. -}
getNumCopies :: Annex NumCopies
-getNumCopies = fromSources
+getNumCopies = fromSourcesOr defaultNumCopies
[ getForcedNumCopies
, getGlobalNumCopies
, deprecatedNumCopies
]
-{- Numcopies value for a file, from any configuration source, including the
- - deprecated git config. -}
-getFileNumCopies :: RawFilePath -> Annex NumCopies
-getFileNumCopies f = fromSources
- [ getForcedNumCopies
- , getFileNumCopies' f
- , deprecatedNumCopies
+{- MinCopies value from any of the non-.gitattributes configuration
+ - sources. -}
+getMinCopies :: Annex MinCopies
+getMinCopies = fromSourcesOr defaultMinCopies
+ [ getForcedMinCopies
+ , getGlobalMinCopies
]
-getAssociatedFileNumCopies :: AssociatedFile -> Annex NumCopies
-getAssociatedFileNumCopies (AssociatedFile afile) =
- maybe getNumCopies getFileNumCopies afile
+{- NumCopies and MinCopies value for a file, from any configuration source,
+ - including .gitattributes. -}
+getFileNumMinCopies :: RawFilePath -> Annex (NumCopies, MinCopies)
+getFileNumMinCopies f = do
+ fnumc <- getForcedNumCopies
+ fminc <- getForcedMinCopies
+ case (fnumc, fminc) of
+ (Just numc, Just minc) -> return (numc, minc)
+ (Just numc, Nothing) -> do
+ minc <- fromSourcesOr defaultMinCopies
+ [ snd <$> getNumMinCopiesAttr f
+ , getGlobalMinCopies
+ ]
+ return (numc, minc)
+ (Nothing, Just minc) -> do
+ numc <- fromSourcesOr defaultNumCopies
+ [ fst <$> getNumMinCopiesAttr f
+ , getGlobalNumCopies
+ , deprecatedNumCopies
+ ]
+ return (numc, minc)
+ (Nothing, Nothing) -> do
+ let fallbacknum = fromSourcesOr defaultNumCopies
+ [ getGlobalNumCopies
+ , deprecatedNumCopies
+ ]
+ let fallbackmin = fromSourcesOr defaultMinCopies
+ [ getGlobalMinCopies
+ ]
+ getNumMinCopiesAttr f >>= \case
+ (Just numc, Just minc) ->
+ return (numc, minc)
+ (Just numc, Nothing) -> (,)
+ <$> pure numc
+ <*> fallbackmin
+ (Nothing, Just minc) -> (,)
+ <$> fallbacknum
+ <*> pure minc
+ (Nothing, Nothing) -> (,)
+ <$> fallbacknum
+ <*> fallbackmin
+
+getAssociatedFileNumMinCopies :: AssociatedFile -> Annex (NumCopies, MinCopies)
+getAssociatedFileNumMinCopies (AssociatedFile (Just file)) =
+ getFileNumMinCopies file
+getAssociatedFileNumMinCopies (AssociatedFile Nothing) = (,)
+ <$> getNumCopies
+ <*> getMinCopies
{- This is the globally visible numcopies value for a file. So it does
- not include local configuration in the git config or command line
- options. -}
getGlobalFileNumCopies :: RawFilePath -> Annex NumCopies
-getGlobalFileNumCopies f = fromSources
- [ getFileNumCopies' f
+getGlobalFileNumCopies f = fromSourcesOr defaultNumCopies
+ [ fst <$> getNumMinCopiesAttr f
+ , getGlobalNumCopies
]
-getFileNumCopies' :: RawFilePath -> Annex (Maybe NumCopies)
-getFileNumCopies' file = maybe getGlobalNumCopies (return . Just) =<< getattr
- where
- getattr = (NumCopies <$$> readish)
- <$> checkAttr "annex.numcopies" file
+getNumMinCopiesAttr :: RawFilePath -> Annex (Maybe NumCopies, Maybe MinCopies)
+getNumMinCopiesAttr file =
+ checkAttrs ["annex.numcopies", "annex.mincopies"] file >>= \case
+ (n:m:[]) -> return
+ ( NumCopies <$> readish n
+ , MinCopies <$> readish m
+ )
+ _ -> error "internal"
{- Checks if numcopies are satisfied for a file by running a comparison
- between the number of (not untrusted) copies that are
@@ -102,7 +158,7 @@ numCopiesCheck file key vs = do
numCopiesCheck' :: RawFilePath -> (Int -> Int -> v) -> [UUID] -> Annex v
numCopiesCheck' file vs have = do
- NumCopies needed <- getFileNumCopies file
+ NumCopies needed <- fst <$> getFileNumMinCopies file
return $ length have `vs` needed
data UnVerifiedCopy = UnVerifiedRemote Remote | UnVerifiedHere
@@ -117,24 +173,25 @@ verifyEnoughCopiesToDrop
-> Key
-> Maybe ContentRemovalLock
-> NumCopies
+ -> MinCopies
-> [UUID] -- repos to skip considering (generally untrusted remotes)
-> [VerifiedCopy] -- copies already verified to exist
-> [UnVerifiedCopy] -- places to check to see if they have copies
-> (SafeDropProof -> Annex a) -- action to perform the drop
-> Annex a -- action to perform when unable to drop
-> Annex a
-verifyEnoughCopiesToDrop nolocmsg key removallock need skip preverified tocheck dropaction nodropaction =
+verifyEnoughCopiesToDrop nolocmsg key removallock neednum needmin skip preverified tocheck dropaction nodropaction =
helper [] [] preverified (nub tocheck) []
where
helper bad missing have [] lockunsupported =
- liftIO (mkSafeDropProof need have removallock) >>= \case
+ liftIO (mkSafeDropProof neednum needmin have removallock) >>= \case
Right proof -> dropaction proof
Left stillhave -> do
- notEnoughCopies key need stillhave (skip++missing) bad nolocmsg lockunsupported
+ notEnoughCopies key neednum needmin stillhave (skip++missing) bad nolocmsg lockunsupported
nodropaction
helper bad missing have (c:cs) lockunsupported
- | isSafeDrop need have removallock =
- liftIO (mkSafeDropProof need have removallock) >>= \case
+ | isSafeDrop neednum needmin have removallock =
+ liftIO (mkSafeDropProof neednum needmin have removallock) >>= \case
Right proof -> dropaction proof
Left stillhave -> helper bad missing stillhave (c:cs) lockunsupported
| otherwise = case c of
@@ -177,16 +234,16 @@ data DropException = DropException SomeException
instance Exception DropException
-notEnoughCopies :: Key -> NumCopies -> [VerifiedCopy] -> [UUID] -> [Remote] -> String -> [Remote] -> Annex ()
-notEnoughCopies key need have skip bad nolocmsg lockunsupported = do
+notEnoughCopies :: Key -> NumCopies -> MinCopies -> [VerifiedCopy] -> [UUID] -> [Remote] -> String -> [Remote] -> Annex ()
+notEnoughCopies key neednum needmin have skip bad nolocmsg lockunsupported = do
showNote "unsafe"
- if length have < fromNumCopies need
+ if length have < fromNumCopies neednum
then showLongNote $
"Could only verify the existence of " ++
- show (length have) ++ " out of " ++ show (fromNumCopies need) ++
+ show (length have) ++ " out of " ++ show (fromNumCopies neednum) ++
" necessary copies"
else do
- showLongNote $ "Unable to lock down 1 copy of file that is required to safely drop it."
+ showLongNote $ "Unable to lock down " ++ show (fromMinCopies needmin) ++ " copy of file that is required to safely drop it."
if null lockunsupported
then showLongNote "(This could have happened because of a concurrent drop, or because a remote has too old a version of git-annex-shell installed.)"
else showLongNote $ "These remotes do not support locking: "
diff --git a/Assistant/Threads/ConfigMonitor.hs b/Assistant/Threads/ConfigMonitor.hs
index a0d748df66..1e6372c5fc 100644
--- a/Assistant/Threads/ConfigMonitor.hs
+++ b/Assistant/Threads/ConfigMonitor.hs
@@ -64,6 +64,7 @@ configFilesActions =
, (trustLog, void $ liftAnnex trustMapLoad)
, (groupLog, void $ liftAnnex groupMapLoad)
, (numcopiesLog, void $ liftAnnex globalNumCopiesLoad)
+ , (mincopiesLog, void $ liftAnnex globalMinCopiesLoad)
, (scheduleLog, void updateScheduleLog)
-- Preferred and required content settings depend on most of the
-- other configs, so will be reloaded whenever any configs change.
diff --git a/CHANGELOG b/CHANGELOG
index ca841d47d0..7bed96d9a7 100644
--- a/CHANGELOG
+++ b/CHANGELOG
@@ -1,11 +1,13 @@
git-annex (8.20201130) UNRELEASED; urgency=medium
- * Added requirednumcopies configuration. This is like numcopies, but is
+ * Added mincopies configuration. This is like numcopies, but is
enforced even more strictly. While numcopies can be violated in
concurrent drop situations involving special remotes that do not
- support locking, requirednumcopies cannot be. The default value is 1,
- which is not a behavior change, but now it can be set to higher
- values if desired.
+ support locking, mincopies cannot be. The default value has always
+ been is 1, but now it can be set to higher values if desired.
+ * Behavior change: When numcopies is set to 0, git-annex used to drop
+ content without requiring any copies. Now to get that (highly unsafe)
+ behavior, mincopies also needs to be set to 0.
* add: Significantly speed up adding lots of non-large files to git,
by disabling the annex smudge filter when running git add.
* add --force-small: Run git add rather than updating the index itself,
diff --git a/CmdLine/GitAnnex.hs b/CmdLine/GitAnnex.hs
index 6d9cc4a438..08c03d7ae9 100644
--- a/CmdLine/GitAnnex.hs
+++ b/CmdLine/GitAnnex.hs
@@ -81,6 +81,7 @@ import qualified Command.Migrate
import qualified Command.Uninit
import qualified Command.Reinit
import qualified Command.NumCopies
+import qualified Command.MinCopies
import qualified Command.Trust
import qualified Command.Untrust
import qualified Command.Semitrust
@@ -157,6 +158,7 @@ cmds testoptparser testrunner mkbenchmarkgenerator =
, Command.PreCommit.cmd
, Command.PostReceive.cmd
, Command.NumCopies.cmd
+ , Command.MinCopies.cmd
, Command.Trust.cmd
, Command.Untrust.cmd
, Command.Semitrust.cmd
diff --git a/CmdLine/GitAnnex/Options.hs b/CmdLine/GitAnnex/Options.hs
index 2d9ccc518e..568fc7de4c 100644
--- a/CmdLine/GitAnnex/Options.hs
+++ b/CmdLine/GitAnnex/Options.hs
@@ -45,7 +45,12 @@ gitAnnexGlobalOptions :: [GlobalOption]
gitAnnexGlobalOptions = commonGlobalOptions ++
[ globalSetter setnumcopies $ option auto
( long "numcopies" <> short 'N' <> metavar paramNumber
- <> help "override default number of copies"
+ <> help "override desired number of copies"
+ <> hidden
+ )
+ , globalSetter setmincopies $ option auto
+ ( long "mincopies" <> short 'N' <> metavar paramNumber
+ <> help "override minimum number of copies"
<> hidden
)
, globalSetter (Remote.forceTrust Trusted) $ strOption
@@ -94,6 +99,7 @@ gitAnnexGlobalOptions = commonGlobalOptions ++
]
where
setnumcopies n = Annex.changeState $ \s -> s { Annex.forcenumcopies = Just $ NumCopies n }
+ setmincopies n = Annex.changeState $ \s -> s { Annex.forcemincopies = Just $ MinCopies n }
setuseragent v = Annex.changeState $ \s -> s { Annex.useragent = Just v }
setgitconfig v = Annex.addGitConfigOverride v
setdesktopnotify v = Annex.changeState $ \s -> s { Annex.desktopnotify = Annex.desktopnotify s <> v }
diff --git a/Command/Drop.hs b/Command/Drop.hs
index fd647682b8..acd863c6ae 100644
--- a/Command/Drop.hs
+++ b/Command/Drop.hs
@@ -1,6 +1,6 @@
{- git-annex command
-
- - Copyright 2010-2020 Joey Hess <id@joeyh.name>
+ - Copyright 2010-2021 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
@@ -84,11 +84,11 @@ start o from si file key = start' o from key afile ai si
start' :: DropOptions -> Maybe Remote -> Key -> AssociatedFile -> ActionItem -> SeekInput -> CommandStart
start' o from key afile ai si =
- checkDropAuto (autoMode o) from afile key $ \numcopies ->
+ checkDropAuto (autoMode o) from afile key $ \numcopies mincopies ->
stopUnless want $
case from of
- Nothing -> startLocal afile ai si numcopies key []
- Just remote -> startRemote afile ai si numcopies key remote
+ Nothing -> startLocal afile ai si numcopies mincopies key []
+ Just remote -> startRemote afile ai si numcopies mincopies key remote
where
want
| autoMode o = wantDrop False (Remote.uuid <$> from) (Just key) afile
@@ -97,21 +97,21 @@ start' o from key afile ai si =
startKeys :: DropOptions -> Maybe Remote -> (SeekInput, Key, ActionItem) -> CommandStart
startKeys o from (si, key, ai) = start' o from key (AssociatedFile Nothing) ai si
-startLocal :: AssociatedFile -> ActionItem -> SeekInput -> NumCopies -> Key -> [VerifiedCopy] -> CommandStart
-startLocal afile ai si numcopies key preverified =
+startLocal :: AssociatedFile -> ActionItem -> SeekInput -> NumCopies -> MinCopies -> Key -> [VerifiedCopy] -> CommandStart
+startLocal afile ai si numcopies mincopies key preverified =
starting "drop" (OnlyActionOn key ai) si $
- performLocal key afile numcopies preverified
+ performLocal key afile numcopies mincopies preverified
-startRemote :: AssociatedFile -> ActionItem -> SeekInput -> NumCopies -> Key -> Remote -> CommandStart
-startRemote afile ai si numcopies key remote =
+startRemote :: AssociatedFile -> ActionItem -> SeekInput -> NumCopies -> MinCopies -> Key -> Remote -> CommandStart
+startRemote afile ai si numcopies mincopies key remote =
starting ("drop " ++ Remote.name remote) (OnlyActionOn key ai) si $
- performRemote key afile numcopies remote
+ performRemote key afile numcopies mincopies remote
-performLocal :: Key -> AssociatedFile -> NumCopies -> [VerifiedCopy] -> CommandPerform
-performLocal key afile numcopies preverified = lockContentForRemoval key fallback $ \contentlock -> do
+performLocal :: Key -> AssociatedFile -> NumCopies -> MinCopies -> [VerifiedCopy] -> CommandPerform
+performLocal key afile numcopies mincopies preverified = lockContentForRemoval key fallback $ \contentlock -> do
u <- getUUID
(tocheck, verified) <- verifiableCopies key [u]
- doDrop u (Just contentlock) key afile numcopies [] (preverified ++ verified) tocheck
+ doDrop u (Just contentlock) key afile numcopies mincopies [] (preverified ++ verified) tocheck
( \proof -> do
liftIO $ debugM "drop" $ unwords
[ "Dropping from here"
@@ -133,12 +133,12 @@ performLocal key afile numcopies preverified = lockContentForRemoval key fallbac
-- to be done except for cleaning up.
fallback = next $ cleanupLocal key
-performRemote :: Key -> AssociatedFile -> NumCopies -> Remote -> CommandPerform
-performRemote key afile numcopies remote = do
+performRemote :: Key -> AssociatedFile -> NumCopies -> MinCopies -> Remote -> CommandPerform
+performRemote key afile numcopies mincopies remote = do
-- Filter the uuid it's being dropped from out of the lists of
-- places assumed to have the key, and places to check.
(tocheck, verified) <- verifiableCopies key [uuid]
- doDrop uuid Nothing key afile numcopies [uuid] verified tocheck
+ doDrop uuid Nothing key afile numcopies mincopies [uuid] verified tocheck
( \proof -> do
liftIO $ debugM "drop" $ unwords
[ "Dropping from remote"
@@ -178,17 +178,18 @@ doDrop
-> Key
-> AssociatedFile
-> NumCopies
+ -> MinCopies
-> [UUID]
-> [VerifiedCopy]
-> [UnVerifiedCopy]
-> (Maybe SafeDropProof -> CommandPerform, CommandPerform)
-> CommandPerform
-doDrop dropfrom contentlock key afile numcopies skip preverified check (dropaction, nodropaction) =
+doDrop dropfrom contentlock key afile numcopies mincopies skip preverified check (dropaction, nodropaction) =
ifM (Annex.getState Annex.force)
( dropaction Nothing
, ifM (checkRequiredContent dropfrom key afile)
( verifyEnoughCopiesToDrop nolocmsg key
- contentlock numcopies
+ contentlock numcopies mincopies
skip preverified check
(dropaction . Just)
(forcehint nodropaction)
@@ -216,17 +217,17 @@ requiredContent = do
{- In auto mode, only runs the action if there are enough
- copies on other semitrusted repositories. -}
-checkDropAuto :: Bool -> Maybe Remote -> AssociatedFile -> Key -> (NumCopies -> CommandStart) -> CommandStart
+checkDropAuto :: Bool -> Maybe Remote -> AssociatedFile -> Key -> (NumCopies -> MinCopies -> CommandStart) -> CommandStart
checkDropAuto automode mremote afile key a =
- go =<< getAssociatedFileNumCopies afile
+ go =<< getAssociatedFileNumMinCopies afile
where
- go numcopies
+ go (numcopies, mincopies)
| automode = do
locs <- Remote.keyLocations key
uuid <- getUUID
let remoteuuid = fromMaybe uuid $ Remote.uuid <$> mremote
locs' <- trustExclude UnTrusted $ filter (/= remoteuuid) locs
if NumCopies (length locs') >= numcopies
- then a numcopies
+ then a numcopies mincopies
else stop
- | otherwise = a numcopies
+ | otherwise = a numcopies mincopies
diff --git a/Command/DropUnused.hs b/Command/DropUnused.hs
index 17067b7d57..6c7ca34d41 100644
--- a/Command/DropUnused.hs
+++ b/Command/DropUnused.hs
@@ -35,20 +35,21 @@ optParser desc = DropUnusedOptions
seek :: DropUnusedOptions -> CommandSeek
seek o = do
numcopies <- getNumCopies
+ mincopies <- getMinCopies
from <- maybe (pure Nothing) (Just <$$> getParsed) (dropFrom o)
- withUnusedMaps (start from numcopies) (rangesToDrop o)
+ withUnusedMaps (start from numcopies mincopies) (rangesToDrop o)
-start :: Maybe Remote -> NumCopies -> UnusedMaps -> Int -> CommandStart
-start from numcopies = startUnused "dropunused"
- (perform from numcopies)
+start :: Maybe Remote -> NumCopies -> MinCopies -> UnusedMaps -> Int -> CommandStart
+start from numcopies mincopies = startUnused "dropunused"
+ (perform from numcopies mincopies)
(performOther gitAnnexBadLocation)
(performOther gitAnnexTmpObjectLocation)
-perform :: Maybe Remote -> NumCopies -> Key -> CommandPerform
-perform from numcopies key = case from of
+perform :: Maybe Remote -> NumCopies -> MinCopies -> Key -> CommandPerform
+perform from numcopies mincopies key = case from of
Just r -> do
showAction $ "from " ++ Remote.name r
- Command.Drop.performRemote key (AssociatedFile Nothing) numcopies r
+ Command.Drop.performRemote key (AssociatedFile Nothing) numcopies mincopies r
Nothing -> ifM (inAnnex key)
( droplocal
, ifM (objectFileExists key)
@@ -62,7 +63,7 @@ perform from numcopies key = case from of
)
)
where
- droplocal = Command.Drop.performLocal key (AssociatedFile Nothing) numcopies []
+ droplocal = Command.Drop.performLocal key (AssociatedFile Nothing) numcopies mincopies []
performOther :: (Key -> Git.Repo -> RawFilePath) -> Key -> CommandPerform
performOther filespec key = do
diff --git a/Command/Fsck.hs b/Command/Fsck.hs
index 439d68f4c1..7c23f87650 100644
--- a/Command/Fsck.hs
+++ b/Command/Fsck.hs
@@ -117,7 +117,7 @@ start :: Maybe Remote -> Incremental -> SeekInput -> RawFilePath -> Key -> Comma
start from inc si file key = Backend.getBackend (fromRawFilePath file) key >>= \case
Nothing -> stop
Just backend -> do
- numcopies <- getFileNumCopies file
+ (numcopies, _mincopies) <- getFileNumMinCopies file
case from of
Nothing -> go $ perform key file backend numcopies
Just r -> go $ performRemote key afile backend numcopies r
diff --git a/Command/Import.hs b/Command/Import.hs
index e1560ce93a..cbd344f0d9 100644
--- a/Command/Import.hs
+++ b/Command/Import.hs
@@ -279,10 +279,10 @@ verifyExisting :: Key -> RawFilePath -> (CommandPerform, CommandPerform) -> Comm
verifyExisting key destfile (yes, no) = do
-- Look up the numcopies setting for the file that it would be
-- imported to, if it were imported.
- need <- getFileNumCopies destfile
+ (needcopies, mincopies) <- getFileNumMinCopies destfile
(tocheck, preverified) <- verifiableCopies key []
- verifyEnoughCopiesToDrop [] key Nothing need [] preverified tocheck
+ verifyEnoughCopiesToDrop [] key Nothing needcopies mincopies [] preverified tocheck
(const yes) no
seekRemote :: Remote -> Branch -> Maybe TopFilePath -> Bool -> CheckGitIgnore -> CommandSeek
diff --git a/Command/MinCopies.hs b/Command/MinCopies.hs
new file mode 100644
index 0000000000..f8678073f3
--- /dev/null
+++ b/Command/MinCopies.hs
@@ -0,0 +1,39 @@
+{- git-annex command
+ -
+ - Copyright 2014-2021 Joey Hess <id@joeyh.name>
+ -
+ - Licensed under the GNU AGPL version 3 or higher.
+ -}
+
+module Command.MinCopies where
+
+import Command
+import Annex.NumCopies
+import qualified Command.NumCopies
+
+cmd :: Command
+cmd = noMessages $ command "mincopies" SectionSetup
+ "configure minimum number of copies"
+ paramNumber (withParams seek)
+
+seek :: CmdParams -> CommandSeek
+seek = withWords (commandAction . Command.NumCopies.start' "mincopies" startGet startSet)
+
+start :: [String] -> CommandStart
+start = Command.NumCopies.start' "mincopies" startGet startSet
+
+startGet :: CommandStart
+startGet = startingCustomOutput (ActionItemOther Nothing) $ next $ do
+ v <- getGlobalMinCopies
+ case v of
+ Just n -> liftIO $ putStrLn $ show $ fromMinCopies n
+ Nothing -> liftIO $ putStrLn "global mincopies is not set"
+ return True
+
+startSet :: Int -> CommandStart
+startSet n = startingUsualMessages "mincopies" ai si $ do
+ setGlobalMinCopies $ MinCopies n
+ next $ return True
+ where
+ ai = ActionItemOther (Just $ show n)
+ si = SeekInput [show n]
diff --git a/Command/Mirror.hs b/Command/Mirror.hs
index 28f7c92968..61c9a1f888 100644
--- a/Command/Mirror.hs
+++ b/Command/Mirror.hs
@@ -68,8 +68,8 @@ startKey o afile (si, key, ai) = case fromToOptions o of
ToRemote r -> checkFailedTransferDirection ai Upload $ ifM (inAnnex key)
( Command.Move.toStart Command.Move.RemoveNever afile key ai si =<< getParsed r
, do
- numcopies <- getnumcopies
- Command.Drop.startRemote afile ai si numcopies key =<< getParsed r
+ (numcopies, mincopies) <- getnummincopies
+ Command.Drop.startRemote afile ai si numcopies mincopies key =<< getParsed r
)
FromRemote r -> checkFailedTransferDirection ai Download $ do
haskey <- flip Remote.hasKey key =<< getParsed r
@@ -81,11 +81,11 @@ startKey o afile (si, key, ai) = case fromToOptions o of
)
Right False -> ifM (inAnnex key)
( do
- numcopies <- getnumcopies
- Command.Drop.startLocal afile ai si numcopies key []
+ (numcopies, mincopies) <- getnummincopies
+ Command.Drop.startLocal afile ai si numcopies mincopies key []
, stop
)
where
- getnumcopies = case afile of
- AssociatedFile Nothing -> getNumCopies
- AssociatedFile (Just af) -> getFileNumCopies af
+ getnummincopies = case afile of
+ AssociatedFile Nothing -> (,) <$> getNumCopies <*> getMinCopies
+ AssociatedFile (Just af) -> getFileNumMinCopies af
diff --git a/Command/Move.hs b/Command/Move.hs
index cc2db5de79..84533506af 100644
--- a/Command/Move.hs
+++ b/Command/Move.hs
@@ -165,10 +165,10 @@ toPerform dest removewhen key afile fastcheck isthere = do
willDropMakeItWorse srcuuid destuuid deststartedwithcopy key afile >>= \case
DropAllowed -> drophere setpresentremote contentlock "moved"
DropCheckNumCopies -> do
- numcopies <- getAssociatedFileNumCopies afile
+ (numcopies, mincopies) <- getAssociatedFileNumMinCopies afile
(tocheck, verified) <- verifiableCopies key [srcuuid]
verifyEnoughCopiesToDrop "" key (Just contentlock)
- numcopies [srcuuid] verified
+ numcopies mincopies [srcuuid] verified
(UnVerifiedRemote dest : tocheck)
(drophere setpresentremote contentlock . showproof)
(faileddrophere setpresentremote)
@@ -244,9 +244,9 @@ fromPerform src removewhen key afile = do
willDropMakeItWorse srcuuid destuuid deststartedwithcopy key afile >>= \case
DropAllowed -> dropremote "moved"
DropCheckNumCopies -> do
- numcopies <- getAssociatedFileNumCopies afile
+ (numcopies, mincopies) <- getAssociatedFileNumMinCopies afile
(tocheck, verified) <- verifiableCopies key [Remote.uuid src]
- verifyEnoughCopiesToDrop "" key Nothing numcopies [Remote.uuid src] verified
+ verifyEnoughCopiesToDrop "" key Nothing numcopies mincopies [Remote.uuid src] verified
tocheck (dropremote . showproof) faileddropremote
DropWorse -> faileddropremote
diff --git a/Command/NumCopies.hs b/Command/NumCopies.hs
index 5cd0bdc551..66a6d363bc 100644
--- a/Command/NumCopies.hs
+++ b/Command/NumCopies.hs
@@ -1,6 +1,6 @@
{- git-annex command
-
- - Copyright 2014 Joey Hess <id@joeyh.name>
+ - Copyright 2014-2021 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
@@ -20,17 +20,20 @@ seek :: CmdParams -> CommandSeek
seek = withWords (commandAction . start)
start :: [String] -> CommandStart
-start [] = startGet
-start [s] = case readish s of
+start = start' "numcopies" startGet startSet
+
+start' :: String -> CommandStart -> (Int -> CommandStart) -> [String] -> CommandStart
+start' _ startget _ [] = startget
+start' setting _ startset [s] = case readish s of
Nothing -> giveup $ "Bad number: " ++ s
Just n
- | n > 0 -> startSet n
+ | n > 0 -> startset n
| n == 0 -> ifM (Annex.getState Annex.force)
- ( startSet n
- , giveup "Setting numcopies to 0 is very unsafe. You will lose data! If you really want to do that, specify --force."
+ ( startset n
+ , giveup $ "Setting " ++ setting ++ " to 0 is very unsafe. You will lose data! If you really want to do that, specify --force."
)
| otherwise -> giveup "Number cannot be negative!"
-start _ = giveup "Specify a single number."
+start' _ _ _ _ = giveup "Specify a single number."
startGet :: CommandStart
startGet = startingCustomOutput (ActionItemOther Nothing) $ next $ do
diff --git a/Git/CheckAttr.hs b/Git/CheckAttr.hs
index fd7b502120..e4a7ea9d40 100644
--- a/Git/CheckAttr.hs
+++ b/Git/CheckAttr.hs
@@ -1,6 +1,6 @@
{- git check-attr interface
-
- - Copyright 2010-2020 Joey Hess <id@joeyh.name>
+ - Copyright 2010-2021 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
@@ -20,8 +20,8 @@ type CheckAttrHandle = (CoProcess.CoProcessHandle, [Attr], RawFilePath)
type Attr = String
-{- Starts git check-attr running to look up the specified gitattributes
- - values and returns a handle. -}
+{- Starts git check-attr running to look up the specified attributes
+ - and returns a handle. -}
checkAttrStart :: [Attr] -> Repo -> IO CheckAttrHandle
checkAttrStart attrs repo = do
currdir <- R.getCurrentDirectory
@@ -38,17 +38,24 @@ checkAttrStart attrs repo = do
checkAttrStop :: CheckAttrHandle -> IO ()
checkAttrStop (h, _, _) = CoProcess.stop h
-{- Gets an attribute of a file. When the attribute is not specified,
- - returns "" -}
checkAttr :: CheckAttrHandle -> Attr -> RawFilePath -> IO String
-checkAttr (h, attrs, currdir) want file = do
- pairs <- CoProcess.query h send (receive "")
- let vals = map snd $ filter (\(attr, _) -> attr == want) pairs
- case vals of
- ["unspecified"] -> return ""
- [v] -> return v
- _ -> error $ "unable to determine " ++ want ++ " attribute of " ++ fromRawFilePath file
+checkAttr h want file = checkAttrs h [want] file >>= return . \case
+ (v:_) -> v
+ [] -> ""
+
+{- Gets attributes of a file. When an attribute is not specified,
+ - returns "" for it. -}
+checkAttrs :: CheckAttrHandle -> [Attr] -> RawFilePath -> IO [String]
+checkAttrs (h, attrs, currdir) want file = do
+ l <- CoProcess.query h send (receive "")
+ return (getvals l want)
where
+ getvals _ [] = []
+ getvals l (x:xs) = case map snd $ filter (\(attr, _) -> attr == x) l of
+ ["unspecified"] -> "" : getvals l xs
+ [v] -> v : getvals l xs
+ _ -> error $ "unable to determine " ++ x ++ " attribute of " ++ fromRawFilePath file
+
send to = B.hPutStr to $ file' `B.snoc` 0
receive c from = do
s <- hGetSomeString from 1024
diff --git a/Logs.hs b/Logs.hs
index c7cec22272..50b955420f 100644
--- a/Logs.hs
+++ b/Logs.hs
@@ -90,6 +90,7 @@ presenceLogs config f =
otherLogs :: [RawFilePath]
otherLogs =
[ numcopiesLog
+ , mincopiesLog
, groupPreferredContentLog
]
@@ -99,6 +100,9 @@ uuidLog = "uuid.log"
numcopiesLog :: RawFilePath
numcopiesLog = "numcopies.log"
+mincopiesLog :: RawFilePath
+mincopiesLog = "mincopies.log"
+
configLog :: RawFilePath
configLog = "config.log"
diff --git a/Logs/NumCopies.hs b/Logs/NumCopies.hs
index 25a151cafd..63078196dc 100644
--- a/Logs/NumCopies.hs
+++ b/Logs/NumCopies.hs
@@ -1,6 +1,6 @@
{- git-annex numcopies log
-
- - Copyright 2014 Joey Hess <id@joeyh.name>
+ - Copyright 2014-2021 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
@@ -9,8 +9,11 @@
module Logs.NumCopies (
setGlobalNumCopies,
+ setGlobalMinCopies,
getGlobalNumCopies,
+ getGlobalMinCopies,
globalNumCopiesLoad,
+ globalMinCopiesLoad,
) where
import Annex.Common
@@ -23,19 +26,40 @@ instance SingleValueSerializable NumCopies where
serialize (NumCopies n) = encodeBS (show n)
deserialize = NumCopies <$$> readish . decodeBS
+instance SingleValueSerializable MinCopies where
+ serialize (MinCopies n) = encodeBS (show n)
+ deserialize = MinCopies <$$> readish . decodeBS
+
setGlobalNumCopies :: NumCopies -> Annex ()
setGlobalNumCopies new = do
curr <- getGlobalNumCopies
when (curr /= Just new) $
setLog numcopiesLog new
+setGlobalMinCopies :: MinCopies -> Annex ()
+setGlobalMinCopies new = do
+ curr <- getGlobalMinCopies
+ when (curr /= Just new) $
+ setLog mincopiesLog new
+
{- Value configured in the numcopies log. Cached for speed. -}
getGlobalNumCopies :: Annex (Maybe NumCopies)
getGlobalNumCopies = maybe globalNumCopiesLoad (return . Just)
=<< Annex.getState Annex.globalnumcopies
+{- Value configured in the mincopies log. Cached for speed. -}
+getGlobalMinCopies :: Annex (Maybe MinCopies)
+getGlobalMinCopies = maybe globalMinCopiesLoad (return . Just)
+ =<< Annex.getState Annex.globalmincopies
+
globalNumCopiesLoad :: Annex (Maybe NumCopies)
globalNumCopiesLoad = do
v <- getLog numcopiesLog
Annex.changeState $ \s -> s { Annex.globalnumcopies = v }
return v
+
+globalMinCopiesLoad :: Annex (Maybe MinCopies)
+globalMinCopiesLoad = do
+ v <- getLog mincopiesLog
+ Annex.changeState $ \s -> s { Annex.globalmincopies = v }
+ return v
diff --git a/Types/NumCopies.hs b/Types/NumCopies.hs
index 506befb10f..94421cb286 100644
--- a/Types/NumCopies.hs
+++ b/Types/NumCopies.hs
@@ -1,6 +1,6 @@
{- git-annex numcopies types
-
- - Copyright 2014-2015 Joey Hess <id@joeyh.name>
+ - Copyright 2014-2021 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
@@ -8,6 +8,8 @@
module Types.NumCopies (
NumCopies(..),
fromNumCopies,
+ MinCopies(..),
+ fromMinCopies,
VerifiedCopy(..),
checkVerifiedCopy,
invalidateVerifiedCopy,
@@ -39,6 +41,12 @@ newtype NumCopies = NumCopies Int
fromNumCopies :: NumCopies -> Int
fromNumCopies (NumCopies n) = n
+newtype MinCopies = MinCopies Int
+ deriving (Ord, Eq, Show)
+
+fromMinCopies :: MinCopies -> Int
+fromMinCopies (MinCopies n) = n
+
-- Indicates that a key's content is exclusively
-- locked locally, pending removal.
newtype ContentRemovalLock = ContentRemovalLock Key
@@ -130,33 +138,33 @@ withVerifiedCopy mk u check = bracketIO setup cleanup
- without requiring impractical amounts of locking.
-
- In particular, concurrent drop races may cause the number of copies
- - to fall below NumCopies, but it will never fall below 1.
+ - to fall below NumCopies, but it will never fall below MinCopies.
-}
-isSafeDrop :: NumCopies -> [VerifiedCopy] -> Maybe ContentRemovalLock -> Bool
+isSafeDrop :: NumCopies -> MinCopies -> [VerifiedCopy] -> Maybe ContentRemovalLock -> Bool
{- When a ContentRemovalLock is provided, the content is being
- dropped from the local repo. That lock will prevent other git repos
- that are concurrently dropping from using the local copy as a VerifiedCopy.
- So, no additional locking is needed; all we need is verifications
- of any kind of N other copies of the content. -}
-isSafeDrop (NumCopies n) l (Just (ContentRemovalLock _)) =
+isSafeDrop (NumCopies n) _ l (Just (ContentRemovalLock _)) =
length (deDupVerifiedCopies l) >= n
{- Dropping from a remote repo.
-
- - Unless numcopies is 0, at least one LockedCopy or TrustedCopy is required.
- - A LockedCopy prevents races between concurrent drops from
- - dropping the last copy, no matter what.
+ - To guarantee MinCopies is never violated, at least that many LockedCopy
+ - or TrustedCopy are required. A LockedCopy prevents races between
+ - concurrent drops from dropping the last copy, no matter what.
-
- - The other N-1 copies can be less strong verifications, like
- - RecentlyVerifiedCopy. While those are subject to concurrent drop races,
- - and so could be dropped all at once, causing numcopies to be violated,
- - this is the best that can be done without requiring that
+ - The other copies required by NumCopies can be less strong verifications,
+ - like RecentlyVerifiedCopy. While those are subject to concurrent drop
+ - races, and so could be dropped all at once, causing NumCopies to be
+ - violated, this is the best that can be done without requiring that
- all special remotes support locking.
-}
-isSafeDrop (NumCopies n) l Nothing
- | n == 0 = True
+isSafeDrop (NumCopies n) (MinCopies m) l Nothing
+ | n == 0 && m == 0 = True
| otherwise = and
[ length (deDupVerifiedCopies l) >= n
- , any fullVerification l
+ , length (filter fullVerification l) >= m
]
fullVerification :: VerifiedCopy -> Bool
@@ -165,14 +173,14 @@ fullVerification (TrustedCopy _) = True
fullVerification (RecentlyVerifiedCopy _) = False
-- A proof that it's currently safe to drop an object.
-data SafeDropProof = SafeDropProof NumCopies [VerifiedCopy] (Maybe ContentRemovalLock)
+data SafeDropProof = SafeDropProof NumCopies MinCopies [VerifiedCopy] (Maybe ContentRemovalLock)
deriving (Show)
--- Make sure that none of the VerifiedCopies have become invalidated
+-- Makes sure that none of the VerifiedCopies have become invalidated
-- before constructing proof.
-mkSafeDropProof :: NumCopies -> [VerifiedCopy] -> Maybe ContentRemovalLock -> IO (Either [VerifiedCopy] SafeDropProof)
-mkSafeDropProof need have removallock = do
+mkSafeDropProof :: NumCopies -> MinCopies -> [VerifiedCopy] -> Maybe ContentRemovalLock -> IO (Either [VerifiedCopy] SafeDropProof)
+mkSafeDropProof need mincopies have removallock = do
stillhave <- filterM checkVerifiedCopy have
- return $ if isSafeDrop need stillhave removallock
- then Right (SafeDropProof need stillhave removallock)
+ return $ if isSafeDrop need mincopies stillhave removallock
+ then Right (SafeDropProof need mincopies stillhave removallock)
else Left stillhave
diff --git a/doc/copies.mdwn b/doc/copies.mdwn
index 73482da7be..f79e94d009 100644
--- a/doc/copies.mdwn
+++ b/doc/copies.mdwn
@@ -10,23 +10,22 @@ numcopies N`, or can be overridden on a per-file-type basis by the
annex.numcopies setting in `.gitattributes` files. The --numcopies switch
allows temporarily using a different value.
-When dropping content, git-annex checks with remotes to make sure
-If enough repositories cannot be verified to have it, it will retain
-the file content to avoid data loss.
-
-When it can, git-annex locks enough copies on other repositories, to allow
-it to safely drop a copy without any possibility that numcopies will be
-violated. There are some exceptions, including special remotes not
-supporting locking, and [[trusted repositories|trust]] that are not
-accessible, where locking is not done.
-
-If such a repository is being relied on to contain a copy and drops it at
-the wrong time, the configured numcopies setting can be violated. To avoid
-losing the last copy in such an unusual situation, git-annex requires that
-at least 1 copy is locked in place when dropping content. If 1 does not
-seem like enough, you can override this default by running `git-annex
-requirednumcopies or setting annex.requirednumcopies in `.gitattributes`
-files.
+When dropping content, git-annex checks with remotes to make sure If enough
+other repositories cannot be verified to have copies, it will refuse to
+drop it, avoid data loss.
+
+In unusual situations, involving special remotes that do not support
+locking, and concurrent drops of the same content from multiple
+repositories, git-annex may violate the numcopies setting. It still
+guarantees at least 1 copy is preserved. This can be configured by
+running `git-annex mincopies N` or can be overridden on a per-file-type
+basis by the annex.mincopies setting in `.gitattributes` files.
+The --mincopies switch allows temporarily using a different value.
+
+Note that [trusted repositories|trust]] are assumed to
+continue to contain content, so checking them is skipped. So dropping
+content from trusted repositories does risk numcopies and mincopies
+later being violated.
To express more detailed requirements about which repositories contain which
content, see [[required_content]].
diff --git a/doc/git-annex-mincopies.mdwn b/doc/git-annex-mincopies.mdwn
new file mode 100644
index 0000000000..9f2ad92517
--- /dev/null
+++ b/doc/git-annex-mincopies.mdwn
@@ -0,0 +1,41 @@
+# NAME
+
+git-annex mincopies - configure minimum number of copies
+
+# SYNOPSIS
+
+git annex mincopies `N`
+
+# DESCRIPTION
+
+Tells git-annex how many copies it is required to preserve of files, over all
+repositories. The default is 1.
+
+Run without a number to get the current value.
+
+This configuration is stored in the git-annex branch, so it will be seen
+by all clones of the repository. It can be overridden on a per-file basis
+by the annex.mincopies setting in .gitattributes files, or can be
+overridden temporarily with the --mincopies option.
+
+When git-annex is asked to drop a file, it first verifies that the
+number of copies can be satisfied among all the other
+repositories that have a copy of the file.
+
+This supplements the [[git-annex-numcopies]](1) setting.
+In unusual situations, involving special remotes that do not support
+locking, and concurrent drops of the same content from multiple
+repositories, git-annex may violate the numcopies setting.
+In these unusual situations, git-annex ensures that
+the mincopies setting is not violated.
+
+# SEE ALSO
+
+[[git-annex]](1)
+[[git-annex-numcopies]](1)
+
+# AUTHOR
+
+Joey Hess <id@joeyh.name>
+
+Warning: Automatically converted into a man page by mdwn2man. Edit with care.
diff --git a/doc/git-annex-numcopies.mdwn b/doc/git-annex-numcopies.mdwn
index 15ddb06fba..8bf2895d95 100644
--- a/doc/git-annex-numcopies.mdwn
+++ b/doc/git-annex-numcopies.mdwn
@@ -22,17 +22,16 @@ When git-annex is asked to drop a file, it first verifies that the
number of copies can be satisfied among all the other
repositories that have a copy of the file.
-In situations involving trusted repositories or special remotes that
-cannot lock content in place, the numcopies setting may be violated
-when the same file is being dropped at the same time from multiple
-repositories. In these unusual situations, git-annex ensures that
-the requirednumcopies setting (default 1) is not violated. See
-[[git-annex-requirednumcopies]](1) for more about this setting.
+In unusual situations, involving special remotes that do not support
+locking, and concurrent drops of the same content from multiple
+repositories, git-annex may violate the numcopies setting. It still
+guarantees at least 1 copy is preserved. This can be configured by
+using [[git-annex-mincopies]](1)
# SEE ALSO
[[git-annex]](1)
-[[git-annex-requirednumcopies]](1)
+[[git-annex-mincopies]](1)
# AUTHOR
diff --git a/doc/git-annex-requirednumcopies.mdwn b/doc/git-annex-requirednumcopies.mdwn
deleted file mode 100644
index 7e25b7ec73..0000000000
--- a/doc/git-annex-requirednumcopies.mdwn
+++ /dev/null
@@ -1,43 +0,0 @@
-# NAME
-
-git-annex requirednumcopies - configure required number of copies
-
-# SYNOPSIS
-
-git annex requirednumcopies `N`
-
-# DESCRIPTION
-
-Tells git-annex how many copies it is required to preserve of files, over all
-repositories. The default is 1.
-
-Run without a number to get the current value.
-
-This configuration is stored in the git-annex branch, so it will be seen
-by all clones of the repository. It can be overridden on a per-file basis
-by the annex.requirednumcopies setting in .gitattributes files, or can be
-overridden temporarily with the --requirednumcopies option.
-
-When git-annex is asked to drop a file, it makes sure that
-that the required number of copies will still exist in other
-repositories, by locking the content in them, preventing it from
-being dropped.
-
-This supplements the [[git-annex-numcopies]](1) setting. git-annex
-checks that numcopies is met before dropping. But in situations
-involving trusted repositories or special remotes that
-cannot lock content in place, the numcopies setting may be violated
-when the same file is being dropped at the same time from multiple
-repositories. In these unusual situations, git-annex ensures that
-the requirednumcopies setting is not violated.
-
-# SEE ALSO
-
-[[git-annex]](1)
-[[git-annex-numcopies]](1)
-
-# AUTHOR
-
-Joey Hess <id@joeyh.name>
-
-Warning: Automatically converted into a man page by mdwn2man. Edit with care.
diff --git a/doc/git-annex.mdwn b/doc/git-annex.mdwn
index 5b653e6456..7571fdfd33 100644
--- a/doc/git-annex.mdwn
+++ b/doc/git-annex.mdwn
@@ -241,6 +241,12 @@ content from the key-value store.
See [[git-annex-numcopies]](1) for details.
+* `mincopies [N]`
+
+ Configure minimum number of copies.
+
+ See [[git-annex-mincopies]](1) for details.
+
* `trust [repository ...]`
Records that a repository is trusted to not unexpectedly lose
@@ -770,8 +776,13 @@ may not be explicitly listed on their individual man pages.
* `--numcopies=n`
- Overrides the numcopies setting, forcing git-annex to ensure the
- specified number of copies exist.
+ Overrides the numcopies setting.
+
+ Note that setting numcopies to 0 is very unsafe.
+
+* `--mincopies=n`
+
+ Overrides the mincopies setting.
Note that setting numcopies to 0 is very unsafe.
@@ -1842,22 +1853,23 @@ settings. Setting annex.largefiles in [[git-annex-config]](1) is an easier
way to configure it across all clones of the repository.
See [[git-annex-matching-expression]](1) for details on the syntax.
-The numcopies setting can also be configured on a per-file-type basis via
-the `annex.numcopies` attribute in `.gitattributes` files. This overrides
-other numcopies settings.
+The numcopies and mincopies settings can also be configured on a
+per-file-type basis via the `annex.numcopies` and `annex.mincopies`
+attributes in `.gitattributes` files. This overrides other settings.
For example, this makes two copies be needed for wav files and 3 copies
for flac files:
*.wav annex.numcopies=2
*.flac annex.numcopies=3
-Note that setting numcopies to 0 is very unsafe.
+Note that setting numcopies and mincopies to 0 is very unsafe.
These settings are honored by git-annex whenever it's operating on a
matching file. However, when using --all, --unused, or --key to specify
keys to operate on, git-annex is operating on keys and not files, so will
not honor the settings from .gitattributes. For this reason, the `git annex
-numcopies` command is useful to configure a global default for numcopies.
+numcopies` and `git annex mincopies` commands are useful to configure a
+global default.
Also note that when using views, only the toplevel .gitattributes file is
preserved in the view, so other settings in other files won't have any
diff --git a/doc/internals.mdwn b/doc/internals.mdwn
index cd48a39f89..6514003c33 100644
--- a/doc/internals.mdwn
+++ b/doc/internals.mdwn
@@ -92,6 +92,12 @@ Records the global numcopies setting.
The file format is simply a timestamp followed by a number.
+## `mincopies.log`
+
+Records the global mincopies setting.
+
+The file format is simply a timestamp followed by a number.
+
## `config.log`
Records global configuration settings, which can be overridden by values
diff --git a/doc/todo/lockContent_for_special_remotes.mdwn b/doc/todo/lockContent_for_special_remotes.mdwn
index 1c2c1545c7..722e476967 100644
--- a/doc/todo/lockContent_for_special_remotes.mdwn
+++ b/doc/todo/lockContent_for_special_remotes.mdwn
@@ -56,7 +56,6 @@ is not guaranteed. It only makes sure lockContent is keeping one copy
locked, and can verify the existence of the other copies less stringently.
So perhaps it would be good to make this explicit in the configuration,
-by adding a requirednumcopies. (Analagous to required content configs.)
+by adding a mincopies. (Analagous to required content configs.)
Defaulting to 1 as now, but if the user wants to they can set it higher,
-perhaps as high as their numcopies (or even just set it to 1000 and make
-it be treated the same value as numcopies when it's >= numcopies.)
+perhaps as high as their numcopies, or higher.
diff --git a/doc/trust.mdwn b/doc/trust.mdwn
index f93c4a9c91..75781b7acb 100644
--- a/doc/trust.mdwn
+++ b/doc/trust.mdwn
@@ -51,6 +51,13 @@ trust temporarily.
To configure a repository as fully and permanently trusted,
use the [[git-annex-trust]] command.
+Note that after dropping content from a trusted repo, other repos
+that are out of sync and trust it to still contain the content
+can drop copies, even though that will violate [[numcopies]]. So
+using trusted repositories can lead to data loss. It is best to take
+extreme care when dropping content from trusted repositories,
+the same as if you were using `--force`.
+
## dead
This is used to indicate that you have no trust that the repository
diff --git a/git-annex.cabal b/git-annex.cabal
index 70704e5bfa..b8b622b8bf 100644
--- a/git-annex.cabal
+++ b/git-annex.cabal
@@ -767,6 +767,7 @@ Executable git-annex
Command.Multicast
Command.NotifyChanges
Command.NumCopies
+ Command.MinCopies
Command.P2P
Command.P2PStdIO
Command.PostReceive