git-annex/Upgrade/V2.hs

147 lines
4.1 KiB
Haskell
Raw Normal View History

{- git-annex v2 -> v3 upgrade support
-
- Copyright 2011 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
2011-06-22 21:51:48 +00:00
module Upgrade.V2 where
import Annex.Common
import qualified Git
2011-12-14 19:56:11 +00:00
import qualified Git.Command
2011-12-12 22:23:24 +00:00
import qualified Git.Ref
2011-10-04 04:40:47 +00:00
import qualified Annex.Branch
import qualified Annex
2011-10-04 04:40:47 +00:00
import Annex.Content
2013-05-12 23:19:28 +00:00
import Utility.Tmp
import Logs
2015-04-03 19:35:32 +00:00
import Messages.Progress
2011-06-22 21:51:48 +00:00
2011-06-24 05:13:33 +00:00
olddir :: Git.Repo -> FilePath
olddir g
| Git.repoIsLocalBare g = ""
| otherwise = ".git-annex"
2011-06-23 03:37:46 +00:00
{- .git-annex/ moved to a git-annex branch.
-
- Strategy:
-
- * Create the git-annex branch.
- * Find each location log file in .git-annex/, and inject its content
- into the git-annex branch, unioning with any content already in
- there. (in passing, this deals with the semi transition that left
- some location logs hashed two different ways; both are found and
- merged).
- * Also inject remote.log, trust.log, and uuid.log.
- * git rm -rf .git-annex
- * Remove stuff that used to be needed in .gitattributes.
- * Commit changes.
-}
2011-06-22 21:51:48 +00:00
upgrade :: Annex Bool
upgrade = do
showAction "v2 to v3"
bare <- fromRepo Git.repoIsLocalBare
old <- fromRepo olddir
2011-06-24 05:15:12 +00:00
2011-10-04 04:40:47 +00:00
Annex.Branch.create
showProgressDots
e <- liftIO $ doesDirectoryExist old
when e $ do
config <- Annex.getGitConfig
mapM_ (\(k, f) -> inject f $ fromRawFilePath $ locationLogFile config k) =<< locationLogs
mapM_ (\f -> inject f f) =<< logFiles old
2011-06-23 18:49:21 +00:00
saveState False
showProgressDots
when e $ do
inRepo $ Git.Command.run [Param "rm", Param "-r", Param "-f", Param "-q", File old]
2011-12-09 05:57:13 +00:00
unless bare $ inRepo gitAttributesUnWrite
showProgressDots
unless bare push
2011-06-23 18:49:21 +00:00
return True
locationLogs :: Annex [(Key, FilePath)]
locationLogs = do
config <- Annex.getGitConfig
dir <- fromRepo gitStateDir
liftIO $ do
levela <- dirContents dir
levelb <- mapM tryDirContents levela
files <- mapM tryDirContents (concat levelb)
return $ mapMaybe (islogfile config) (concat files)
2012-11-11 04:51:07 +00:00
where
tryDirContents d = catchDefaultIO [] $ dirContents d
islogfile config f = maybe Nothing (\k -> Just (k, f)) $
locationLogFileKey config (toRawFilePath f)
inject :: FilePath -> FilePath -> Annex ()
inject source dest = do
old <- fromRepo olddir
new <- liftIO (readFile $ old </> source)
Annex.Branch.change (toRawFilePath dest) $ \prev ->
encodeBL $ unlines $ nub $ lines (decodeBL prev) ++ lines new
logFiles :: FilePath -> Annex [FilePath]
logFiles dir = return . filter (".log" `isSuffixOf`)
2012-06-14 04:01:48 +00:00
<=< liftIO $ getDirectoryContents dir
push :: Annex ()
push = do
2011-12-12 22:23:24 +00:00
origin_master <- inRepo $ Git.Ref.exists $ Git.Ref "origin/master"
2011-10-04 04:40:47 +00:00
origin_gitannex <- Annex.Branch.hasOrigin
case (origin_master, origin_gitannex) of
(_, True) -> do
-- Merge in the origin's git-annex branch,
-- so that pushing the git-annex branch
-- will immediately work. Not pushed here,
-- because it's less obnoxious to let the user
-- push.
2011-10-04 04:40:47 +00:00
Annex.Branch.update
(True, False) -> do
-- push git-annex to origin, so that
-- "git push" will from then on
-- automatically push it
2011-10-04 04:40:47 +00:00
Annex.Branch.update -- just in case
showAction "pushing new git-annex branch to origin"
showOutput
inRepo $ Git.Command.run
[ Param "push"
, Param "origin"
, Param $ Git.fromRef Annex.Branch.name
]
_ -> do
-- no origin exists, so just let the user
-- know about the new branch
2011-10-04 04:40:47 +00:00
Annex.Branch.update
showLongNote $
"git-annex branch created\n" ++
"Be sure to push this branch when pushing to remotes.\n"
{- Old .gitattributes contents, not needed anymore. -}
attrLines :: [String]
attrLines =
[ stateDir </> "*.log merge=union"
, stateDir </> "*/*/*.log merge=union"
]
gitAttributesUnWrite :: Git.Repo -> IO ()
gitAttributesUnWrite repo = do
let attributes = Git.attributes repo
whenM (doesFileExist attributes) $ do
c <- readFileStrict attributes
2011-06-30 04:42:09 +00:00
liftIO $ viaTmp writeFile attributes $ unlines $
filter (`notElem` attrLines) $ lines c
Git.Command.run [Param "add", File attributes] repo
2011-06-23 12:48:13 +00:00
stateDir :: FilePath
stateDir = addTrailingPathSeparator ".git-annex"
2011-06-23 12:48:13 +00:00
gitStateDir :: Git.Repo -> FilePath
gitStateDir repo = addTrailingPathSeparator $
fromRawFilePath (Git.repoPath repo) </> stateDir