2012-06-13 21:54:23 +00:00
|
|
|
{- git-annex assistant sanity checker
|
|
|
|
-
|
assistant: Detect stale git lock files at startup time, and remove them.
Extends the index.lock handling to other git lock files. I surveyed
all lock files used by git, and found more than I expected. All are
handled the same in git; it leaves them open while doing the operation,
possibly writing the new file content to the lock file, and then closes
them when done.
The gc.pid file is excluded because it won't affect the normal operation
of the assistant, and waiting for a gc to finish on startup wouldn't be
good.
All threads except the webapp thread wait on the new startup sanity checker
thread to complete, so they won't try to do things with git that fail
due to stale lock files. The webapp thread mostly avoids doing that kind of
thing itself. A few configurators might fail on lock files, but only if the
user is explicitly trying to run them. The webapp needs to start
immediately when the user has opened it, even if there are stale lock
files.
Arranging for the threads to wait on the startup sanity checker was a bit
of a bear. Have to get all the NotificationHandles set up before the
startup sanity checker runs, or they won't see its signal. Perhaps
the NotificationBroadcaster is not the best interface to have used for
this. Oh well, it works.
This commit was sponsored by Michael Jakl
2013-10-05 21:02:11 +00:00
|
|
|
- Copyright 2012, 2013 Joey Hess <joey@kitenet.net>
|
2012-06-23 05:20:40 +00:00
|
|
|
-
|
|
|
|
- Licensed under the GNU GPL version 3 or higher.
|
2012-06-13 21:54:23 +00:00
|
|
|
-}
|
|
|
|
|
2012-06-25 20:10:10 +00:00
|
|
|
module Assistant.Threads.SanityChecker (
|
assistant: Detect stale git lock files at startup time, and remove them.
Extends the index.lock handling to other git lock files. I surveyed
all lock files used by git, and found more than I expected. All are
handled the same in git; it leaves them open while doing the operation,
possibly writing the new file content to the lock file, and then closes
them when done.
The gc.pid file is excluded because it won't affect the normal operation
of the assistant, and waiting for a gc to finish on startup wouldn't be
good.
All threads except the webapp thread wait on the new startup sanity checker
thread to complete, so they won't try to do things with git that fail
due to stale lock files. The webapp thread mostly avoids doing that kind of
thing itself. A few configurators might fail on lock files, but only if the
user is explicitly trying to run them. The webapp needs to start
immediately when the user has opened it, even if there are stale lock
files.
Arranging for the threads to wait on the startup sanity checker was a bit
of a bear. Have to get all the NotificationHandles set up before the
startup sanity checker runs, or they won't see its signal. Perhaps
the NotificationBroadcaster is not the best interface to have used for
this. Oh well, it works.
This commit was sponsored by Michael Jakl
2013-10-05 21:02:11 +00:00
|
|
|
sanityCheckerStartupThread,
|
2013-03-01 17:30:48 +00:00
|
|
|
sanityCheckerDailyThread,
|
|
|
|
sanityCheckerHourlyThread
|
2012-06-13 21:54:23 +00:00
|
|
|
) where
|
|
|
|
|
2012-07-20 23:29:59 +00:00
|
|
|
import Assistant.Common
|
2012-06-13 21:54:23 +00:00
|
|
|
import Assistant.DaemonStatus
|
2012-07-29 21:53:18 +00:00
|
|
|
import Assistant.Alert
|
2012-07-20 23:29:59 +00:00
|
|
|
import qualified Git.LsFiles
|
2013-03-03 17:39:57 +00:00
|
|
|
import qualified Git.Command
|
2013-03-03 18:07:13 +00:00
|
|
|
import qualified Git.Config
|
2012-06-13 21:54:23 +00:00
|
|
|
import Utility.ThreadScheduler
|
2012-06-25 20:10:10 +00:00
|
|
|
import qualified Assistant.Threads.Watcher as Watcher
|
2013-03-01 17:30:48 +00:00
|
|
|
import Utility.LogFile
|
2013-06-21 17:29:42 +00:00
|
|
|
import Utility.Batch
|
assistant: Detect stale git lock files at startup time, and remove them.
Extends the index.lock handling to other git lock files. I surveyed
all lock files used by git, and found more than I expected. All are
handled the same in git; it leaves them open while doing the operation,
possibly writing the new file content to the lock file, and then closes
them when done.
The gc.pid file is excluded because it won't affect the normal operation
of the assistant, and waiting for a gc to finish on startup wouldn't be
good.
All threads except the webapp thread wait on the new startup sanity checker
thread to complete, so they won't try to do things with git that fail
due to stale lock files. The webapp thread mostly avoids doing that kind of
thing itself. A few configurators might fail on lock files, but only if the
user is explicitly trying to run them. The webapp needs to start
immediately when the user has opened it, even if there are stale lock
files.
Arranging for the threads to wait on the startup sanity checker was a bit
of a bear. Have to get all the NotificationHandles set up before the
startup sanity checker runs, or they won't see its signal. Perhaps
the NotificationBroadcaster is not the best interface to have used for
this. Oh well, it works.
This commit was sponsored by Michael Jakl
2013-10-05 21:02:11 +00:00
|
|
|
import Utility.NotificationBroadcaster
|
2013-03-04 18:25:18 +00:00
|
|
|
import Config
|
assistant: Detect stale git lock files at startup time, and remove them.
Extends the index.lock handling to other git lock files. I surveyed
all lock files used by git, and found more than I expected. All are
handled the same in git; it leaves them open while doing the operation,
possibly writing the new file content to the lock file, and then closes
them when done.
The gc.pid file is excluded because it won't affect the normal operation
of the assistant, and waiting for a gc to finish on startup wouldn't be
good.
All threads except the webapp thread wait on the new startup sanity checker
thread to complete, so they won't try to do things with git that fail
due to stale lock files. The webapp thread mostly avoids doing that kind of
thing itself. A few configurators might fail on lock files, but only if the
user is explicitly trying to run them. The webapp needs to start
immediately when the user has opened it, even if there are stale lock
files.
Arranging for the threads to wait on the startup sanity checker was a bit
of a bear. Have to get all the NotificationHandles set up before the
startup sanity checker runs, or they won't see its signal. Perhaps
the NotificationBroadcaster is not the best interface to have used for
this. Oh well, it works.
This commit was sponsored by Michael Jakl
2013-10-05 21:02:11 +00:00
|
|
|
import qualified Git
|
|
|
|
import qualified Utility.Lsof as Lsof
|
2013-10-26 16:42:58 +00:00
|
|
|
import Utility.HumanTime
|
2012-06-13 21:54:23 +00:00
|
|
|
|
|
|
|
import Data.Time.Clock.POSIX
|
|
|
|
|
assistant: Detect stale git lock files at startup time, and remove them.
Extends the index.lock handling to other git lock files. I surveyed
all lock files used by git, and found more than I expected. All are
handled the same in git; it leaves them open while doing the operation,
possibly writing the new file content to the lock file, and then closes
them when done.
The gc.pid file is excluded because it won't affect the normal operation
of the assistant, and waiting for a gc to finish on startup wouldn't be
good.
All threads except the webapp thread wait on the new startup sanity checker
thread to complete, so they won't try to do things with git that fail
due to stale lock files. The webapp thread mostly avoids doing that kind of
thing itself. A few configurators might fail on lock files, but only if the
user is explicitly trying to run them. The webapp needs to start
immediately when the user has opened it, even if there are stale lock
files.
Arranging for the threads to wait on the startup sanity checker was a bit
of a bear. Have to get all the NotificationHandles set up before the
startup sanity checker runs, or they won't see its signal. Perhaps
the NotificationBroadcaster is not the best interface to have used for
this. Oh well, it works.
This commit was sponsored by Michael Jakl
2013-10-05 21:02:11 +00:00
|
|
|
{- This thread runs once at startup, and most other threads wait for it
|
|
|
|
- to finish. (However, the webapp thread does not, to prevent the UI
|
|
|
|
- being nonresponsive.) -}
|
2013-10-26 16:42:58 +00:00
|
|
|
sanityCheckerStartupThread :: Maybe Duration -> NamedThread
|
|
|
|
sanityCheckerStartupThread startupdelay = namedThreadUnchecked "SanityCheckerStartup" $ do
|
|
|
|
checkStaleGitLocks
|
|
|
|
|
|
|
|
liftIO $ maybe noop (threadDelaySeconds . Seconds . fromIntegral . durationSeconds) startupdelay
|
|
|
|
|
|
|
|
{- Notify other threads that the startup sanity check is done. -}
|
|
|
|
status <- getDaemonStatus
|
|
|
|
liftIO $ sendNotification $ startupSanityCheckNotifier status
|
assistant: Detect stale git lock files at startup time, and remove them.
Extends the index.lock handling to other git lock files. I surveyed
all lock files used by git, and found more than I expected. All are
handled the same in git; it leaves them open while doing the operation,
possibly writing the new file content to the lock file, and then closes
them when done.
The gc.pid file is excluded because it won't affect the normal operation
of the assistant, and waiting for a gc to finish on startup wouldn't be
good.
All threads except the webapp thread wait on the new startup sanity checker
thread to complete, so they won't try to do things with git that fail
due to stale lock files. The webapp thread mostly avoids doing that kind of
thing itself. A few configurators might fail on lock files, but only if the
user is explicitly trying to run them. The webapp needs to start
immediately when the user has opened it, even if there are stale lock
files.
Arranging for the threads to wait on the startup sanity checker was a bit
of a bear. Have to get all the NotificationHandles set up before the
startup sanity checker runs, or they won't see its signal. Perhaps
the NotificationBroadcaster is not the best interface to have used for
this. Oh well, it works.
This commit was sponsored by Michael Jakl
2013-10-05 21:02:11 +00:00
|
|
|
|
2013-03-01 17:30:48 +00:00
|
|
|
{- This thread wakes up hourly for inxepensive frequent sanity checks. -}
|
|
|
|
sanityCheckerHourlyThread :: NamedThread
|
|
|
|
sanityCheckerHourlyThread = namedThread "SanityCheckerHourly" $ forever $ do
|
|
|
|
liftIO $ threadDelaySeconds $ Seconds oneHour
|
|
|
|
hourlyCheck
|
|
|
|
|
|
|
|
{- This thread wakes up daily to make sure the tree is in good shape. -}
|
|
|
|
sanityCheckerDailyThread :: NamedThread
|
|
|
|
sanityCheckerDailyThread = namedThread "SanityCheckerDaily" $ forever $ do
|
2012-10-29 06:21:04 +00:00
|
|
|
waitForNextCheck
|
2012-06-13 21:54:23 +00:00
|
|
|
|
2012-10-29 06:21:04 +00:00
|
|
|
debug ["starting sanity check"]
|
2012-10-29 20:49:47 +00:00
|
|
|
void $ alertWhile sanityCheckAlert go
|
2012-10-29 06:21:04 +00:00
|
|
|
debug ["sanity check complete"]
|
|
|
|
where
|
|
|
|
go = do
|
2012-10-30 19:39:15 +00:00
|
|
|
modifyDaemonStatus_ $ \s -> s { sanityCheckRunning = True }
|
2012-10-29 06:21:04 +00:00
|
|
|
|
2013-10-03 02:59:07 +00:00
|
|
|
now <- liftIO getPOSIXTime -- before check started
|
2013-06-21 17:29:42 +00:00
|
|
|
r <- either showerr return =<< (tryIO . batch) <~> dailyCheck
|
2012-07-29 21:53:18 +00:00
|
|
|
|
2012-10-30 19:39:15 +00:00
|
|
|
modifyDaemonStatus_ $ \s -> s
|
2012-10-29 06:21:04 +00:00
|
|
|
{ sanityCheckRunning = False
|
|
|
|
, lastSanityCheck = Just now
|
|
|
|
}
|
2012-07-29 21:53:18 +00:00
|
|
|
|
2012-10-29 06:21:04 +00:00
|
|
|
return r
|
2012-07-20 23:29:59 +00:00
|
|
|
|
2012-10-29 06:21:04 +00:00
|
|
|
showerr e = do
|
|
|
|
liftAnnex $ warning $ show e
|
|
|
|
return False
|
2012-07-30 06:07:02 +00:00
|
|
|
|
2012-06-13 21:54:23 +00:00
|
|
|
{- Only run one check per day, from the time of the last check. -}
|
2012-10-29 06:21:04 +00:00
|
|
|
waitForNextCheck :: Assistant ()
|
|
|
|
waitForNextCheck = do
|
2012-10-30 18:44:18 +00:00
|
|
|
v <- lastSanityCheck <$> getDaemonStatus
|
2012-10-29 06:21:04 +00:00
|
|
|
now <- liftIO getPOSIXTime
|
|
|
|
liftIO $ threadDelaySeconds $ Seconds $ calcdelay now v
|
|
|
|
where
|
|
|
|
calcdelay _ Nothing = oneDay
|
|
|
|
calcdelay now (Just lastcheck)
|
|
|
|
| lastcheck < now = max oneDay $
|
|
|
|
oneDay - truncate (now - lastcheck)
|
|
|
|
| otherwise = oneDay
|
2012-06-13 21:54:23 +00:00
|
|
|
|
2012-06-13 23:25:47 +00:00
|
|
|
{- It's important to stay out of the Annex monad as much as possible while
|
|
|
|
- running potentially expensive parts of this check, since remaining in it
|
|
|
|
- will block the watcher. -}
|
2013-03-01 17:30:48 +00:00
|
|
|
dailyCheck :: Assistant Bool
|
|
|
|
dailyCheck = do
|
2012-10-29 06:21:04 +00:00
|
|
|
g <- liftAnnex gitRepo
|
2013-03-03 17:39:57 +00:00
|
|
|
|
2012-06-13 23:25:47 +00:00
|
|
|
-- Find old unstaged symlinks, and add them to git.
|
2012-10-29 06:21:04 +00:00
|
|
|
(unstaged, cleanup) <- liftIO $ Git.LsFiles.notInRepo False ["."] g
|
2013-10-03 02:59:07 +00:00
|
|
|
now <- liftIO getPOSIXTime
|
2012-06-13 23:25:47 +00:00
|
|
|
forM_ unstaged $ \file -> do
|
2012-10-29 06:21:04 +00:00
|
|
|
ms <- liftIO $ catchMaybeIO $ getSymbolicLinkStatus file
|
2012-06-13 23:25:47 +00:00
|
|
|
case ms of
|
|
|
|
Just s | toonew (statusChangeTime s) now -> noop
|
2012-10-29 06:21:04 +00:00
|
|
|
| isSymbolicLink s -> addsymlink file ms
|
2012-06-13 23:25:47 +00:00
|
|
|
_ -> noop
|
2012-10-29 06:21:04 +00:00
|
|
|
liftIO $ void cleanup
|
2013-03-03 17:39:57 +00:00
|
|
|
|
|
|
|
{- Allow git-gc to run once per day. More frequent gc is avoided
|
2013-03-03 18:07:13 +00:00
|
|
|
- by default to avoid slowing things down. Only run repacks when 100x
|
|
|
|
- the usual number of loose objects are present; we tend
|
|
|
|
- to have a lot of small objects and they should not be a
|
|
|
|
- significant size. -}
|
|
|
|
when (Git.Config.getMaybe "gc.auto" g == Just "0") $
|
|
|
|
liftIO $ void $ Git.Command.runBool
|
|
|
|
[ Param "-c", Param "gc.auto=670000"
|
|
|
|
, Param "gc"
|
|
|
|
, Param "--auto"
|
|
|
|
] g
|
2013-03-03 17:39:57 +00:00
|
|
|
|
2012-07-30 06:07:02 +00:00
|
|
|
return True
|
2012-10-29 06:21:04 +00:00
|
|
|
where
|
|
|
|
toonew timestamp now = now < (realToFrac (timestamp + slop) :: POSIXTime)
|
|
|
|
slop = fromIntegral tenMinutes
|
|
|
|
insanity msg = do
|
|
|
|
liftAnnex $ warning msg
|
2012-10-30 19:39:15 +00:00
|
|
|
void $ addAlert $ sanityCheckFixAlert msg
|
2012-10-29 06:21:04 +00:00
|
|
|
addsymlink file s = do
|
2013-03-04 18:25:18 +00:00
|
|
|
isdirect <- liftAnnex isDirect
|
|
|
|
Watcher.runHandler (Watcher.onAddSymlink isdirect) file s
|
2012-10-29 06:21:04 +00:00
|
|
|
insanity $ "found unstaged symlink: " ++ file
|
2013-03-01 17:30:48 +00:00
|
|
|
|
|
|
|
hourlyCheck :: Assistant ()
|
|
|
|
hourlyCheck = checkLogSize 0
|
|
|
|
|
|
|
|
{- Rotate logs until log file size is < 1 mb. -}
|
|
|
|
checkLogSize :: Int -> Assistant ()
|
|
|
|
checkLogSize n = do
|
|
|
|
f <- liftAnnex $ fromRepo gitAnnexLogFile
|
|
|
|
logs <- liftIO $ listLogs f
|
|
|
|
totalsize <- liftIO $ sum <$> mapM filesize logs
|
|
|
|
when (totalsize > oneMegabyte) $ do
|
|
|
|
notice ["Rotated logs due to size:", show totalsize]
|
2013-03-01 20:55:54 +00:00
|
|
|
liftIO $ openLog f >>= redirLog
|
2013-03-01 17:30:48 +00:00
|
|
|
when (n < maxLogs + 1) $
|
|
|
|
checkLogSize $ n + 1
|
|
|
|
where
|
|
|
|
filesize f = fromIntegral . fileSize <$> liftIO (getFileStatus f)
|
|
|
|
|
assistant: Detect stale git lock files at startup time, and remove them.
Extends the index.lock handling to other git lock files. I surveyed
all lock files used by git, and found more than I expected. All are
handled the same in git; it leaves them open while doing the operation,
possibly writing the new file content to the lock file, and then closes
them when done.
The gc.pid file is excluded because it won't affect the normal operation
of the assistant, and waiting for a gc to finish on startup wouldn't be
good.
All threads except the webapp thread wait on the new startup sanity checker
thread to complete, so they won't try to do things with git that fail
due to stale lock files. The webapp thread mostly avoids doing that kind of
thing itself. A few configurators might fail on lock files, but only if the
user is explicitly trying to run them. The webapp needs to start
immediately when the user has opened it, even if there are stale lock
files.
Arranging for the threads to wait on the startup sanity checker was a bit
of a bear. Have to get all the NotificationHandles set up before the
startup sanity checker runs, or they won't see its signal. Perhaps
the NotificationBroadcaster is not the best interface to have used for
this. Oh well, it works.
This commit was sponsored by Michael Jakl
2013-10-05 21:02:11 +00:00
|
|
|
{- Detect when a git lock file exists and has no git process currently
|
|
|
|
- writing to it. This strongly suggests it is a stale lock file.
|
|
|
|
-
|
|
|
|
- However, this could be on a network filesystem. Which is not very safe
|
|
|
|
- anyway (the assistant relies on being able to check when files have
|
|
|
|
- no writers to know when to commit them). Just in case, when the lock
|
|
|
|
- file appears stale, we delay for one minute, and check its size. If
|
|
|
|
- the size changed, delay for another minute, and so on. This will at
|
|
|
|
- least work to detect is another machine is writing out a new index
|
|
|
|
- file, since git does so by writing the new content to index.lock.
|
|
|
|
-}
|
|
|
|
checkStaleGitLocks :: Assistant ()
|
|
|
|
checkStaleGitLocks = do
|
|
|
|
lockfiles <- filter (not . isInfixOf "gc.pid")
|
|
|
|
. filter (".lock" `isSuffixOf`)
|
2013-10-07 17:03:05 +00:00
|
|
|
<$> (liftIO . dirContentsRecursiveSkipping (== dropTrailingPathSeparator annexDir)
|
assistant: Detect stale git lock files at startup time, and remove them.
Extends the index.lock handling to other git lock files. I surveyed
all lock files used by git, and found more than I expected. All are
handled the same in git; it leaves them open while doing the operation,
possibly writing the new file content to the lock file, and then closes
them when done.
The gc.pid file is excluded because it won't affect the normal operation
of the assistant, and waiting for a gc to finish on startup wouldn't be
good.
All threads except the webapp thread wait on the new startup sanity checker
thread to complete, so they won't try to do things with git that fail
due to stale lock files. The webapp thread mostly avoids doing that kind of
thing itself. A few configurators might fail on lock files, but only if the
user is explicitly trying to run them. The webapp needs to start
immediately when the user has opened it, even if there are stale lock
files.
Arranging for the threads to wait on the startup sanity checker was a bit
of a bear. Have to get all the NotificationHandles set up before the
startup sanity checker runs, or they won't see its signal. Perhaps
the NotificationBroadcaster is not the best interface to have used for
this. Oh well, it works.
This commit was sponsored by Michael Jakl
2013-10-05 21:02:11 +00:00
|
|
|
=<< liftAnnex (fromRepo Git.localGitDir))
|
|
|
|
checkStaleLocks lockfiles
|
|
|
|
checkStaleLocks :: [FilePath] -> Assistant ()
|
|
|
|
checkStaleLocks lockfiles = go =<< getsizes
|
|
|
|
where
|
|
|
|
getsize lf = catchMaybeIO $
|
|
|
|
(\s -> (lf, fileSize s)) <$> getFileStatus lf
|
|
|
|
getsizes = liftIO $ catMaybes <$> mapM getsize lockfiles
|
|
|
|
go [] = return ()
|
|
|
|
go l = ifM (liftIO $ null <$> Lsof.query ("--" : map fst l))
|
|
|
|
( do
|
|
|
|
waitforit "to check stale git lock file"
|
|
|
|
l' <- getsizes
|
|
|
|
if l' == l
|
|
|
|
then liftIO $ mapM_ nukeFile (map fst l)
|
|
|
|
else go l'
|
|
|
|
, do
|
|
|
|
waitforit "for git lock file writer"
|
|
|
|
go =<< getsizes
|
|
|
|
)
|
|
|
|
waitforit why = do
|
|
|
|
notice ["Waiting for 60 seconds", why]
|
|
|
|
liftIO $ threadDelaySeconds $ Seconds 60
|
|
|
|
|
2013-03-01 17:30:48 +00:00
|
|
|
oneMegabyte :: Int
|
|
|
|
oneMegabyte = 1000000
|
|
|
|
|
|
|
|
oneHour :: Int
|
|
|
|
oneHour = 60 * 60
|
|
|
|
|
|
|
|
oneDay :: Int
|
|
|
|
oneDay = 24 * oneHour
|
assistant: Detect stale git lock files at startup time, and remove them.
Extends the index.lock handling to other git lock files. I surveyed
all lock files used by git, and found more than I expected. All are
handled the same in git; it leaves them open while doing the operation,
possibly writing the new file content to the lock file, and then closes
them when done.
The gc.pid file is excluded because it won't affect the normal operation
of the assistant, and waiting for a gc to finish on startup wouldn't be
good.
All threads except the webapp thread wait on the new startup sanity checker
thread to complete, so they won't try to do things with git that fail
due to stale lock files. The webapp thread mostly avoids doing that kind of
thing itself. A few configurators might fail on lock files, but only if the
user is explicitly trying to run them. The webapp needs to start
immediately when the user has opened it, even if there are stale lock
files.
Arranging for the threads to wait on the startup sanity checker was a bit
of a bear. Have to get all the NotificationHandles set up before the
startup sanity checker runs, or they won't see its signal. Perhaps
the NotificationBroadcaster is not the best interface to have used for
this. Oh well, it works.
This commit was sponsored by Michael Jakl
2013-10-05 21:02:11 +00:00
|
|
|
|