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.
This commit is contained in:
parent
428d228ee5
commit
cc89699457
29 changed files with 412 additions and 219 deletions
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
|
39
Command/MinCopies.hs
Normal file
39
Command/MinCopies.hs
Normal file
|
@ -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]
|
|
@ -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
|
||||
|
|
|
@ -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
|
||||
|
||||
|
|
|
@ -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
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue