improve version checking for v3

Do not set annex.version whenever any command is run. Just do it in init.
This ensures that, if a repo has annex.version=3, it has a git-annex
branch, so we don't have to run a command every time to check for the
branch.

Remove the old ad-hoc logic for v0 and v1, to simplify version checking.
This commit is contained in:
Joey Hess 2011-06-22 18:07:45 -04:00
parent c7a1690f02
commit 944c51ba26
4 changed files with 16 additions and 32 deletions

View file

@ -22,7 +22,7 @@ import Types
import Utility import Utility
command :: [Command] command :: [Command]
command = [repoCommand "init" paramDesc seek command = [standaloneCommand "init" paramDesc seek
"initialize git-annex with repository description"] "initialize git-annex with repository description"]
seek :: [CommandSeek] seek :: [CommandSeek]

View file

@ -9,6 +9,7 @@ module Command.Version where
import Control.Monad.State (liftIO) import Control.Monad.State (liftIO)
import Data.String.Utils import Data.String.Utils
import Data.Maybe
import Command import Command
import qualified SysConfig import qualified SysConfig
@ -24,7 +25,7 @@ start :: CommandStartNothing
start = do start = do
liftIO $ putStrLn $ "git-annex version: " ++ SysConfig.packageversion liftIO $ putStrLn $ "git-annex version: " ++ SysConfig.packageversion
v <- getVersion v <- getVersion
liftIO $ putStrLn $ "local repository version: " ++ v liftIO $ putStrLn $ "local repository version: " ++ fromMaybe "unknown" v
liftIO $ putStrLn $ "default repository version: " ++ defaultVersion liftIO $ putStrLn $ "default repository version: " ++ defaultVersion
liftIO $ putStrLn $ "supported repository versions: " ++ vs supportedVersions liftIO $ putStrLn $ "supported repository versions: " ++ vs supportedVersions
liftIO $ putStrLn $ "upgrade supported from repository versions: " ++ vs upgradableVersions liftIO $ putStrLn $ "upgrade supported from repository versions: " ++ vs upgradableVersions

View file

@ -18,7 +18,7 @@ upgrade :: Annex Bool
upgrade = do upgrade = do
version <- getVersion version <- getVersion
case version of case version of
"0" -> Upgrade.V0.upgrade Just "0" -> Upgrade.V0.upgrade
"1" -> Upgrade.V1.upgrade Just "1" -> Upgrade.V1.upgrade
"2" -> Upgrade.V2.upgrade Just "2" -> Upgrade.V2.upgrade
_ -> return True _ -> return True

View file

@ -7,14 +7,11 @@
module Version where module Version where
import Control.Monad.State (liftIO)
import Control.Monad (unless) import Control.Monad (unless)
import System.Directory
import Types import Types
import qualified Annex import qualified Annex
import qualified GitRepo as Git import qualified GitRepo as Git
import Locations
import Config import Config
type Version = String type Version = String
@ -31,40 +28,26 @@ upgradableVersions = ["0", "1", "2"]
versionField :: String versionField :: String
versionField = "annex.version" versionField = "annex.version"
getVersion :: Annex Version getVersion :: Annex (Maybe Version)
getVersion = do getVersion = do
g <- Annex.gitRepo g <- Annex.gitRepo
let v = Git.configGet g versionField "" let v = Git.configGet g versionField ""
if not $ null v if not $ null v
then return v then return $ Just v
else do else return Nothing
-- version 0 was not recorded in .git/config;
-- such a repo should have an gitAnnexDir but no
-- gitAnnexObjectDir.
--
-- version 1 may not be recorded if the user
-- forgot to init. Such a repo should have a
-- gitAnnexObjectDir already.
d <- liftIO $ doesDirectoryExist $ gitAnnexDir g
o <- liftIO $ doesDirectoryExist $ gitAnnexObjectDir g
case (d, o) of
(True, False) -> return "0"
(True, True) -> return "1"
_ -> do
setVersion
return defaultVersion
setVersion :: Annex () setVersion :: Annex ()
setVersion = setConfig versionField defaultVersion setVersion = setConfig versionField defaultVersion
checkVersion :: Annex () checkVersion :: Annex ()
checkVersion = do checkVersion = getVersion >>= handle
v <- getVersion
unless (v `elem` supportedVersions) $ do
error $ "Repository version " ++ v ++
" is not supported. " ++
msg v
where where
handle Nothing = error "First run: git-annex init"
handle (Just v) = do
unless (v `elem` supportedVersions) $ do
error $ "Repository version " ++ v ++
" is not supported. " ++
msg v
msg v msg v
| v `elem` upgradableVersions = "Upgrade this repository: git-annex upgrade" | v `elem` upgradableVersions = "Upgrade this repository: git-annex upgrade"
| otherwise = "Upgrade git-annex." | otherwise = "Upgrade git-annex."