git-annex (5.20131127) unstable; urgency=low
* webapp: Detect when upgrades are available, and upgrade if the user desires. (Only when git-annex is installed using the prebuilt binaries from git-annex upstream, not from eg Debian.) * assistant: Detect when the git-annex binary is modified or replaced, and either prompt the user to restart the program, or automatically restart it. * annex.autoupgrade configures both the above upgrade behaviors. * Added support for quvi 0.9. Slightly suboptimal due to limitations in its interface compared with the old version. * Bug fix: annex.version did not get set on automatic upgrade to v5 direct mode repo, so the upgrade was performed repeatedly, slowing commands down. * webapp: Fix bug that broke switching between local repositories that use the new guarded direct mode. * Android: Fix stripping of the git-annex binary. * Android: Make terminal app show git-annex version number. * Android: Re-enable XMPP support. * reinject: Allow to be used in direct mode. * Futher improvements to git repo repair. Has now been tested in tens of thousands of intentionally damaged repos, and successfully repaired them all. * Allow use of --unused in bare repository. # imported from the archive
This commit is contained in:
commit
7189dfd77d
6383 changed files with 204042 additions and 0 deletions
79
Assistant/WebApp/Control.hs
Normal file
79
Assistant/WebApp/Control.hs
Normal file
|
@ -0,0 +1,79 @@
|
|||
{- git-annex assistant webapp control
|
||||
-
|
||||
- Copyright 2012, 2013 Joey Hess <joey@kitenet.net>
|
||||
-
|
||||
- Licensed under the GNU AGPL version 3 or higher.
|
||||
-}
|
||||
|
||||
{-# LANGUAGE CPP, TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-}
|
||||
|
||||
module Assistant.WebApp.Control where
|
||||
|
||||
import Assistant.WebApp.Common
|
||||
import Assistant.DaemonStatus
|
||||
import Assistant.Alert
|
||||
import Assistant.TransferSlots
|
||||
import Assistant.Restart
|
||||
import Utility.LogFile
|
||||
import Utility.NotificationBroadcaster
|
||||
|
||||
import Control.Concurrent
|
||||
import System.Posix (getProcessID, signalProcess, sigTERM)
|
||||
import qualified Data.Map as M
|
||||
import qualified Data.Text as T
|
||||
|
||||
getShutdownR :: Handler Html
|
||||
getShutdownR = page "Shutdown" Nothing $
|
||||
$(widgetFile "control/shutdown")
|
||||
|
||||
getShutdownConfirmedR :: Handler Html
|
||||
getShutdownConfirmedR = do
|
||||
liftAssistant $ do
|
||||
{- Remove all alerts for currently running activities. -}
|
||||
updateAlertMap $ M.filter $ \a -> alertClass a /= Activity
|
||||
void $ addAlert shutdownAlert
|
||||
{- Stop transfers the assistant is running,
|
||||
- otherwise they would continue past shutdown.
|
||||
- Pausing transfers prevents more being started up (and stops
|
||||
- the transfer processes). -}
|
||||
ts <- M.keys . currentTransfers <$> getDaemonStatus
|
||||
mapM_ pauseTransfer ts
|
||||
webapp <- getYesod
|
||||
let url = T.unpack $ yesodRender webapp (T.pack "") NotRunningR []
|
||||
{- Signal any other web browsers. -}
|
||||
liftAssistant $ do
|
||||
modifyDaemonStatus_ $ \status -> status { globalRedirUrl = Just url }
|
||||
liftIO . sendNotification . globalRedirNotifier =<< getDaemonStatus
|
||||
{- Wait 2 seconds before shutting down, to give the web
|
||||
- page time to load in the browser. -}
|
||||
void $ liftIO $ forkIO $ do
|
||||
threadDelay 2000000
|
||||
signalProcess sigTERM =<< getProcessID
|
||||
redirect NotRunningR
|
||||
|
||||
{- Use a custom page to avoid putting long polling elements on it that will
|
||||
- fail and cause the web browser to show an error once the webapp is
|
||||
- truely stopped. -}
|
||||
getNotRunningR :: Handler Html
|
||||
getNotRunningR = customPage' False Nothing $
|
||||
$(widgetFile "control/notrunning")
|
||||
|
||||
getRestartR :: Handler Html
|
||||
getRestartR = do
|
||||
liftAssistant prepRestart
|
||||
url <- liftAssistant runRestart
|
||||
liftAssistant $ postRestart url
|
||||
redirect url
|
||||
|
||||
getRestartThreadR :: ThreadName -> Handler ()
|
||||
getRestartThreadR name = do
|
||||
m <- liftAssistant $ startedThreads <$> getDaemonStatus
|
||||
liftIO $ maybe noop snd $ M.lookup name m
|
||||
redirectBack
|
||||
|
||||
getLogR :: Handler Html
|
||||
getLogR = page "Logs" Nothing $ do
|
||||
logfile <- liftAnnex $ fromRepo gitAnnexLogFile
|
||||
logs <- liftIO $ listLogs logfile
|
||||
logcontent <- liftIO $ concat <$> mapM readFileStrictAnyEncoding logs
|
||||
$(widgetFile "control/log")
|
Loading…
Add table
Add a link
Reference in a new issue