rekey: New plumbing level command, can be used to change the keys used for files en masse.

This commit is contained in:
Joey Hess 2012-02-16 16:36:35 -04:00
parent aeaaa0ff87
commit db6b4cdfcf
6 changed files with 87 additions and 17 deletions

View file

@ -58,22 +58,27 @@ perform file oldkey newbackend = do
cleantmp tmpfile
case k of
Nothing -> stop
Just (newkey, _) -> stopUnless (link src newkey) $ do
-- Update symlink to use the new key.
liftIO $ removeFile file
-- If the old key had some
-- associated urls, record them for
-- the new key as well.
urls <- getUrls oldkey
unless (null urls) $
mapM_ (setUrlPresent newkey) urls
next $ Command.Add.cleanup file newkey True
Just (newkey, _) -> stopUnless (linkKey src newkey) $
next $ cleanup file oldkey newkey
where
cleantmp t = liftIO $ whenM (doesFileExist t) $ removeFile t
link src newkey = getViaTmpUnchecked newkey $ \t -> do
-- Make a hard link to the old backend's
-- cached key, to avoid wasting disk space.
liftIO $ unlessM (doesFileExist t) $ createLink src t
return True
linkKey :: FilePath -> Key -> Annex Bool
linkKey src newkey = getViaTmpUnchecked newkey $ \t -> do
-- Make a hard link to the old backend's
-- cached key, to avoid wasting disk space.
liftIO $ unlessM (doesFileExist t) $ createLink src t
return True
cleanup :: FilePath -> Key -> Key -> CommandCleanup
cleanup file oldkey newkey = do
-- Update symlink to use the new key.
liftIO $ removeFile file
-- If the old key had some associated urls, record them for
-- the new key as well.
urls <- getUrls oldkey
unless (null urls) $
mapM_ (setUrlPresent newkey) urls
Command.Add.cleanup file newkey True

46
Command/ReKey.hs Normal file
View file

@ -0,0 +1,46 @@
{- git-annex command
-
- Copyright 2012 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Command.ReKey where
import Common.Annex
import Command
import qualified Annex
import Types.Key
import Annex.Content
import qualified Command.Migrate
def :: [Command]
def = [command "rekey"
(paramOptional $ paramRepeating $ paramPair paramPath paramKey)
seek "change keys used for files"]
seek :: [CommandSeek]
seek = [withPairs start]
start :: (FilePath, String) -> CommandStart
start (file, keyname) = ifAnnexed file go stop
where
newkey = fromMaybe (error "bad key") $ readKey keyname
go (oldkey, _)
| oldkey == newkey = stop
| otherwise = do
showStart "rekey" file
next $ perform file oldkey newkey
perform :: FilePath -> Key -> Key -> CommandPerform
perform file oldkey newkey = do
present <- inAnnex oldkey
_ <- if present
then do
src <- inRepo $ gitAnnexLocation oldkey
Command.Migrate.linkKey src newkey
else do
unlessM (Annex.getState Annex.force) $
error $ file ++ " is not available (use --force to override)"
return True
next $ Command.Migrate.cleanup file oldkey newkey

View file

@ -28,6 +28,7 @@ import qualified Command.Copy
import qualified Command.Get
import qualified Command.FromKey
import qualified Command.DropKey
import qualified Command.ReKey
import qualified Command.Reinject
import qualified Command.Fix
import qualified Command.Init
@ -80,6 +81,7 @@ cmds = concat
, Command.Dead.def
, Command.FromKey.def
, Command.DropKey.def
, Command.ReKey.def
, Command.Fix.def
, Command.Fsck.def
, Command.Unused.def

View file

@ -45,6 +45,13 @@ withWords a params = return [a params]
withStrings :: (String -> CommandStart) -> CommandSeek
withStrings a params = return $ map a params
withPairs :: ((String, String) -> CommandStart) -> CommandSeek
withPairs a params = return $ map a $ pairs [] params
where
pairs c [] = reverse c
pairs c (x:y:xs) = pairs ((x,y):c) xs
pairs _ _ = error "expected pairs"
withFilesToBeCommitted :: (String -> CommandStart) -> CommandSeek
withFilesToBeCommitted a params = prepFiltered a $
seekHelper LsFiles.stagedNotDeleted params

2
debian/changelog vendored
View file

@ -30,6 +30,8 @@ git-annex (3.20120124) UNRELEASED; urgency=low
location of the file.
* addurl: Normalize badly encoded urls.
* addurl: Add --pathdepth option.
* rekey: New plumbing level command, can be used to change the keys used
for files en masse.
-- Joey Hess <joeyh@debian.org> Tue, 24 Jan 2012 16:21:55 -0400

View file

@ -399,6 +399,14 @@ subdirectories).
git annex dropkey SHA1-s10-7da006579dd64330eb2456001fd01948430572f2
* rekey [file key ...]
This plumbing-level command is similar to migrate, but you specify
both the file, and the new key to use for it.
With --force, even files whose content is not currently available will
be rekeyed. Use with caution.
# OPTIONS
* --force