improve upgrade
This commit is contained in:
parent
744638197f
commit
5eb76d2b03
5 changed files with 30 additions and 14 deletions
|
@ -8,7 +8,7 @@
|
||||||
module Command.Init where
|
module Command.Init where
|
||||||
|
|
||||||
import Control.Monad.State (liftIO)
|
import Control.Monad.State (liftIO)
|
||||||
import Control.Monad (when)
|
import Control.Monad (when, unless)
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
|
|
||||||
|
@ -74,12 +74,14 @@ gitAttributesWrite repo = do
|
||||||
exists <- doesFileExist attributes
|
exists <- doesFileExist attributes
|
||||||
if not exists
|
if not exists
|
||||||
then do
|
then do
|
||||||
safeWriteFile attributes $ attrLine ++ "\n"
|
safeWriteFile attributes $ unlines attrLines
|
||||||
commit
|
commit
|
||||||
else do
|
else do
|
||||||
content <- readFile attributes
|
content <- readFile attributes
|
||||||
when (all (/= attrLine) (lines content)) $ do
|
let present = lines content
|
||||||
appendFile attributes $ attrLine ++ "\n"
|
let missing = filter (\l -> not $ l `elem` present) attrLines
|
||||||
|
unless (null missing) $ do
|
||||||
|
appendFile attributes $ unlines missing
|
||||||
commit
|
commit
|
||||||
where
|
where
|
||||||
attributes = Git.attributes repo
|
attributes = Git.attributes repo
|
||||||
|
@ -91,8 +93,11 @@ gitAttributesWrite repo = do
|
||||||
, Param attributes
|
, Param attributes
|
||||||
]
|
]
|
||||||
|
|
||||||
attrLine :: String
|
attrLines :: [String]
|
||||||
attrLine = stateDir </> "*.log merge=union"
|
attrLines =
|
||||||
|
[ stateDir </> "*.log merge=union"
|
||||||
|
, stateDir </> "*/*/*.log merge=union"
|
||||||
|
]
|
||||||
|
|
||||||
{- set up a git pre-commit hook, if one is not already present -}
|
{- set up a git pre-commit hook, if one is not already present -}
|
||||||
gitPreCommitHookWrite :: Git.Repo -> Annex ()
|
gitPreCommitHookWrite :: Git.Repo -> Annex ()
|
||||||
|
|
|
@ -60,4 +60,4 @@ gitAttributesUnWrite repo = do
|
||||||
when attrexists $ do
|
when attrexists $ do
|
||||||
c <- readFileStrict attributes
|
c <- readFileStrict attributes
|
||||||
safeWriteFile attributes $ unlines $
|
safeWriteFile attributes $ unlines $
|
||||||
filter (/= Command.Init.attrLine) $ lines c
|
filter (\l -> not $ l `elem` Command.Init.attrLines) $ lines c
|
||||||
|
|
|
@ -24,6 +24,8 @@ module LocationLog (
|
||||||
LogStatus(..),
|
LogStatus(..),
|
||||||
logChange,
|
logChange,
|
||||||
logFile,
|
logFile,
|
||||||
|
readLog,
|
||||||
|
writeLog,
|
||||||
keyLocations
|
keyLocations
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
|
|
@ -21,13 +21,15 @@ import Key
|
||||||
import Content
|
import Content
|
||||||
import Types
|
import Types
|
||||||
import Locations
|
import Locations
|
||||||
|
import LocationLog
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import qualified GitRepo as Git
|
import qualified GitRepo as Git
|
||||||
import Backend
|
import Backend
|
||||||
import Messages
|
import Messages
|
||||||
import Version
|
import Version
|
||||||
import Utility
|
import Utility
|
||||||
|
import qualified Command.Init
|
||||||
|
|
||||||
-- v2 adds hashing of filenames of content and location log files.
|
-- v2 adds hashing of filenames of content and location log files.
|
||||||
-- Key information is encoded in filenames differently, so
|
-- Key information is encoded in filenames differently, so
|
||||||
-- both content and location log files move around, and symlinks
|
-- both content and location log files move around, and symlinks
|
||||||
|
@ -61,6 +63,12 @@ upgrade = do
|
||||||
|
|
||||||
Annex.queueRun
|
Annex.queueRun
|
||||||
setVersion
|
setVersion
|
||||||
|
|
||||||
|
-- add new line to auto-merge hashed location logs
|
||||||
|
-- this commits, so has to come after the upgrade
|
||||||
|
g <- Annex.gitRepo
|
||||||
|
liftIO $ Command.Init.gitAttributesWrite g
|
||||||
|
|
||||||
return True
|
return True
|
||||||
|
|
||||||
moveContent :: Annex ()
|
moveContent :: Annex ()
|
||||||
|
@ -110,8 +118,12 @@ moveLocationLogs = do
|
||||||
let f = dir </> l
|
let f = dir </> l
|
||||||
liftIO $ createDirectoryIfMissing True (parentDir dest)
|
liftIO $ createDirectoryIfMissing True (parentDir dest)
|
||||||
-- could just git mv, but this way deals with
|
-- could just git mv, but this way deals with
|
||||||
-- log files that are not checked into git
|
-- log files that are not checked into git,
|
||||||
liftIO $ copyFile f dest
|
-- as well as merging with already upgraded
|
||||||
|
-- logs that have been pulled from elsewhere
|
||||||
|
old <- liftIO $ readLog f
|
||||||
|
new <- liftIO $ readLog dest
|
||||||
|
liftIO $ writeLog dest (old++new)
|
||||||
Annex.queue "add" [Param "--"] dest
|
Annex.queue "add" [Param "--"] dest
|
||||||
Annex.queue "add" [Param "--"] f
|
Annex.queue "add" [Param "--"] f
|
||||||
Annex.queue "rm" [Param "--quiet", Param "-f", Param "--"] f
|
Annex.queue "rm" [Param "--quiet", Param "-f", Param "--"] f
|
||||||
|
|
5
debian/changelog
vendored
5
debian/changelog
vendored
|
@ -1,12 +1,9 @@
|
||||||
git-annex (0.20110316) UNRELEASED; urgency=low
|
git-annex (0.20110316) UNRELEASED; urgency=low
|
||||||
|
|
||||||
* Reorganized .git/annex/objects and .git-annex/; annex.version=2
|
* New repository format, annex.version=2.
|
||||||
* The first time git-annex is run in an old format repository, it
|
* The first time git-annex is run in an old format repository, it
|
||||||
will automatically upgrade it to the new format, staging all
|
will automatically upgrade it to the new format, staging all
|
||||||
necessary changes to git.
|
necessary changes to git.
|
||||||
* Note that remotes must be running this version of git-annex,
|
|
||||||
and must also have been upgraded, in order for git-annex to
|
|
||||||
communicate with them.
|
|
||||||
* Colons are now avoided in filenames, so bare clones of git repos
|
* Colons are now avoided in filenames, so bare clones of git repos
|
||||||
can be put on USB thumb drives formatted with vFAT or similar
|
can be put on USB thumb drives formatted with vFAT or similar
|
||||||
filesystems.
|
filesystems.
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue