git-annex/Assistant/Upgrade.hs

366 lines
11 KiB
Haskell
Raw Normal View History

{- git-annex assistant upgrading
-
- Copyright 2013 Joey Hess <joey@kitenet.net>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
2013-11-24 03:45:49 +00:00
{-# LANGUAGE CPP #-}
module Assistant.Upgrade where
import Assistant.Common
import Assistant.Restart
import qualified Annex
import Assistant.Alert
import Assistant.DaemonStatus
import Utility.Env
import Types.Distribution
2013-11-24 01:58:39 +00:00
import Logs.Transfer
import Logs.Web
2013-11-24 03:45:49 +00:00
import Logs.Presence
import Logs.Location
2013-11-24 01:58:39 +00:00
import Annex.Content
import qualified Backend
import qualified Types.Backend
import qualified Types.Key
import Assistant.TransferQueue
import Assistant.TransferSlots
2013-11-24 03:45:49 +00:00
import Remote (remoteFromUUID)
import Annex.Path
2013-11-24 03:45:49 +00:00
import Config.Files
import Utility.ThreadScheduler
import Utility.Tmp
2013-11-24 16:49:03 +00:00
import Utility.UserInfo
import Utility.Gpg
2014-07-03 23:49:26 +00:00
import Utility.FileMode
2013-11-24 03:45:49 +00:00
import qualified Utility.Lsof as Lsof
import qualified Build.SysConfig
import qualified Utility.Url as Url
import qualified Annex.Url as Url
import qualified Data.Map as M
2013-11-24 03:45:49 +00:00
import Data.Tuple.Utils
{- Upgrade without interaction in the webapp. -}
unattendedUpgrade :: Assistant ()
unattendedUpgrade = do
prepUpgrade
url <- runRestart
postUpgrade url
prepUpgrade :: Assistant ()
prepUpgrade = do
void $ addAlert upgradingAlert
void $ liftIO $ setEnv upgradedEnv "1" True
prepRestart
postUpgrade :: URLString -> Assistant ()
postUpgrade = postRestart
autoUpgradeEnabled :: Assistant Bool
autoUpgradeEnabled = liftAnnex $ (==) AutoUpgrade . annexAutoUpgrade <$> Annex.getGitConfig
checkSuccessfulUpgrade :: IO Bool
checkSuccessfulUpgrade = isJust <$> getEnv upgradedEnv
upgradedEnv :: String
upgradedEnv = "GIT_ANNEX_UPGRADED"
2013-11-24 01:58:39 +00:00
{- Start downloading the distribution key from the web.
2013-11-24 03:45:49 +00:00
- Install a hook that will be run once the download is complete,
- and finishes the upgrade.
-
- Creates the destination directory where the upgrade will be installed
- early, in order to check if another upgrade has happened (or is
- happending). On failure, the directory is removed.
-}
startDistributionDownload :: GitAnnexDistribution -> Assistant ()
startDistributionDownload d = go =<< liftIO . newVersionLocation d =<< liftIO oldVersionLocation
where
go Nothing = debug ["Skipping redundant upgrade"]
go (Just dest) = do
liftAnnex $ setUrlPresent k u
hook <- asIO1 $ distributionDownloadComplete d dest cleanup
modifyDaemonStatus_ $ \s -> s
{ transferHook = M.insert k hook (transferHook s) }
maybe noop (queueTransfer "upgrade" Next (Just f) t)
=<< liftAnnex (remoteFromUUID webUUID)
startTransfer t
k = distributionKey d
u = distributionUrl d
f = takeFileName u ++ " (for upgrade)"
t = Transfer
{ transferDirection = Download
, transferUUID = webUUID
, transferKey = k
}
2013-11-24 03:45:49 +00:00
cleanup = liftAnnex $ do
removeAnnex k
setUrlMissing k u
logStatus k InfoMissing
2013-11-24 03:45:49 +00:00
{- Called once the download is done.
- Passed an action that can be used to clean up the downloaded file.
-
- Fsck the key to verify the download.
-}
distributionDownloadComplete :: GitAnnexDistribution -> FilePath -> Assistant () -> Transfer -> Assistant ()
distributionDownloadComplete d dest cleanup t
| transferDirection t == Download = do
debug ["finished downloading git-annex distribution"]
maybe (failedupgrade "bad download") go
=<< liftAnnex (withObjectLoc k fsckit (getM fsckit))
2013-11-24 16:49:03 +00:00
| otherwise = cleanup
2013-11-24 01:58:39 +00:00
where
k = distributionKey d
fsckit f = case Backend.maybeLookupBackendName (Types.Key.keyBackendName k) of
Nothing -> return $ Just f
Just b -> case Types.Backend.fsckKey b of
Nothing -> return $ Just f
Just a -> ifM (a k f)
( return $ Just f
2013-11-24 03:45:49 +00:00
, return Nothing
2013-11-24 01:58:39 +00:00
)
2013-11-24 18:04:03 +00:00
go f = do
ua <- asIO $ upgradeToDistribution dest cleanup f
2013-11-24 18:04:03 +00:00
fa <- asIO1 failedupgrade
liftIO $ ua `catchNonAsync` (fa . show)
failedupgrade msg = do
void $ addAlert $ upgradeFailedAlert msg
2013-11-24 18:04:03 +00:00
cleanup
liftIO $ void $ tryIO $ removeDirectoryRecursive dest
2013-11-24 01:58:39 +00:00
2013-11-24 03:45:49 +00:00
{- The upgrade method varies by OS.
-
- In general, find where the distribution was installed before,
- and unpack the new distribution next to it (in a versioned directory).
- Then update the programFile to point to the new version.
-}
upgradeToDistribution :: FilePath -> Assistant () -> FilePath -> Assistant ()
upgradeToDistribution newdir cleanup distributionfile = do
2013-11-24 19:53:15 +00:00
liftIO $ createDirectoryIfMissing True newdir
(program, deleteold) <- unpack
changeprogram program
2013-11-24 03:45:49 +00:00
cleanup
prepUpgrade
url <- runRestart
{- At this point, the new assistant is fully running, so
- it's safe to delete the old version. -}
2013-11-24 16:49:03 +00:00
liftIO $ void $ tryIO deleteold
2013-11-24 03:45:49 +00:00
postUpgrade url
where
changeprogram program = liftIO $ do
unlessM (boolSystem program [Param "version"]) $
error "New git-annex program failed to run! Not using."
pf <- programFile
liftIO $ writeFile pf program
#ifdef darwin_HOST_OS
{- OS X uses a dmg, so mount it, and copy the contents into place. -}
2013-11-24 19:53:15 +00:00
unpack = liftIO $ do
olddir <- oldVersionLocation
withTmpDirIn (parentDir newdir) "git-annex.upgrade" $ \tmpdir -> do
void $ boolSystem "hdiutil"
2013-11-25 17:10:45 +00:00
[ Param "attach", File distributionfile
2013-11-25 17:53:28 +00:00
, Param "-mountpoint", File tmpdir
2013-11-24 19:53:15 +00:00
]
2013-11-25 17:15:27 +00:00
void $ boolSystem "cp"
[ Param "-R"
2013-11-25 18:37:44 +00:00
, File $ tmpdir </> installBase </> "Contents"
, File $ newdir
2013-11-25 17:15:27 +00:00
]
2013-11-24 19:53:15 +00:00
void $ boolSystem "hdiutil"
[ Param "eject"
2013-11-25 18:01:41 +00:00
, File tmpdir
2013-11-24 19:53:15 +00:00
]
2013-11-25 18:46:33 +00:00
sanitycheck newdir
2013-11-24 19:53:15 +00:00
let deleteold = do
deleteFromManifest $ olddir </> "Contents" </> "MacOS"
makeorigsymlink olddir
2013-11-25 18:52:04 +00:00
return (newdir </> "Contents" </> "MacOS" </> "git-annex", deleteold)
#else
{- Linux uses a tarball (so could other POSIX systems), so
- untar it (into a temp directory) and move the directory
- into place. -}
unpack = liftIO $ do
olddir <- oldVersionLocation
2013-11-24 16:49:03 +00:00
withTmpDirIn (parentDir newdir) "git-annex.upgrade" $ \tmpdir -> do
let tarball = tmpdir </> "tar"
-- Cannot rely on filename extension, and this also
-- avoids problems if tar doesn't support transparent
-- decompression.
void $ boolSystem "sh"
[ Param "-c"
, Param $ "zcat < " ++ shellEscape distributionfile ++
" > " ++ shellEscape tarball
]
tarok <- boolSystem "tar"
[ Param "xf"
, Param tarball
, Param "--directory", File tmpdir
]
unless tarok $
error $ "failed to untar " ++ distributionfile
2013-11-25 18:46:33 +00:00
sanitycheck $ tmpdir </> installBase
2013-11-24 19:53:15 +00:00
installby rename newdir (tmpdir </> installBase)
2013-11-24 16:49:03 +00:00
let deleteold = do
deleteFromManifest olddir
2013-11-24 19:53:15 +00:00
makeorigsymlink olddir
2013-11-24 16:49:03 +00:00
return (newdir </> "git-annex", deleteold)
installby a dstdir srcdir =
mapM_ (\x -> a x (dstdir </> takeFileName x))
=<< dirContents srcdir
#endif
2013-11-24 19:53:15 +00:00
sanitycheck dir =
2013-11-25 18:47:56 +00:00
unlessM (doesDirectoryExist dir) $
2013-11-25 18:46:33 +00:00
error $ "did not find " ++ dir ++ " in " ++ distributionfile
2013-11-24 19:53:15 +00:00
makeorigsymlink olddir = do
let origdir = parentDir olddir </> installBase
nukeFile origdir
createSymbolicLink newdir origdir
{- Finds where the old version was installed. -}
oldVersionLocation :: IO FilePath
oldVersionLocation = do
2013-11-24 19:53:15 +00:00
pdir <- parentDir <$> readProgramFile
#ifdef darwin_HOST_OS
2013-11-24 19:53:15 +00:00
let dirs = splitDirectories pdir
{- It will probably be deep inside a git-annex.app directory. -}
2013-11-25 18:29:14 +00:00
let olddir = case findIndex ("git-annex.app" `isPrefixOf`) dirs of
Nothing -> pdir
Just i -> joinPath (take (i + 1) dirs)
#else
let olddir = pdir
#endif
when (null olddir) $
error $ "Cannot find old distribution bundle; not upgrading. (Looked in " ++ pdir ++ ")"
return olddir
2013-11-24 16:49:03 +00:00
{- Finds a place to install the new version.
- Generally, put it in the parent directory of where the old version was
- installed, and use a version number in the directory name.
- If unable to write to there, instead put it in the home directory.
-
- The directory is created. If it already exists, returns Nothing.
2013-11-24 16:49:03 +00:00
-}
newVersionLocation :: GitAnnexDistribution -> FilePath -> IO (Maybe FilePath)
newVersionLocation d olddir =
trymkdir newloc $ do
home <- myHomeDir
trymkdir (home </> s) $
return Nothing
2013-11-24 16:49:03 +00:00
where
s = installBase ++ "." ++ distributionVersion d
2013-11-24 16:49:03 +00:00
topdir = parentDir olddir
newloc = topdir </> s
trymkdir dir fallback =
(createDirectory dir >> return (Just dir))
`catchIO` const fallback
installBase :: String
installBase = "git-annex." ++
#ifdef linux_HOST_OS
"linux"
#else
#ifdef darwin_HOST_OS
2013-11-24 19:53:15 +00:00
"app"
#else
"dir"
#endif
#endif
2013-11-24 16:49:03 +00:00
deleteFromManifest :: FilePath -> IO ()
deleteFromManifest dir = do
fs <- map (dir </>) . lines <$> catchDefaultIO "" (readFile manifest)
mapM_ nukeFile fs
nukeFile manifest
2013-11-24 16:56:49 +00:00
removeEmptyRecursive dir
where
manifest = dir </> "git-annex.MANIFEST"
2013-11-24 16:56:49 +00:00
removeEmptyRecursive :: FilePath -> IO ()
removeEmptyRecursive dir = do
mapM_ removeEmptyRecursive =<< dirContents dir
void $ tryIO $ removeDirectory dir
2013-11-24 03:45:49 +00:00
{- This is a file that the UpgradeWatcher can watch for modifications to
- detect when git-annex has been upgraded.
-}
upgradeFlagFile :: IO (Maybe FilePath)
upgradeFlagFile = ifM usingDistribution
( Just <$> programFile
, programPath
)
{- Sanity check to see if an upgrade is complete and the program is ready
- to be run. -}
upgradeSanityCheck :: IO Bool
upgradeSanityCheck = ifM usingDistribution
( doesFileExist =<< programFile
, do
-- Ensure that the program is present, and has no writers,
-- and can be run. This should handle distribution
-- upgrades, manual upgrades, etc.
v <- programPath
case v of
Nothing -> return False
Just program -> do
untilM (doesFileExist program <&&> nowriter program) $
threadDelaySeconds (Seconds 60)
boolSystem program [Param "version"]
)
where
nowriter f = null
. filter (`elem` [Lsof.OpenReadWrite, Lsof.OpenWriteOnly])
. map snd3
<$> Lsof.query [f]
usingDistribution :: IO Bool
usingDistribution = isJust <$> getEnv "GIT_ANNEX_STANDLONE_ENV"
downloadDistributionInfo :: Assistant (Maybe GitAnnexDistribution)
downloadDistributionInfo = do
uo <- liftAnnex Url.getUrlOptions
liftIO $ withTmpDir "git-annex.tmp" $ \tmpdir -> do
let infof = tmpdir </> "info"
let sigf = infof ++ ".sig"
ifM (Url.downloadQuiet distributionInfoUrl infof uo
<&&> Url.downloadQuiet distributionInfoSigUrl sigf uo
<&&> verifyDistributionSig sigf)
( readish <$> readFileStrict infof
, return Nothing
)
distributionInfoUrl :: String
distributionInfoUrl = fromJust Build.SysConfig.upgradelocation ++ ".info"
distributionInfoSigUrl :: String
distributionInfoSigUrl = distributionInfoUrl ++ ".sig"
{- Verifies that a file from the git-annex distribution has a valid
- signature. Pass the detached .sig file; the file to be verified should
- be located next to it.
-
- The gpg keyring used to verify the signature is located in
- trustedkeys.gpg, next to the git-annex program.
-}
verifyDistributionSig :: FilePath -> IO Bool
verifyDistributionSig sig = do
p <- readProgramFile
if isAbsolute p
then withUmask 0o0077 $ withTmpDir "git-annex-gpg.tmp" $ \gpgtmp -> do
let trustedkeys = takeDirectory p </> "trustedkeys.gpg"
boolSystem gpgcmd
[ Param "--no-default-keyring"
, Param "--no-auto-check-trustdb"
, Param "--no-options"
, Param "--homedir"
, File gpgtmp
, Param "--keyring"
, File trustedkeys
, Param "--verify"
, File sig
]
else return False