prevent numcopies or mincopies being configured to 0
Ignore annex.numcopies set to 0 in gitattributes or git config, or by git-annex numcopies or by --numcopies, since that configuration would make git-annex easily lose data. Same for mincopies. This is a continuation of the work to make data only be able to be lost when --force is used. It earlier led to the --trust option being disabled, and similar reasoning applies here. Most numcopies configs had docs that strongly discouraged setting it to 0 anyway. And I can't imagine a use case for setting to 0. Not that there might not be one, but it's just so far from the intended use case of git-annex, of managing and storing your data, that it does not seem like it makes sense to cater to such a hypothetical use case, where any git-annex drop can lose your data at any time. Using a smart constructor makes sure every place avoids 0. Note that this does mean that NumCopies is for the configured desired values, and not the actual existing number of copies, which of course can be 0. The name configuredNumCopies is used to make that clear. Sponsored-by: Brock Spratlen on Patreon
This commit is contained in:
parent
fdcb14d475
commit
d266a41f8d
16 changed files with 59 additions and 47 deletions
|
@ -70,10 +70,10 @@ handleDropsFrom locs rs reason fromhere key afile si preverified runner = do
|
|||
- will surely fail.
|
||||
-}
|
||||
checkcopies (have, numcopies, mincopies, _untrusted) Nothing =
|
||||
NumCopies have > numcopies && MinCopies have > mincopies
|
||||
have > fromNumCopies numcopies && have > fromMinCopies mincopies
|
||||
checkcopies (have, numcopies, mincopies, untrusted) (Just u)
|
||||
| S.member u untrusted = NumCopies have >= numcopies && MinCopies have >= mincopies
|
||||
| otherwise = NumCopies have > numcopies && MinCopies have > mincopies
|
||||
| S.member u untrusted = have >= fromNumCopies numcopies && have >= fromMinCopies mincopies
|
||||
| otherwise = have > fromNumCopies numcopies && have > fromMinCopies mincopies
|
||||
|
||||
decrcopies (have, numcopies, mincopies, untrusted) Nothing =
|
||||
(have - 1, numcopies, mincopies, untrusted)
|
||||
|
|
|
@ -43,10 +43,10 @@ import qualified Control.Monad.Catch as M
|
|||
import Data.Typeable
|
||||
|
||||
defaultNumCopies :: NumCopies
|
||||
defaultNumCopies = NumCopies 1
|
||||
defaultNumCopies = configuredNumCopies 1
|
||||
|
||||
defaultMinCopies :: MinCopies
|
||||
defaultMinCopies = MinCopies 1
|
||||
defaultMinCopies = configuredMinCopies 1
|
||||
|
||||
fromSourcesOr :: v -> [Annex (Maybe v)] -> Annex v
|
||||
fromSourcesOr v = fromMaybe v <$$> getM id
|
||||
|
@ -178,8 +178,8 @@ 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
|
||||
( configuredNumCopies <$> readish n
|
||||
, configuredMinCopies <$> readish m
|
||||
)
|
||||
_ -> error "internal"
|
||||
|
||||
|
@ -197,8 +197,8 @@ numCopiesCheck file key vs = do
|
|||
|
||||
numCopiesCheck' :: RawFilePath -> (Int -> Int -> v) -> [UUID] -> Annex v
|
||||
numCopiesCheck' file vs have = do
|
||||
NumCopies needed <- fst <$> getFileNumMinCopies file
|
||||
return $ length have `vs` needed
|
||||
needed <- fst <$> getFileNumMinCopies file
|
||||
return $ length have `vs` fromNumCopies needed
|
||||
|
||||
data UnVerifiedCopy = UnVerifiedRemote Remote | UnVerifiedHere
|
||||
deriving (Ord, Eq)
|
||||
|
|
|
@ -85,7 +85,7 @@ getPrefs = PrefsForm
|
|||
storePrefs :: PrefsForm -> Annex ()
|
||||
storePrefs p = do
|
||||
setConfig (annexConfig "diskreserve") (T.unpack $ diskReserve p)
|
||||
setGlobalNumCopies (NumCopies $ numCopies p)
|
||||
setGlobalNumCopies (configuredNumCopies $ numCopies p)
|
||||
unsetConfig (annexConfig "numcopies") -- deprecated
|
||||
setConfig (annexConfig "autoupgrade") (fromAutoUpgrade $ autoUpgrade p)
|
||||
unlessM ((==) <$> pure (autoStart p) <*> inAutoStartFile) $ do
|
||||
|
|
|
@ -1,3 +1,12 @@
|
|||
git-annex (10.20220323) UNRELEASED; urgency=medium
|
||||
|
||||
* Ignore annex.numcopies set to 0 in gitattributes or git config,
|
||||
or by git-annex numcopies or by --numcopies, since that
|
||||
configuration would make git-annex easily lose data.
|
||||
Same for mincopies.
|
||||
|
||||
-- Joey Hess <id@joeyh.name> Mon, 28 Mar 2022 14:46:10 -0400
|
||||
|
||||
git-annex (10.20220322) upstream; urgency=medium
|
||||
|
||||
* Directory special remotes with importtree=yes have changed to once more
|
||||
|
|
|
@ -100,8 +100,8 @@ 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 }
|
||||
setnumcopies n = Annex.changeState $ \s -> s { Annex.forcenumcopies = Just $ configuredNumCopies n }
|
||||
setmincopies n = Annex.changeState $ \s -> s { Annex.forcemincopies = Just $ configuredMinCopies 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 }
|
||||
|
|
|
@ -252,7 +252,7 @@ checkDropAuto automode mremote afile key a =
|
|||
uuid <- getUUID
|
||||
let remoteuuid = fromMaybe uuid $ Remote.uuid <$> mremote
|
||||
locs' <- trustExclude UnTrusted $ filter (/= remoteuuid) locs
|
||||
if NumCopies (length locs') >= numcopies
|
||||
if length locs' >= fromNumCopies numcopies
|
||||
then a numcopies mincopies
|
||||
else stop
|
||||
| otherwise = a numcopies mincopies
|
||||
|
|
|
@ -517,8 +517,8 @@ checkKeyNumCopies key afile numcopies = do
|
|||
locs <- loggedLocations key
|
||||
(untrustedlocations, otherlocations) <- trustPartition UnTrusted locs
|
||||
(deadlocations, safelocations) <- trustPartition DeadTrusted otherlocations
|
||||
let present = NumCopies (length safelocations)
|
||||
if present < numcopies
|
||||
let present = length safelocations
|
||||
if present < fromNumCopies numcopies
|
||||
then ifM (pure (not hasafile) <&&> checkDead key)
|
||||
( do
|
||||
showLongNote $ "This key is dead, skipping."
|
||||
|
@ -527,21 +527,21 @@ checkKeyNumCopies key afile numcopies = do
|
|||
untrusted <- Remote.prettyPrintUUIDs "untrusted" untrustedlocations
|
||||
dead <- Remote.prettyPrintUUIDs "dead" deadlocations
|
||||
warning $ missingNote desc present numcopies untrusted dead
|
||||
when (fromNumCopies present == 0 && not hasafile) $
|
||||
when (present == 0 && not hasafile) $
|
||||
showLongNote "(Avoid this check by running: git annex dead --key )"
|
||||
return False
|
||||
)
|
||||
else return True
|
||||
|
||||
missingNote :: String -> NumCopies -> NumCopies -> String -> String -> String
|
||||
missingNote file (NumCopies 0) _ [] dead =
|
||||
missingNote :: String -> Int -> NumCopies -> String -> String -> String
|
||||
missingNote file 0 _ [] dead =
|
||||
"** No known copies exist of " ++ file ++ honorDead dead
|
||||
missingNote file (NumCopies 0) _ untrusted dead =
|
||||
missingNote file 0 _ untrusted dead =
|
||||
"Only these untrusted locations may have copies of " ++ file ++
|
||||
"\n" ++ untrusted ++
|
||||
"Back it up to trusted locations with git-annex copy." ++ honorDead dead
|
||||
missingNote file present needed [] _ =
|
||||
"Only " ++ show (fromNumCopies present) ++ " of " ++ show (fromNumCopies needed) ++
|
||||
"Only " ++ show present ++ " of " ++ show (fromNumCopies needed) ++
|
||||
" trustworthy copies exist of " ++ file ++
|
||||
"\nBack it up with git-annex copy."
|
||||
missingNote file present needed untrusted dead =
|
||||
|
|
|
@ -32,7 +32,7 @@ startGet = startingCustomOutput (ActionItemOther Nothing) $ next $ do
|
|||
|
||||
startSet :: Int -> CommandStart
|
||||
startSet n = startingUsualMessages "mincopies" ai si $ do
|
||||
setGlobalMinCopies $ MinCopies n
|
||||
setGlobalMinCopies $ configuredMinCopies n
|
||||
next $ return True
|
||||
where
|
||||
ai = ActionItemOther (Just $ show n)
|
||||
|
|
|
@ -8,7 +8,6 @@
|
|||
module Command.NumCopies where
|
||||
|
||||
import Command
|
||||
import qualified Annex
|
||||
import Annex.NumCopies
|
||||
|
||||
cmd :: Command
|
||||
|
@ -28,11 +27,8 @@ start' setting _ startset [s] = case readish s of
|
|||
Nothing -> giveup $ "Bad number: " ++ s
|
||||
Just n
|
||||
| n > 0 -> startset n
|
||||
| n == 0 -> ifM (Annex.getState Annex.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!"
|
||||
| n == 0 -> giveup $ "Cannot set " ++ setting ++ " to 0."
|
||||
| otherwise -> giveup $ setting ++ " cannot be negative!"
|
||||
start' _ _ _ _ = giveup "Specify a single number."
|
||||
|
||||
startGet :: CommandStart
|
||||
|
@ -50,7 +46,7 @@ startGet = startingCustomOutput (ActionItemOther Nothing) $ next $ do
|
|||
|
||||
startSet :: Int -> CommandStart
|
||||
startSet n = startingUsualMessages "numcopies" ai si $ do
|
||||
setGlobalNumCopies $ NumCopies n
|
||||
setGlobalNumCopies $ configuredNumCopies n
|
||||
next $ return True
|
||||
where
|
||||
ai = ActionItemOther (Just $ show n)
|
||||
|
|
|
@ -315,7 +315,7 @@ parseCfg defcfg = go [] defcfg . lines
|
|||
in Right $ cfg { cfgGlobalConfigs = m }
|
||||
| setting == "numcopies" = case readish val of
|
||||
Nothing -> Left "parse error (expected an integer)"
|
||||
Just n -> Right $ cfg { cfgNumCopies = Just (NumCopies n) }
|
||||
Just n -> Right $ cfg { cfgNumCopies = Just (configuredNumCopies n) }
|
||||
| otherwise = badval "setting" setting
|
||||
where
|
||||
u = toUUID f
|
||||
|
|
4
Limit.hs
4
Limit.hs
|
@ -397,7 +397,7 @@ limitLackingCopies approx want = case readish want of
|
|||
Nothing -> Left "bad value for number of lacking copies"
|
||||
where
|
||||
go mi needed notpresent key = do
|
||||
NumCopies numcopies <- if approx
|
||||
numcopies <- if approx
|
||||
then approxNumCopies
|
||||
else case mi of
|
||||
MatchingFile fi -> getGlobalFileNumCopies $
|
||||
|
@ -406,7 +406,7 @@ limitLackingCopies approx want = case readish want of
|
|||
MatchingUserInfo {} -> approxNumCopies
|
||||
us <- filter (`S.notMember` notpresent)
|
||||
<$> (trustExclude UnTrusted =<< Remote.keyLocations key)
|
||||
return $ numcopies - length us >= needed
|
||||
return $ fromNumCopies numcopies - length us >= needed
|
||||
approxNumCopies = fromMaybe defaultNumCopies <$> getGlobalNumCopies
|
||||
|
||||
{- Match keys that are unused.
|
||||
|
|
|
@ -24,12 +24,12 @@ import Logs
|
|||
import Logs.SingleValue
|
||||
|
||||
instance SingleValueSerializable NumCopies where
|
||||
serialize (NumCopies n) = encodeBS (show n)
|
||||
deserialize = NumCopies <$$> readish . decodeBS
|
||||
serialize = encodeBS . show . fromNumCopies
|
||||
deserialize = configuredNumCopies <$$> readish . decodeBS
|
||||
|
||||
instance SingleValueSerializable MinCopies where
|
||||
serialize (MinCopies n) = encodeBS (show n)
|
||||
deserialize = MinCopies <$$> readish . decodeBS
|
||||
serialize = encodeBS . show . fromMinCopies
|
||||
deserialize = configuredMinCopies <$$> readish . decodeBS
|
||||
|
||||
setGlobalNumCopies :: NumCopies -> Annex ()
|
||||
setGlobalNumCopies new = do
|
||||
|
|
|
@ -148,7 +148,8 @@ extractGitConfig :: ConfigSource -> Git.Repo -> GitConfig
|
|||
extractGitConfig configsource r = GitConfig
|
||||
{ annexVersion = RepoVersion <$> getmayberead (annexConfig "version")
|
||||
, annexUUID = hereuuid
|
||||
, annexNumCopies = NumCopies <$> getmayberead (annexConfig "numcopies")
|
||||
, annexNumCopies = configuredNumCopies
|
||||
<$> getmayberead (annexConfig "numcopies")
|
||||
, annexDiskReserve = fromMaybe onemegabyte $
|
||||
readSize dataUnits =<< getmaybe (annexConfig "diskreserve")
|
||||
, annexDirect = getbool (annexConfig "direct") False
|
||||
|
|
|
@ -1,14 +1,16 @@
|
|||
{- git-annex numcopies types
|
||||
-
|
||||
- Copyright 2014-2021 Joey Hess <id@joeyh.name>
|
||||
- Copyright 2014-2022 Joey Hess <id@joeyh.name>
|
||||
-
|
||||
- Licensed under the GNU AGPL version 3 or higher.
|
||||
-}
|
||||
|
||||
module Types.NumCopies (
|
||||
NumCopies(..),
|
||||
NumCopies,
|
||||
configuredNumCopies,
|
||||
fromNumCopies,
|
||||
MinCopies(..),
|
||||
MinCopies,
|
||||
configuredMinCopies,
|
||||
fromMinCopies,
|
||||
VerifiedCopy(..),
|
||||
checkVerifiedCopy,
|
||||
|
@ -38,12 +40,24 @@ import Control.Monad
|
|||
newtype NumCopies = NumCopies Int
|
||||
deriving (Ord, Eq, Show)
|
||||
|
||||
-- Smart constructor; prevent configuring numcopies to 0 which would
|
||||
-- cause data loss.
|
||||
configuredNumCopies :: Int -> NumCopies
|
||||
configuredNumCopies n
|
||||
| n > 0 = NumCopies n
|
||||
| otherwise = NumCopies 1
|
||||
|
||||
fromNumCopies :: NumCopies -> Int
|
||||
fromNumCopies (NumCopies n) = n
|
||||
|
||||
newtype MinCopies = MinCopies Int
|
||||
deriving (Ord, Eq, Show)
|
||||
|
||||
configuredMinCopies :: Int -> MinCopies
|
||||
configuredMinCopies n
|
||||
| n > 0 = MinCopies n
|
||||
| otherwise = MinCopies 1
|
||||
|
||||
fromMinCopies :: MinCopies -> Int
|
||||
fromMinCopies (MinCopies n) = n
|
||||
|
||||
|
|
|
@ -59,14 +59,10 @@ Most of these options are accepted by all git-annex commands.
|
|||
|
||||
Overrides the numcopies setting.
|
||||
|
||||
Note that setting numcopies to 0 is very unsafe.
|
||||
|
||||
* `--mincopies=n`
|
||||
|
||||
Overrides the mincopies setting.
|
||||
|
||||
Note that setting mincopies to 0 is very unsafe.
|
||||
|
||||
* `--time-limit=time`
|
||||
|
||||
Limits how long a git-annex command runs. The time can be something
|
||||
|
|
|
@ -932,8 +932,6 @@ repository, using [[git-annex-config]]. See its man page for a list.)
|
|||
never been configured, and when there's no annex.numcopies setting in the
|
||||
.gitattributes file.
|
||||
|
||||
Note that setting numcopies to 0 is very unsafe.
|
||||
|
||||
* `annex.genmetadata`
|
||||
|
||||
Set this to `true` to make git-annex automatically generate some metadata
|
||||
|
@ -1881,8 +1879,6 @@ for flac files:
|
|||
*.wav annex.numcopies=2
|
||||
*.flac annex.numcopies=3
|
||||
|
||||
Note that setting numcopies or 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
|
||||
|
|
Loading…
Add table
Reference in a new issue