aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authornicolas.pouillard <nicolas.pouillard@gmail.com>2008-01-14 21:28:33 +0100
committernicolas.pouillard <nicolas.pouillard@gmail.com>2008-01-14 21:28:33 +0100
commit672132c833ff5511c3f3b31cb9b4a9e1adcacaf8 (patch)
treef57f18a6bda19701a4b20ae3a74ef6bcae711ea7 /XMonad
parentabe51db04ba60b2ec984713c9811e05ccf078f04 (diff)
downloadXMonadContrib-672132c833ff5511c3f3b31cb9b4a9e1adcacaf8.tar.gz
XMonadContrib-672132c833ff5511c3f3b31cb9b4a9e1adcacaf8.tar.xz
XMonadContrib-672132c833ff5511c3f3b31cb9b4a9e1adcacaf8.zip
Use doubleFork instead of manual double fork, or buggy single fork.
This fixes showWName because Timer was leaking zombie processes. You should update xmonad, since doubleFork was not exported. darcs-hash:20080114202833-94725-04a4419a36181a6cc0d662b868fef3374d9b38c1.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Util/Run.hs42
-rw-r--r--XMonad/Util/Timer.hs3
2 files changed, 16 insertions, 29 deletions
diff --git a/XMonad/Util/Run.hs b/XMonad/Util/Run.hs
index c9ac2a5..face2d8 100644
--- a/XMonad/Util/Run.hs
+++ b/XMonad/Util/Run.hs
@@ -29,11 +29,9 @@ module XMonad.Util.Run (
) where
import System.Posix.IO
-import System.Posix.Process (createSession, forkProcess, executeFile,
- getProcessStatus)
+import System.Posix.Process (executeFile)
import Control.Concurrent (threadDelay)
import Control.Exception (try)
-import System.Exit (ExitCode(ExitSuccess), exitWith)
import System.IO
import System.Process (runInteractiveProcess, waitForProcess)
import XMonad
@@ -67,22 +65,16 @@ runProcessWithInput cmd args input = do
-- | Wait is in us
runProcessWithInputAndWait :: FilePath -> [String] -> String -> Int -> IO ()
runProcessWithInputAndWait cmd args input timeout = do
- pid <- forkProcess $ do
- forkProcess $ do -- double fork it over to init
- createSession
- (pin, pout, perr, ph) <- runInteractiveProcess cmd args Nothing Nothing
- hPutStr pin input
- hFlush pin
- threadDelay timeout
- hClose pin
- hClose pout
- hClose perr
- waitForProcess ph
- return ()
- exitWith ExitSuccess
- return ()
- getProcessStatus True False pid
- return ()
+ doubleFork $ do
+ (pin, pout, perr, ph) <- runInteractiveProcess cmd args Nothing Nothing
+ hPutStr pin input
+ hFlush pin
+ threadDelay timeout
+ hClose pin
+ hClose pout
+ hClose perr
+ waitForProcess ph
+ return ()
-- | Multiplies by ONE MILLION, for use with
-- 'runProcessWithInputAndWait'.
@@ -113,7 +105,7 @@ seconds = fromEnum . (* 1000000)
-- interpolation, whereas the safeSpawn example can be safe because
-- Firefox doesn't need any arguments if it is just being started.
safeSpawn :: MonadIO m => FilePath -> String -> m ()
-safeSpawn prog arg = liftIO (try (forkProcess $ executeFile prog True [arg] Nothing) >> return ())
+safeSpawn prog arg = liftIO (try (doubleFork $ executeFile prog True [arg] Nothing) >> return ())
unsafeSpawn :: MonadIO m => String -> m ()
unsafeSpawn = spawn
@@ -134,11 +126,7 @@ spawnPipe x = do
setFdOption wr CloseOnExec True
h <- fdToHandle wr
hSetBuffering h LineBuffering
- pid <- forkProcess $ do
- forkProcess $ do
- dupTo rd stdInput
- createSession
- executeFile "/bin/sh" False ["-c", x] Nothing
- exitWith ExitSuccess
- getProcessStatus True False pid
+ doubleFork $ do
+ dupTo rd stdInput
+ executeFile "/bin/sh" False ["-c", x] Nothing
return h
diff --git a/XMonad/Util/Timer.hs b/XMonad/Util/Timer.hs
index 65ed65c..8d5c2f7 100644
--- a/XMonad/Util/Timer.hs
+++ b/XMonad/Util/Timer.hs
@@ -24,7 +24,6 @@ import Control.Applicative
import Control.Concurrent
import Data.Unique
import System.Environment
-import System.Posix.Process
-- $usage
-- This module can be used to setup a timer to handle deferred events.
@@ -40,7 +39,7 @@ startTimer s = io $ do
d <- openDisplay dpy
rw <- rootWindow d $ defaultScreen d
u <- hashUnique <$> newUnique
- forkProcess $ do
+ doubleFork $ do
threadDelay (fromEnum $ s * 1000000)
a <- internAtom d "XMONAD_TIMER" False
allocaXEvent $ \e -> do