fixes for upgrading bare repos

This commit is contained in:
Joey Hess 2011-06-24 01:13:33 -04:00
parent 69d3c1cec9
commit 59b2e4ec1d

View file

@ -10,6 +10,7 @@ module Upgrade.V2 where
import System.Directory import System.Directory
import System.FilePath import System.FilePath
import Control.Monad.State (liftIO) import Control.Monad.State (liftIO)
import Control.Monad.State (unless)
import List import List
import Data.Maybe import Data.Maybe
@ -22,8 +23,10 @@ import Messages
import Utility import Utility
import Locations import Locations
olddir :: FilePath olddir :: Git.Repo -> FilePath
olddir = ".git-annex" olddir g
| Git.repoIsLocalBare g = ""
| otherwise = ".git-annex"
{- .git-annex/ moved to a git-annex branch. {- .git-annex/ moved to a git-annex branch.
- -
@ -46,14 +49,15 @@ upgrade = do
g <- Annex.gitRepo g <- Annex.gitRepo
Branch.create Branch.create
mapM_ (\(k, f) -> inject f $ logFile k) =<< locationLogs g mapM_ (\(k, f) -> inject f $ logFile k) =<< locationLogs g
mapM_ (\f -> inject f f) =<< logFiles olddir mapM_ (\f -> inject f f) =<< logFiles (olddir g)
liftIO $ do liftIO $ do
Git.run g "rm" [Param "-r", Param "-f", Param "-q", File olddir] Git.run g "rm" [Param "-r", Param "-f", Param "-q", File (olddir g)]
gitAttributesUnWrite g unless (Git.repoIsLocalBare g) $ gitAttributesUnWrite g
showLongNote $ showLongNote $
"git-annex branch created\n" ++ "git-annex branch created\n" ++
"Now you should push the new branch: git push origin git-annex\n" "Now you should push the new branch: git push origin git-annex\n"
showProgress
return True return True
@ -71,7 +75,8 @@ locationLogs repo = liftIO $ do
inject :: FilePath -> FilePath -> Annex () inject :: FilePath -> FilePath -> Annex ()
inject source dest = do inject source dest = do
new <- liftIO (readFile $ olddir </> source) g <- Annex.gitRepo
new <- liftIO (readFile $ olddir g </> source)
prev <- Branch.get dest prev <- Branch.get dest
Branch.change dest $ unlines $ nub $ lines prev ++ lines new Branch.change dest $ unlines $ nub $ lines prev ++ lines new