Merge branch 'master' into s3-aws

Conflicts:
	Utility/Url.hs
	debian/changelog
	git-annex.cabal
This commit is contained in:
Joey Hess 2014-09-18 14:36:20 -04:00
commit f7847ae98d
282 changed files with 6524 additions and 1207 deletions

View file

@ -53,6 +53,10 @@ postRestart url = do
liftIO . sendNotification . globalRedirNotifier =<< getDaemonStatus
void $ liftIO $ forkIO $ do
threadDelaySeconds (Seconds 120)
terminateSelf
terminateSelf :: IO ()
terminateSelf =
#ifndef mingw32_HOST_OS
signalProcess sigTERM =<< getPID
#else

View file

@ -21,7 +21,9 @@ import Assistant.Drop
import Assistant.Ssh
import Assistant.TransferQueue
import Assistant.Types.UrlRenderer
import Assistant.Restart
import qualified Annex.Branch
import qualified Git
import qualified Git.LsFiles
import qualified Git.Command.Batch
import qualified Git.Config
@ -146,6 +148,8 @@ waitForNextCheck = do
- will block the watcher. -}
dailyCheck :: UrlRenderer -> Assistant Bool
dailyCheck urlrenderer = do
checkRepoExists
g <- liftAnnex gitRepo
batchmaker <- liftIO getBatchCommandMaker
@ -203,6 +207,7 @@ dailyCheck urlrenderer = do
hourlyCheck :: Assistant ()
hourlyCheck = do
checkRepoExists
#ifndef mingw32_HOST_OS
checkLogSize 0
#else
@ -316,3 +321,9 @@ cleanOld check f = go =<< catchMaybeIO getmtime
getmtime = realToFrac . modificationTime <$> getSymbolicLinkStatus f
go (Just mtime) | check mtime = nukeFile f
go _ = noop
checkRepoExists :: Assistant ()
checkRepoExists = do
g <- liftAnnex gitRepo
liftIO $ unlessM (doesDirectoryExist $ Git.repoPath g) $
terminateSelf

View file

@ -77,7 +77,7 @@ expireUnused duration = do
forM_ oldkeys $ \k -> do
debug ["removing old unused key", key2file k]
liftAnnex $ do
removeAnnex k
lockContent k removeAnnex
logStatus k InfoMissing
where
boundry = durationToPOSIXTime <$> duration

View file

@ -96,7 +96,7 @@ startDistributionDownload d = go =<< liftIO . newVersionLocation d =<< liftIO ol
, transferKey = k
}
cleanup = liftAnnex $ do
removeAnnex k
lockContent k removeAnnex
setUrlMissing k u
logStatus k InfoMissing

View file

@ -5,7 +5,7 @@
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE CPP, TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-}
{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses, TemplateHaskell, OverloadedStrings, RankNTypes #-}
module Assistant.WebApp.Control where
@ -16,16 +16,10 @@ import Assistant.TransferSlots
import Assistant.Restart
import Utility.LogFile
import Utility.NotificationBroadcaster
import Utility.PID
import Control.Concurrent
import qualified Data.Map as M
import qualified Data.Text as T
#ifndef mingw32_HOST_OS
import System.Posix (signalProcess, sigTERM)
#else
import Utility.WinProcess
#endif
getShutdownR :: Handler Html
getShutdownR = page "Shutdown" Nothing $
@ -53,15 +47,11 @@ getShutdownConfirmedR = do
- page time to load in the browser. -}
void $ liftIO $ forkIO $ do
threadDelay 2000000
#ifndef mingw32_HOST_OS
signalProcess sigTERM =<< getPID
#else
terminatePID =<< getPID
#endif
terminateSelf
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
- fail and cause thet web browser to show an error once the webapp is
- truely stopped. -}
getNotRunningR :: Handler Html
getNotRunningR = customPage' False Nothing $