2013-11-23 04:54:08 +00:00
|
|
|
{- git-annex assistant upgrading
|
|
|
|
-
|
2015-01-21 16:50:09 +00:00
|
|
|
- Copyright 2013 Joey Hess <id@joeyh.name>
|
2013-11-23 04:54:08 +00:00
|
|
|
-
|
2016-11-22 03:46:59 +00:00
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
2013-11-23 04:54:08 +00:00
|
|
|
-}
|
|
|
|
|
2013-11-24 03:45:49 +00:00
|
|
|
{-# LANGUAGE CPP #-}
|
|
|
|
|
2013-11-23 04:54:08 +00:00
|
|
|
module Assistant.Upgrade where
|
|
|
|
|
|
|
|
import Assistant.Common
|
2013-11-23 19:50:17 +00:00
|
|
|
import Assistant.Restart
|
2013-11-23 04:54:08 +00:00
|
|
|
import qualified Annex
|
|
|
|
import Assistant.Alert
|
|
|
|
import Assistant.DaemonStatus
|
2013-11-23 16:39:36 +00:00
|
|
|
import Utility.Env
|
global webapp redirects, to finish upgrades
When an automatic upgrade completes, or when the user clicks on the upgrade
button in one webapp, but also has it open in another browser window/tab,
we have a problem: The current web server is going to stop running in
minutes, but there is no way to send a redirect to the web browser to the
new url.
To solve this, used long polling, so the webapp is always listening for
urls it should redirect to. This allows globally redirecting every open
webapp. Works great! Tested with 2 web browsers with 2 tabs each.
May be useful for other purposes later too, dunno.
The overhead is 2 http requests per page load in the webapp. Due to yesod's
speed, this does not seem to noticibly delay it. Only 1 of the requests
could possibly block the page load, the other is async.
2013-11-23 18:47:38 +00:00
|
|
|
import Types.Distribution
|
2016-08-03 16:37:12 +00:00
|
|
|
import Types.Transfer
|
2013-11-24 01:58:39 +00:00
|
|
|
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
|
2014-12-17 17:57:52 +00:00
|
|
|
import Annex.UUID
|
2013-11-24 01:58:39 +00:00
|
|
|
import qualified Backend
|
|
|
|
import qualified Types.Backend
|
|
|
|
import qualified Types.Key
|
2013-11-24 02:12:36 +00:00
|
|
|
import Assistant.TransferQueue
|
|
|
|
import Assistant.TransferSlots
|
2013-11-24 03:45:49 +00:00
|
|
|
import Remote (remoteFromUUID)
|
2013-11-24 20:03:03 +00:00
|
|
|
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
|
2014-04-23 17:30:30 +00:00
|
|
|
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
|
2014-04-23 17:30:30 +00:00
|
|
|
import qualified Build.SysConfig
|
|
|
|
import qualified Utility.Url as Url
|
|
|
|
import qualified Annex.Url as Url
|
2013-11-24 02:12:36 +00:00
|
|
|
|
|
|
|
import qualified Data.Map as M
|
2013-11-24 03:45:49 +00:00
|
|
|
import Data.Tuple.Utils
|
2013-11-23 04:54:08 +00:00
|
|
|
|
2013-11-23 19:50:17 +00:00
|
|
|
{- Upgrade without interaction in the webapp. -}
|
|
|
|
unattendedUpgrade :: Assistant ()
|
|
|
|
unattendedUpgrade = do
|
|
|
|
prepUpgrade
|
|
|
|
url <- runRestart
|
|
|
|
postUpgrade url
|
2013-11-23 04:54:08 +00:00
|
|
|
|
|
|
|
prepUpgrade :: Assistant ()
|
|
|
|
prepUpgrade = do
|
|
|
|
void $ addAlert upgradingAlert
|
2014-10-16 00:33:52 +00:00
|
|
|
liftIO $ setEnv upgradedEnv "1" True
|
2013-11-23 19:50:17 +00:00
|
|
|
prepRestart
|
2013-11-23 04:54:08 +00:00
|
|
|
|
global webapp redirects, to finish upgrades
When an automatic upgrade completes, or when the user clicks on the upgrade
button in one webapp, but also has it open in another browser window/tab,
we have a problem: The current web server is going to stop running in
minutes, but there is no way to send a redirect to the web browser to the
new url.
To solve this, used long polling, so the webapp is always listening for
urls it should redirect to. This allows globally redirecting every open
webapp. Works great! Tested with 2 web browsers with 2 tabs each.
May be useful for other purposes later too, dunno.
The overhead is 2 http requests per page load in the webapp. Due to yesod's
speed, this does not seem to noticibly delay it. Only 1 of the requests
could possibly block the page load, the other is async.
2013-11-23 18:47:38 +00:00
|
|
|
postUpgrade :: URLString -> Assistant ()
|
2013-11-23 19:50:17 +00:00
|
|
|
postUpgrade = postRestart
|
global webapp redirects, to finish upgrades
When an automatic upgrade completes, or when the user clicks on the upgrade
button in one webapp, but also has it open in another browser window/tab,
we have a problem: The current web server is going to stop running in
minutes, but there is no way to send a redirect to the web browser to the
new url.
To solve this, used long polling, so the webapp is always listening for
urls it should redirect to. This allows globally redirecting every open
webapp. Works great! Tested with 2 web browsers with 2 tabs each.
May be useful for other purposes later too, dunno.
The overhead is 2 http requests per page load in the webapp. Due to yesod's
speed, this does not seem to noticibly delay it. Only 1 of the requests
could possibly block the page load, the other is async.
2013-11-23 18:47:38 +00:00
|
|
|
|
|
|
|
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
|
|
|
|
2013-11-24 02:12:36 +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,
|
2013-11-24 19:03:50 +00:00
|
|
|
- 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.
|
|
|
|
-}
|
2013-11-24 02:12:36 +00:00
|
|
|
startDistributionDownload :: GitAnnexDistribution -> Assistant ()
|
2013-11-24 19:03:50 +00:00
|
|
|
startDistributionDownload d = go =<< liftIO . newVersionLocation d =<< liftIO oldVersionLocation
|
2013-11-24 02:12:36 +00:00
|
|
|
where
|
2014-10-09 18:53:13 +00:00
|
|
|
go Nothing = debug ["Skipping redundant upgrade"]
|
2013-11-24 19:03:50 +00:00
|
|
|
go (Just dest) = do
|
2014-12-08 23:14:24 +00:00
|
|
|
liftAnnex $ setUrlPresent webUUID k u
|
2013-11-24 19:03:50 +00:00
|
|
|
hook <- asIO1 $ distributionDownloadComplete d dest cleanup
|
|
|
|
modifyDaemonStatus_ $ \s -> s
|
|
|
|
{ transferHook = M.insert k hook (transferHook s) }
|
2017-03-10 17:12:24 +00:00
|
|
|
maybe noop (queueTransfer "upgrade" Next (AssociatedFile (Just f)) t)
|
2013-11-24 19:03:50 +00:00
|
|
|
=<< liftAnnex (remoteFromUUID webUUID)
|
|
|
|
startTransfer t
|
2013-11-24 02:12:36 +00:00
|
|
|
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
|
2015-10-09 19:48:02 +00:00
|
|
|
lockContentForRemoval k removeAnnex
|
2014-12-08 23:14:24 +00:00
|
|
|
setUrlMissing webUUID k u
|
2013-11-24 03:45:49 +00:00
|
|
|
logStatus k InfoMissing
|
2013-11-24 02:12:36 +00:00
|
|
|
|
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.
|
|
|
|
-
|
2015-10-01 17:28:49 +00:00
|
|
|
- Verifies the content of the downloaded key.
|
2013-11-24 03:45:49 +00:00
|
|
|
-}
|
2013-11-24 19:03:50 +00:00
|
|
|
distributionDownloadComplete :: GitAnnexDistribution -> FilePath -> Assistant () -> Transfer -> Assistant ()
|
|
|
|
distributionDownloadComplete d dest cleanup t
|
2013-11-24 04:26:20 +00:00
|
|
|
| transferDirection t == Download = do
|
|
|
|
debug ["finished downloading git-annex distribution"]
|
2013-11-24 19:03:50 +00:00
|
|
|
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
|
2017-02-24 19:16:56 +00:00
|
|
|
fsckit f = case Backend.maybeLookupBackendVariety (Types.Key.keyVariety k) of
|
2013-11-24 01:58:39 +00:00
|
|
|
Nothing -> return $ Just f
|
2015-10-01 17:28:49 +00:00
|
|
|
Just b -> case Types.Backend.verifyKeyContent b of
|
2013-11-24 01:58:39 +00:00
|
|
|
Nothing -> return $ Just f
|
2015-10-01 17:28:49 +00:00
|
|
|
Just verifier -> ifM (verifier k f)
|
2013-11-24 01:58:39 +00:00
|
|
|
( 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
|
2013-11-24 19:03:50 +00:00
|
|
|
ua <- asIO $ upgradeToDistribution dest cleanup f
|
2013-11-24 18:04:03 +00:00
|
|
|
fa <- asIO1 failedupgrade
|
2013-11-24 19:03:50 +00:00
|
|
|
liftIO $ ua `catchNonAsync` (fa . show)
|
|
|
|
failedupgrade msg = do
|
|
|
|
void $ addAlert $ upgradeFailedAlert msg
|
2013-11-24 18:04:03 +00:00
|
|
|
cleanup
|
2013-11-24 19:03:50 +00:00
|
|
|
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.
|
|
|
|
-}
|
2013-11-24 19:03:50 +00:00
|
|
|
upgradeToDistribution :: FilePath -> Assistant () -> FilePath -> Assistant ()
|
|
|
|
upgradeToDistribution newdir cleanup distributionfile = do
|
2013-11-24 19:53:15 +00:00
|
|
|
liftIO $ createDirectoryIfMissing True newdir
|
2013-11-24 05:11:04 +00:00
|
|
|
(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
|
2013-11-24 05:11:04 +00:00
|
|
|
- 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"]) $
|
2016-11-16 01:29:54 +00:00
|
|
|
giveup "New git-annex program failed to run! Not using."
|
2013-11-24 03:45:49 +00:00
|
|
|
pf <- programFile
|
|
|
|
liftIO $ writeFile pf program
|
2013-11-24 05:11:04 +00:00
|
|
|
|
|
|
|
#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
|
2015-01-09 17:11:56 +00:00
|
|
|
withTmpDirIn (parentDir newdir) "git-annex.upgrade" $ \tmpdir -> do
|
2013-11-24 19:53:15 +00:00
|
|
|
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"
|
2013-11-25 17:24:36 +00:00
|
|
|
, 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)
|
2013-11-24 05:11:04 +00:00
|
|
|
#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
|
2013-11-24 19:03:50 +00:00
|
|
|
olddir <- oldVersionLocation
|
2015-01-09 17:11:56 +00:00
|
|
|
withTmpDirIn (parentDir newdir) "git-annex.upgrade" $ \tmpdir -> do
|
2013-11-24 05:11:04 +00:00
|
|
|
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"
|
2013-11-24 19:03:50 +00:00
|
|
|
, Param $ "zcat < " ++ shellEscape distributionfile ++
|
2013-11-24 05:11:04 +00:00
|
|
|
" > " ++ shellEscape tarball
|
|
|
|
]
|
|
|
|
tarok <- boolSystem "tar"
|
|
|
|
[ Param "xf"
|
|
|
|
, Param tarball
|
|
|
|
, Param "--directory", File tmpdir
|
|
|
|
]
|
|
|
|
unless tarok $
|
2013-11-24 19:03:50 +00:00
|
|
|
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)
|
2013-11-25 17:24:36 +00:00
|
|
|
installby a dstdir srcdir =
|
|
|
|
mapM_ (\x -> a x (dstdir </> takeFileName x))
|
|
|
|
=<< dirContents srcdir
|
2013-11-24 05:11:04 +00:00
|
|
|
#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
|
2015-01-09 17:11:56 +00:00
|
|
|
let origdir = parentDir olddir </> installBase
|
2013-11-24 19:53:15 +00:00
|
|
|
nukeFile origdir
|
|
|
|
createSymbolicLink newdir origdir
|
2013-11-24 19:03:50 +00:00
|
|
|
|
|
|
|
{- Finds where the old version was installed. -}
|
|
|
|
oldVersionLocation :: IO FilePath
|
|
|
|
oldVersionLocation = do
|
2015-01-09 17:11:56 +00:00
|
|
|
pdir <- parentDir <$> readProgramFile
|
2014-05-21 17:27:40 +00:00
|
|
|
#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)
|
2013-11-24 19:03:50 +00:00
|
|
|
#else
|
2014-05-21 17:27:40 +00:00
|
|
|
let olddir = pdir
|
2013-11-24 19:03:50 +00:00
|
|
|
#endif
|
|
|
|
when (null olddir) $
|
2014-05-21 17:27:40 +00:00
|
|
|
error $ "Cannot find old distribution bundle; not upgrading. (Looked in " ++ pdir ++ ")"
|
2013-11-24 19:03:50 +00:00
|
|
|
return olddir
|
2013-11-24 05:11:04 +00:00
|
|
|
|
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.
|
2013-11-24 19:03:50 +00:00
|
|
|
-
|
|
|
|
- The directory is created. If it already exists, returns Nothing.
|
2013-11-24 16:49:03 +00:00
|
|
|
-}
|
2013-11-24 19:03:50 +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
|
2013-11-24 19:03:50 +00:00
|
|
|
s = installBase ++ "." ++ distributionVersion d
|
2015-01-09 17:11:56 +00:00
|
|
|
topdir = parentDir olddir
|
2013-11-24 16:49:03 +00:00
|
|
|
newloc = topdir </> s
|
2013-11-24 19:03:50 +00:00
|
|
|
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"
|
2013-11-24 19:03:50 +00:00
|
|
|
#else
|
|
|
|
"dir"
|
|
|
|
#endif
|
|
|
|
#endif
|
2013-11-24 16:49:03 +00:00
|
|
|
|
2013-11-24 05:11:04 +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
|
2013-11-24 05:11:04 +00:00
|
|
|
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.
|
|
|
|
-}
|
2015-02-28 20:59:52 +00:00
|
|
|
upgradeFlagFile :: IO FilePath
|
|
|
|
upgradeFlagFile = programPath
|
2013-11-24 03:45:49 +00:00
|
|
|
|
|
|
|
{- 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.
|
2015-02-28 20:59:52 +00:00
|
|
|
program <- programPath
|
|
|
|
untilM (doesFileExist program <&&> nowriter program) $
|
|
|
|
threadDelaySeconds (Seconds 60)
|
|
|
|
boolSystem program [Param "version"]
|
2013-11-24 03:45:49 +00:00
|
|
|
)
|
|
|
|
where
|
|
|
|
nowriter f = null
|
|
|
|
. filter (`elem` [Lsof.OpenReadWrite, Lsof.OpenWriteOnly])
|
|
|
|
. map snd3
|
|
|
|
<$> Lsof.query [f]
|
2013-11-24 04:26:20 +00:00
|
|
|
|
|
|
|
usingDistribution :: IO Bool
|
|
|
|
usingDistribution = isJust <$> getEnv "GIT_ANNEX_STANDLONE_ENV"
|
2014-04-23 17:30:30 +00:00
|
|
|
|
|
|
|
downloadDistributionInfo :: Assistant (Maybe GitAnnexDistribution)
|
|
|
|
downloadDistributionInfo = do
|
|
|
|
uo <- liftAnnex Url.getUrlOptions
|
2015-09-09 22:06:49 +00:00
|
|
|
gpgcmd <- liftAnnex $ gpgCmd <$> Annex.getGitConfig
|
2014-04-23 17:30:30 +00:00
|
|
|
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
|
2015-09-09 22:06:49 +00:00
|
|
|
<&&> verifyDistributionSig gpgcmd sigf)
|
2017-02-24 22:51:57 +00:00
|
|
|
( parseInfoFile <$> readFileStrict infof
|
2014-04-23 17:30:30 +00:00
|
|
|
, 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.
|
|
|
|
-}
|
2015-09-09 22:06:49 +00:00
|
|
|
verifyDistributionSig :: GpgCmd -> FilePath -> IO Bool
|
|
|
|
verifyDistributionSig gpgcmd sig = do
|
2014-04-23 17:30:30 +00:00
|
|
|
p <- readProgramFile
|
|
|
|
if isAbsolute p
|
2014-07-03 19:43:09 +00:00
|
|
|
then withUmask 0o0077 $ withTmpDir "git-annex-gpg.tmp" $ \gpgtmp -> do
|
2014-04-23 17:30:30 +00:00
|
|
|
let trustedkeys = takeDirectory p </> "trustedkeys.gpg"
|
2015-09-09 22:06:49 +00:00
|
|
|
boolGpgCmd gpgcmd
|
2014-04-23 17:30:30 +00:00
|
|
|
[ 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
|