2010-11-14 18:44:24 +00:00
|
|
|
{- git-annex upgrade support
|
|
|
|
-
|
2022-01-19 17:06:31 +00:00
|
|
|
- Copyright 2010-2022 Joey Hess <id@joeyh.name>
|
2010-11-14 18:44:24 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2010-11-14 18:44:24 +00:00
|
|
|
-}
|
|
|
|
|
2013-05-11 20:03:00 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
2010-11-14 18:44:24 +00:00
|
|
|
module Upgrade where
|
|
|
|
|
2016-01-20 20:36:33 +00:00
|
|
|
import Annex.Common
|
2022-01-19 17:06:31 +00:00
|
|
|
import Types.Upgrade
|
2019-09-01 17:29:55 +00:00
|
|
|
import qualified Annex
|
|
|
|
import qualified Git
|
2020-03-09 20:47:57 +00:00
|
|
|
import Config
|
2020-03-30 20:03:44 +00:00
|
|
|
import Annex.Path
|
2011-10-04 04:40:47 +00:00
|
|
|
import Annex.Version
|
2018-10-25 21:23:53 +00:00
|
|
|
import Types.RepoVersion
|
2022-01-19 19:51:04 +00:00
|
|
|
import Logs.Upgrade
|
2013-08-04 17:07:55 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2011-03-16 05:23:20 +00:00
|
|
|
import qualified Upgrade.V0
|
|
|
|
import qualified Upgrade.V1
|
2013-05-11 20:03:00 +00:00
|
|
|
#endif
|
2011-06-22 21:51:48 +00:00
|
|
|
import qualified Upgrade.V2
|
2013-12-29 17:06:23 +00:00
|
|
|
import qualified Upgrade.V3
|
2013-11-05 20:42:59 +00:00
|
|
|
import qualified Upgrade.V4
|
2015-12-04 20:14:48 +00:00
|
|
|
import qualified Upgrade.V5
|
2018-10-25 21:23:53 +00:00
|
|
|
import qualified Upgrade.V6
|
2019-11-06 19:37:18 +00:00
|
|
|
import qualified Upgrade.V7
|
2022-01-11 18:52:50 +00:00
|
|
|
import qualified Upgrade.V8
|
2022-01-19 17:06:31 +00:00
|
|
|
import qualified Upgrade.V9
|
2010-11-14 18:44:24 +00:00
|
|
|
|
2018-10-25 22:33:34 +00:00
|
|
|
import qualified Data.Map as M
|
2022-01-19 19:51:04 +00:00
|
|
|
import Data.Time.Clock.POSIX
|
2018-10-25 22:33:34 +00:00
|
|
|
|
2018-10-25 21:23:53 +00:00
|
|
|
checkUpgrade :: RepoVersion -> Annex ()
|
2016-11-16 01:29:54 +00:00
|
|
|
checkUpgrade = maybe noop giveup <=< needsUpgrade
|
2013-11-17 18:58:35 +00:00
|
|
|
|
2018-10-25 21:23:53 +00:00
|
|
|
needsUpgrade :: RepoVersion -> Annex (Maybe String)
|
2013-11-17 18:58:35 +00:00
|
|
|
needsUpgrade v
|
2022-07-25 20:09:11 +00:00
|
|
|
| v `elem` supportedVersions = case M.lookup v autoUpgradeableVersions of
|
|
|
|
Just newv | newv /= v -> ifM (annexAutoUpgradeRepository <$> Annex.getGitConfig)
|
|
|
|
( runupgrade newv
|
|
|
|
, ok
|
|
|
|
)
|
|
|
|
_ -> ok
|
2018-10-25 22:33:34 +00:00
|
|
|
| otherwise = case M.lookup v autoUpgradeableVersions of
|
|
|
|
Nothing
|
2022-01-19 16:14:50 +00:00
|
|
|
| v `elem` upgradeableVersions ->
|
2018-10-25 22:33:34 +00:00
|
|
|
err "Upgrade this repository: git-annex upgrade"
|
|
|
|
| otherwise ->
|
|
|
|
err "Upgrade git-annex."
|
2019-09-01 17:29:55 +00:00
|
|
|
Just newv -> ifM (annexAutoUpgradeRepository <$> Annex.getGitConfig)
|
2022-07-25 20:09:11 +00:00
|
|
|
( runupgrade newv
|
2019-09-01 17:29:55 +00:00
|
|
|
, err "Automatic upgrade is disabled by annex.autoupgraderepository configuration. To upgrade this repository: git-annex upgrade"
|
2018-10-25 22:33:34 +00:00
|
|
|
)
|
2013-11-05 20:42:59 +00:00
|
|
|
where
|
2019-09-01 17:29:55 +00:00
|
|
|
err msg = do
|
|
|
|
g <- Annex.gitRepo
|
2020-10-30 17:31:35 +00:00
|
|
|
p <- liftIO $ absPath $ Git.repoPath g
|
2019-09-01 17:29:55 +00:00
|
|
|
return $ Just $ unwords
|
2020-10-30 17:31:35 +00:00
|
|
|
[ "Repository", fromRawFilePath p
|
2019-09-01 17:29:55 +00:00
|
|
|
, "is at unsupported version"
|
|
|
|
, show (fromRepoVersion v) ++ "."
|
|
|
|
, msg
|
|
|
|
]
|
2022-07-25 20:09:11 +00:00
|
|
|
|
2013-11-17 18:58:35 +00:00
|
|
|
ok = return Nothing
|
2013-11-05 20:42:59 +00:00
|
|
|
|
2022-07-25 20:09:11 +00:00
|
|
|
runupgrade newv = tryNonAsync (upgrade True newv) >>= \case
|
|
|
|
Right True -> ok
|
|
|
|
Right False -> err "Automatic upgrade failed!"
|
|
|
|
Left ex -> err $ "Automatic upgrade exception! " ++ show ex
|
|
|
|
|
2018-10-25 21:23:53 +00:00
|
|
|
upgrade :: Bool -> RepoVersion -> Annex Bool
|
2022-09-26 16:55:51 +00:00
|
|
|
upgrade automatic destversion = go =<< getVersion
|
2012-11-11 04:51:07 +00:00
|
|
|
where
|
2018-10-26 18:29:52 +00:00
|
|
|
go (Just v)
|
2022-09-26 16:55:51 +00:00
|
|
|
| v >= destversion = return True
|
2020-03-09 20:47:57 +00:00
|
|
|
| otherwise = ifM upgradingRemote
|
|
|
|
( upgraderemote
|
2022-01-19 17:06:31 +00:00
|
|
|
, up v >>= \case
|
2022-09-26 16:55:51 +00:00
|
|
|
UpgradeSuccess -> do
|
|
|
|
let v' = incrversion v
|
|
|
|
upgradedto v'
|
|
|
|
go (Just v')
|
|
|
|
UpgradeFailed -> return False
|
|
|
|
UpgradeDeferred -> return True
|
2018-10-26 18:29:52 +00:00
|
|
|
)
|
2022-09-26 16:55:51 +00:00
|
|
|
go Nothing = return True
|
2018-10-26 18:29:52 +00:00
|
|
|
|
2022-01-19 17:06:31 +00:00
|
|
|
incrversion v = RepoVersion (fromRepoVersion v + 1)
|
|
|
|
|
2013-08-04 17:07:55 +00:00
|
|
|
#ifndef mingw32_HOST_OS
|
2018-10-26 18:29:52 +00:00
|
|
|
up (RepoVersion 0) = Upgrade.V0.upgrade
|
|
|
|
up (RepoVersion 1) = Upgrade.V1.upgrade
|
2013-05-11 20:03:00 +00:00
|
|
|
#else
|
2018-10-26 18:29:52 +00:00
|
|
|
up (RepoVersion 0) = giveup "upgrade from v0 on Windows not supported"
|
|
|
|
up (RepoVersion 1) = giveup "upgrade from v1 on Windows not supported"
|
2013-05-11 20:03:00 +00:00
|
|
|
#endif
|
2018-10-26 18:29:52 +00:00
|
|
|
up (RepoVersion 2) = Upgrade.V2.upgrade
|
|
|
|
up (RepoVersion 3) = Upgrade.V3.upgrade automatic
|
|
|
|
up (RepoVersion 4) = Upgrade.V4.upgrade automatic
|
|
|
|
up (RepoVersion 5) = Upgrade.V5.upgrade automatic
|
|
|
|
up (RepoVersion 6) = Upgrade.V6.upgrade automatic
|
2019-11-06 19:37:18 +00:00
|
|
|
up (RepoVersion 7) = Upgrade.V7.upgrade automatic
|
2022-01-11 18:52:50 +00:00
|
|
|
up (RepoVersion 8) = Upgrade.V8.upgrade automatic
|
2022-01-19 17:06:31 +00:00
|
|
|
up (RepoVersion 9) = Upgrade.V9.upgrade automatic
|
|
|
|
up _ = return UpgradeDeferred
|
2020-03-09 20:47:57 +00:00
|
|
|
|
|
|
|
-- Upgrade local remotes by running git-annex upgrade in them.
|
|
|
|
-- This avoids complicating the upgrade code by needing to handle
|
|
|
|
-- upgrading a git repo other than the current repo.
|
|
|
|
upgraderemote = do
|
|
|
|
rp <- fromRawFilePath <$> fromRepo Git.repoPath
|
2022-09-26 16:55:51 +00:00
|
|
|
ok <- gitAnnexChildProcess "upgrade"
|
propagate git-annex -c on to transferrer child process
git -c was already propagated via environment, but need this for
consistency.
Also, notice it does not use gitAnnexChildProcess to run the
transferrer. So nothing is done about avoid it taking the
pid lock. It's possible that the caller is already doing something that
took the pid lock, and if so, the transferrer will certianly fail,
since it needs to take the pid lock too. This may prevent combining
annex.stalldetection with annex.pidlock, but I have not verified it's
really a problem. If it was, it seems git-annex would have to take
the pid lock when starting a transferrer, and hold it until shutdown,
or would need to take pid lock when starting to use a transferrer,
and hold it until done with a transfer and then drop it. The latter
would require starting the transferrer with pid locking disabled for the
child process, so assumes that the transferrer does not do anyting that
needs locking when not running a transfer.
2020-12-15 15:36:25 +00:00
|
|
|
[ Param "--quiet"
|
|
|
|
, Param "--autoonly"
|
2020-03-09 20:47:57 +00:00
|
|
|
]
|
|
|
|
(\p -> p { cwd = Just rp })
|
2020-08-25 18:57:25 +00:00
|
|
|
(\_ _ _ pid -> waitForProcess pid >>= return . \case
|
2022-09-26 16:55:51 +00:00
|
|
|
ExitSuccess -> True
|
|
|
|
_ -> False
|
2020-08-25 18:57:25 +00:00
|
|
|
)
|
2022-09-26 16:55:51 +00:00
|
|
|
when ok
|
|
|
|
reloadConfig
|
|
|
|
return ok
|
2020-03-09 20:47:57 +00:00
|
|
|
|
2022-01-19 19:51:04 +00:00
|
|
|
upgradedto v = do
|
|
|
|
setVersion v
|
|
|
|
writeUpgradeLog v =<< liftIO getPOSIXTime
|
|
|
|
|
2020-03-09 20:47:57 +00:00
|
|
|
upgradingRemote :: Annex Bool
|
|
|
|
upgradingRemote = isJust <$> fromRepo Git.remoteName
|