git-annex/Upgrade.hs
Joey Hess 067aabdd48
wip RawFilePath 2x git-annex find speedup
Finally builds (oh the agoncy of making it build), but still very
unmergable, only Command.Find is included and lots of stuff is badly
hacked to make it compile.

Benchmarking vs master, this git-annex find is significantly faster!
Specifically:

	num files	old	new	speedup
	48500		4.77	3.73	28%
	12500		1.36	1.02	66%
	20		0.075	0.074	0% (so startup time is unchanged)

That's without really finishing the optimization. Things still to do:

* Eliminate all the fromRawFilePath, toRawFilePath, encodeBS,
  decodeBS conversions.
* Use versions of IO actions like getFileStatus that take a RawFilePath.
* Eliminate some Data.ByteString.Lazy.toStrict, which is a slow copy.
* Use ByteString for parsing git config to speed up startup.

It's likely several of those will speed up git-annex find further.
And other commands will certianly benefit even more.
2019-11-26 16:01:58 -04:00

92 lines
2.4 KiB
Haskell

{- git-annex upgrade support
-
- Copyright 2010-2019 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE CPP #-}
module Upgrade where
import Annex.Common
import qualified Annex
import qualified Git
import Annex.Version
import Types.RepoVersion
#ifndef mingw32_HOST_OS
{-
import qualified Upgrade.V0
import qualified Upgrade.V1
#endif
import qualified Upgrade.V2
import qualified Upgrade.V3
import qualified Upgrade.V4
import qualified Upgrade.V5
import qualified Upgrade.V6
-}
import qualified Data.Map as M
checkUpgrade :: RepoVersion -> Annex ()
checkUpgrade = maybe noop giveup <=< needsUpgrade
needsUpgrade :: RepoVersion -> Annex (Maybe String)
needsUpgrade v
| v `elem` supportedVersions = ok
| otherwise = case M.lookup v autoUpgradeableVersions of
Nothing
| v `elem` upgradableVersions ->
err "Upgrade this repository: git-annex upgrade"
| otherwise ->
err "Upgrade git-annex."
Just newv -> ifM (annexAutoUpgradeRepository <$> Annex.getGitConfig)
( tryNonAsync (upgrade True newv) >>= \case
Right True -> ok
Right False -> err "Automatic upgrade failed!"
Left ex -> err $ "Automatic upgrade exception! " ++ show ex
, err "Automatic upgrade is disabled by annex.autoupgraderepository configuration. To upgrade this repository: git-annex upgrade"
)
where
err msg = do
g <- Annex.gitRepo
p <- liftIO $ absPath $ Git.repoPath g
return $ Just $ unwords
[ "Repository", p
, "is at unsupported version"
, show (fromRepoVersion v) ++ "."
, msg
]
ok = return Nothing
upgrade :: Bool -> RepoVersion -> Annex Bool
upgrade automatic destversion = do
upgraded <- go =<< getVersion
when upgraded $
setVersion destversion
return upgraded
where
go (Just v)
| v >= destversion = return True
| otherwise = ifM (up v)
( go (Just (RepoVersion (fromRepoVersion v + 1)))
, return False
)
go _ = return True
{-
#ifndef mingw32_HOST_OS
up (RepoVersion 0) = Upgrade.V0.upgrade
up (RepoVersion 1) = Upgrade.V1.upgrade
#else
up (RepoVersion 0) = giveup "upgrade from v0 on Windows not supported"
up (RepoVersion 1) = giveup "upgrade from v1 on Windows not supported"
#endif
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
-}
up _ = return True