aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--XMonad/Prompt/Man.hs4
-rw-r--r--XMonad/Util/Loggers.hs6
-rw-r--r--XMonad/Util/Run.hs13
-rw-r--r--XMonad/Util/Timer.hs3
4 files changed, 14 insertions, 12 deletions
diff --git a/XMonad/Prompt/Man.hs b/XMonad/Prompt/Man.hs
index 20e282d..a9c8d0e 100644
--- a/XMonad/Prompt/Man.hs
+++ b/XMonad/Prompt/Man.hs
@@ -88,12 +88,12 @@ manCompl mans s | s == "" || last s == ' ' = return []
-- better\/more idiomatic.)
getCommandOutput :: String -> IO String
getCommandOutput s = do
- (pin, pout, perr, ph) <- runInteractiveCommand s
+ -- we can ignore the process handle because we ignor SIGCHLD
+ (pin, pout, perr, _) <- runInteractiveCommand s
hClose pin
output <- hGetContents pout
E.evaluate (length output)
hClose perr
- waitForProcess ph
return output
stripExt :: String -> String
diff --git a/XMonad/Util/Loggers.hs b/XMonad/Util/Loggers.hs
index af0871c..35892fd 100644
--- a/XMonad/Util/Loggers.hs
+++ b/XMonad/Util/Loggers.hs
@@ -30,7 +30,7 @@ import XMonad.Core
import System.Time
import System.IO
-import System.Process (runInteractiveCommand, waitForProcess)
+import System.Process (runInteractiveCommand)
import System.Locale
-- $usage
@@ -82,7 +82,7 @@ battery = logCmd "/usr/bin/acpi | sed -r 's/.*?: (.*%).*/\\1/; s/discharging, ([
-- | Create a 'Logger' from an arbitrary shell command.
logCmd :: String -> Logger
-logCmd c = io $ do (_, out, _, proc) <- runInteractiveCommand c
+logCmd c = io $ do (_, out, _, _) <- runInteractiveCommand c
output <- hGetLine out
- waitForProcess proc
+ -- no need to waitForProcess, we ignore SIGCHLD
return $ Just output
diff --git a/XMonad/Util/Run.hs b/XMonad/Util/Run.hs
index 8e92ff4..dfc90b9 100644
--- a/XMonad/Util/Run.hs
+++ b/XMonad/Util/Run.hs
@@ -31,7 +31,7 @@ module XMonad.Util.Run (
) where
import System.Posix.IO
-import System.Posix.Process (executeFile)
+import System.Posix.Process (executeFile, forkProcess)
import Control.Concurrent (threadDelay)
import Control.Exception (try)
import System.IO
@@ -54,20 +54,20 @@ import Control.Monad
-- This corresponds to dmenu's notion of exit code 1 for a cancelled invocation.
runProcessWithInput :: FilePath -> [String] -> String -> IO String
runProcessWithInput cmd args input = do
- (pin, pout, perr, ph) <- runInteractiveProcess cmd args Nothing Nothing
+ (pin, pout, perr, _) <- runInteractiveProcess cmd args Nothing Nothing
hPutStr pin input
hClose pin
output <- hGetContents pout
when (output == output) $ return ()
hClose pout
hClose perr
- waitForProcess ph
+ -- no need to waitForProcess, we ignore SIGCHLD
return output
-- | Wait is in µs (microseconds)
runProcessWithInputAndWait :: FilePath -> [String] -> String -> Int -> IO ()
runProcessWithInputAndWait cmd args input timeout = do
- doubleFork $ do
+ forkProcess $ do
(pin, pout, perr, ph) <- runInteractiveProcess cmd args Nothing Nothing
hPutStr pin input
hFlush pin
@@ -77,6 +77,7 @@ runProcessWithInputAndWait cmd args input timeout = do
hClose perr
waitForProcess ph
return ()
+ return ()
-- | Multiplies by ONE MILLION, for functions that take microseconds.
--
@@ -106,7 +107,7 @@ it makes use of shell interpretation by relying on @$HOME@ and
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 (doubleFork $ executeFile prog True [arg] Nothing) >> return ())
+safeSpawn prog arg = liftIO (try (forkProcess $ executeFile prog True [arg] Nothing) >> return ())
unsafeSpawn :: MonadIO m => String -> m ()
unsafeSpawn = spawn
@@ -128,7 +129,7 @@ spawnPipe x = do
setFdOption wr CloseOnExec True
h <- fdToHandle wr
hSetBuffering h LineBuffering
- doubleFork $ do
+ forkProcess $ 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 8d21030..b5b6f6b 100644
--- a/XMonad/Util/Timer.hs
+++ b/XMonad/Util/Timer.hs
@@ -23,6 +23,7 @@ import XMonad
import Control.Applicative
import Control.Concurrent
import Data.Unique
+import System.Posix.Process (forkProcess)
-- $usage
-- This module can be used to setup a timer to handle deferred events.
@@ -35,7 +36,7 @@ type TimerId = Int
startTimer :: Rational -> X TimerId
startTimer s = io $ do
u <- hashUnique <$> newUnique
- doubleFork $ do
+ forkProcess $ do
d <- openDisplay ""
rw <- rootWindow d $ defaultScreen d
threadDelay (fromEnum $ s * 1000000)