diff options
-rw-r--r-- | Command/Upgrade.hs | 4 | ||||
-rw-r--r-- | Upgrade/V1.hs | 5 | ||||
-rw-r--r-- | Upgrade/V2.hs | 54 | ||||
-rw-r--r-- | doc/upgrades.mdwn | 71 |
4 files changed, 89 insertions, 45 deletions
diff --git a/Command/Upgrade.hs b/Command/Upgrade.hs index b3c046803..b79b13cd3 100644 --- a/Command/Upgrade.hs +++ b/Command/Upgrade.hs @@ -21,7 +21,7 @@ seek = [withNothing start] start :: CommandStartNothing start = do - showStart "upgrade" "" + showStart "upgrade" "." r <- upgrade - checkVersion + setVersion next $ next $ return r diff --git a/Upgrade/V1.hs b/Upgrade/V1.hs index 1f327f77b..61a801859 100644 --- a/Upgrade/V1.hs +++ b/Upgrade/V1.hs @@ -30,6 +30,7 @@ import Backend import Messages import Version import Utility +import qualified Upgrade.V2 -- v2 adds hashing of filenames of content and location log files. -- Key information is encoded in filenames differently, so @@ -70,8 +71,8 @@ upgrade = do AnnexQueue.flush True setVersion - - return True + + Upgrade.V2.upgrade moveContent :: Annex () moveContent = do diff --git a/Upgrade/V2.hs b/Upgrade/V2.hs index c249e340b..36ba1a0f2 100644 --- a/Upgrade/V2.hs +++ b/Upgrade/V2.hs @@ -1,4 +1,4 @@ -{- git-annex v2 -> v2 upgrade support +{- git-annex v2 -> v3 upgrade support - - Copyright 2011 Joey Hess <joey@kitenet.net> - @@ -9,14 +9,22 @@ module Upgrade.V2 where import System.Directory import System.FilePath +import Control.Monad.State (liftIO) +import List +import Data.Maybe import Types.Key import Types +import qualified Annex import qualified GitRepo as Git +import qualified Branch import Messages import Utility import Locations +olddir :: FilePath +olddir = ".git-annex" + {- .git-annex/ moved to a git-annex branch. - - Strategy: @@ -35,7 +43,36 @@ import Locations upgrade :: Annex Bool upgrade = do showNote "v2 to v3" - error "TODO" + g <- Annex.gitRepo + Branch.create + mapM_ (\(k, f) -> inject f $ logFile k) =<< locationLogs g + mapM_ (\f -> inject f f) =<< logFiles olddir + liftIO $ do + Git.run g "rm" [Param "-r", Param "-f", Param "-q", File olddir] + gitAttributesUnWrite g + return True + +locationLogs :: Git.Repo -> Annex [(Key, FilePath)] +locationLogs repo = liftIO $ do + levela <- dirContents dir + levelb <- mapM tryDirContents levela + files <- mapM tryDirContents (concat levelb) + return $ catMaybes $ map islogfile (concat files) + where + tryDirContents d = catch (dirContents d) (return . const []) + dir = gitStateDir repo + islogfile f = maybe Nothing (\k -> Just $ (k, f)) $ + logFileKey $ takeFileName f + +inject :: FilePath -> FilePath -> Annex () +inject source dest = do + new <- liftIO (readFile $ olddir </> source) + prev <- Branch.get dest + Branch.change dest $ unlines $ nub $ lines prev ++ lines new + +logFiles :: FilePath -> Annex [FilePath] +logFiles dir = return . filter (".log" `isSuffixOf`) + =<< liftIO (getDirectoryContents dir) {- Old .gitattributes contents, not needed anymore. -} attrLines :: [String] @@ -49,15 +86,6 @@ gitAttributesUnWrite repo = do let attributes = Git.attributes repo whenM (doesFileExist attributes) $ do c <- readFileStrict attributes - safeWriteFile attributes $ unlines $ + liftIO $ safeWriteFile attributes $ unlines $ filter (\l -> not $ l `elem` attrLines) $ lines c - -oldlogFile :: Git.Repo -> Key -> String -oldlogFile = logFile' hashDirLower - -oldlogFileOld :: Git.Repo -> Key -> String -oldlogFileOld = logFile' hashDirMixed - -logFile' :: (Key -> FilePath) -> Git.Repo -> Key -> String -logFile' hasher repo key = - gitStateDir repo ++ hasher key ++ keyFile key ++ ".log" + Git.run repo "add" [File attributes] diff --git a/doc/upgrades.mdwn b/doc/upgrades.mdwn index 516e5b3bb..bf12f7e43 100644 --- a/doc/upgrades.mdwn +++ b/doc/upgrades.mdwn @@ -7,49 +7,38 @@ There's a committment that git-annex will always support upgrades from all past versions. After all, you may have offline drives from an earlier git-annex, and might want to use them with a newer git-annex. -## Upgrade process - git-annex will notice if it is run in a repository that needs an upgrade, and refuse to do anything. To upgrade, use the "git annex upgrade" command. The upgrade can tend to take a while, if you have a lot of files. -Each clone of a repository should be individually upgraded. -Until a repository's remotes have been upgraded, git-annex -will refuse to communicate with them. - -Generally, start by upgrading one repository, and then you can commit -the changes git-annex staged during upgrade, and push them out to other -repositories. And then upgrade those other repositories. Doing it this -way avoids git-annex doing some duplicate work during the upgrade. - The upgrade process is guaranteed to be conflict-free. Unless you already have git conflicts in your repository or between repositories. Upgrading a repository with conflicts is not recommended; resolve the conflicts first before upgrading git-annex. -Example upgrade process: +## Upgrade events, so far - cd localrepo - git pull - git annex upgrade - (Upgrading object directory layout v1 to v2...) - git commit -m "upgrade v1 to v2" - git push +### v2 -> v3 (git-annex version 3.x) - ssh remote - cd remoterepo - git pull - git annex upgrade - ... +Involved moving the .git-annex/ directory into a separate git-annex branch. -## Upgrade events, so far +### tips for this upgrade -### v2 -> v3 (git-annex version 0.20110610 to version 0.20110622) +This upgrade is easier than the previous upgrades. You don't need to +upgrade every repository at once; it's sufficient to upgrade each +repository only when you next use it. -Involved moving the .git-annex/ directory into a separate git-annex branch. +This upgrade can be sped up by, before you start, making +.git/index.git-annex into a symlink to a file on a ramdisk. +For example: `ln -s /run/shm/index.git-annex.$(git config annex.uuid) .git/index.git-annex` +but, if you do that, be sure to remove the symlink after the upgrade! -### v1 -> v2 (git-annex version 0.23 to version 0.20110316) +After the upgrade is complete, commit the changes it staged. + + git commit -m "upgrade v2 to v3" + +### v1 -> v2 (git-annex version 0.20110316) Involved adding hashing to .git/annex/ and changing the names of all keys. Symlinks changed. @@ -64,7 +53,33 @@ and that information will be used by git-annex for disk free space checking. To ensure that information is available for all your annexed files, see [[upgrades/SHA_size]]. -### v0 -> v1 (git-annex version 0.03 to version 0.04) +### tips for this upgrade + +Each clone of a repository should be individually upgraded. +Until a repository's remotes have been upgraded, git-annex +will refuse to communicate with them. + +Start by upgrading one repository, and then you can commit +the changes git-annex staged during upgrade, and push them out to other +repositories. And then upgrade those other repositories. Doing it this +way avoids git-annex doing some duplicate work during the upgrade. + +Example upgrade process: + + cd localrepo + git pull + git annex upgrade + (Upgrading object directory layout v1 to v2...) + git commit -m "upgrade v1 to v2" + git push + + ssh remote + cd remoterepo + git pull + git annex upgrade + ... + +### v0 -> v1 (git-annex version 0.04) Involved a reorganisation of the layout of .git/annex/. Symlinks changed. |