remove reapZombies

Believed to be no longer needed as I've squashed the last ones.

Note that, in Test.Framework, I can see no reason for the code to have
run it twice. It does not cause running processes to exit after all,
so any process that has leaked and is running and causing problems with
cleanup of the directory won't be helped by running it.

This commit was sponsored by Mark Reidenbach on Patreon.
This commit is contained in:
Joey Hess 2020-09-25 11:47:34 -04:00
parent f624876dc2
commit 3e577a6dd3
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
3 changed files with 1 additions and 32 deletions

View file

@ -5,20 +5,13 @@
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
{-# LANGUAGE CPP #-}
module Annex.Action ( module Annex.Action (
startup, startup,
shutdown, shutdown,
stopCoProcesses, stopCoProcesses,
reapZombies,
) where ) where
import qualified Data.Map as M import qualified Data.Map as M
#ifndef mingw32_HOST_OS
import System.Posix.Process (getAnyProcessStatus)
import Utility.Exception
#endif
import Annex.Common import Annex.Common
import qualified Annex import qualified Annex
@ -38,7 +31,6 @@ shutdown nocommit = do
saveState nocommit saveState nocommit
sequence_ =<< M.elems <$> Annex.getState Annex.cleanup sequence_ =<< M.elems <$> Annex.getState Annex.cleanup
stopCoProcesses stopCoProcesses
liftIO reapZombies -- zombies from long-running git processes
{- Stops all long-running git query processes. -} {- Stops all long-running git query processes. -}
stopCoProcesses :: Annex () stopCoProcesses :: Annex ()
@ -47,19 +39,3 @@ stopCoProcesses = do
checkAttrStop checkAttrStop
hashObjectStop hashObjectStop
checkIgnoreStop checkIgnoreStop
{- Reaps any zombie processes that may be hanging around.
-
- Warning: Not thread safe. Anything that was expecting to wait
- on a process and get back an exit status is going to be confused
- if this reap gets there first. -}
reapZombies :: IO ()
#ifndef mingw32_HOST_OS
reapZombies =
-- throws an exception when there are no child processes
catchDefaultIO Nothing (getAnyProcessStatus False True)
>>= maybe (return ()) (const reapZombies)
#else
reapZombies = return ()
#endif

View file

@ -15,7 +15,6 @@ import CmdLine
import CmdLine.GitAnnex.Options import CmdLine.GitAnnex.Options
import qualified Annex import qualified Annex
import qualified Annex.Branch import qualified Annex.Branch
import Annex.Action
import qualified Options.Applicative as O import qualified Options.Applicative as O
@ -35,10 +34,6 @@ mkGenerator cmds userinput = do
-- The cmd is run for benchmarking without startup or -- The cmd is run for benchmarking without startup or
-- shutdown actions. -- shutdown actions.
Annex.eval st $ performCommandAction cmd seek noop Annex.eval st $ performCommandAction cmd seek noop
-- Since the cmd will be run many times, some zombie
-- processes that normally only occur once per command
-- will build up; reap them.
reapZombies
where where
-- Simplified versio of CmdLine.dispatch, without support for fuzzy -- Simplified versio of CmdLine.dispatch, without support for fuzzy
-- matching or out-of-repo commands. -- matching or out-of-repo commands.

View file

@ -245,15 +245,13 @@ cleanup dir = whenM (doesDirectoryExist dir) $ do
finalCleanup :: IO () finalCleanup :: IO ()
finalCleanup = whenM (doesDirectoryExist tmpdir) $ do finalCleanup = whenM (doesDirectoryExist tmpdir) $ do
Annex.Action.reapZombies
Command.Uninit.prepareRemoveAnnexDir' tmpdir Command.Uninit.prepareRemoveAnnexDir' tmpdir
catchIO (removeDirectoryForCleanup tmpdir) $ \e -> do catchIO (removeDirectoryForCleanup tmpdir) $ \e -> do
print e print e
putStrLn "sleeping 10 seconds and will retry directory cleanup" putStrLn "sleeping 10 seconds and will retry directory cleanup"
Utility.ThreadScheduler.threadDelaySeconds $ Utility.ThreadScheduler.threadDelaySeconds $
Utility.ThreadScheduler.Seconds 10 Utility.ThreadScheduler.Seconds 10
whenM (doesDirectoryExist tmpdir) $ do whenM (doesDirectoryExist tmpdir) $
Annex.Action.reapZombies
removeDirectoryForCleanup tmpdir removeDirectoryForCleanup tmpdir
checklink :: FilePath -> Assertion checklink :: FilePath -> Assertion