aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util
diff options
context:
space:
mode:
authorgwern0 <gwern0@gmail.com>2011-04-11 18:37:40 +0200
committergwern0 <gwern0@gmail.com>2011-04-11 18:37:40 +0200
commit21547435014507058b0f1c921431b608a897193d (patch)
treeaddb6ee0d161ca48ed89c14ad7a6c91dbb863d51 /XMonad/Util
parent0b0d55ac9ba9090d705cd1dc31c9f703dc47873c (diff)
downloadXMonadContrib-21547435014507058b0f1c921431b608a897193d.tar.gz
XMonadContrib-21547435014507058b0f1c921431b608a897193d.tar.xz
XMonadContrib-21547435014507058b0f1c921431b608a897193d.zip
XMonad.Util.Run: resolve issue #441
Ignore-this: 9e3da81df65f6750c822a5044952f1a1 See <http://code.google.com/p/xmonad/issues/detail?idD1> > I have run into programs that fail when run by safeSpawn but succeed with spawn. > I tracked it down in one (python) and it seems to be due to uninstallSignalHandlers. > When run by safeSpawn, the program reports errors from wait. dylan did not supply a patch and his version doesn't match the declared type signature; since I don't want to break every `safeSpawn` user, I tossed a `>> return ()` in to make the type right, although I'm troubled at removing the exception functions. darcs-hash:20110411163740-f7719-bf0d46f94d103cc328629ad32f8e650fec609cdc.gz
Diffstat (limited to 'XMonad/Util')
-rw-r--r--XMonad/Util/Run.hs22
1 files changed, 11 insertions, 11 deletions
diff --git a/XMonad/Util/Run.hs b/XMonad/Util/Run.hs
index 77c3b0c..30696f5 100644
--- a/XMonad/Util/Run.hs
+++ b/XMonad/Util/Run.hs
@@ -32,10 +32,8 @@ module XMonad.Util.Run (
) where
import System.Posix.IO
-import System.Posix.Process (executeFile)
-import System.Posix.Types (ProcessID)
+import System.Posix.Process (createSession, executeFile, forkProcess)
import Control.Concurrent (threadDelay)
-import Control.Exception.Extensible (try,SomeException)
import System.IO
import System.Process (runInteractiveProcess)
import XMonad
@@ -68,7 +66,7 @@ runProcessWithInput cmd args input = io $ do
-- | Wait is in &#956; (microseconds)
runProcessWithInputAndWait :: MonadIO m => FilePath -> [String] -> String -> Int -> m ()
runProcessWithInputAndWait cmd args input timeout = io $ do
- xfork $ do
+ _ <- xfork $ do
(pin, pout, perr, _) <- runInteractiveProcess cmd args Nothing Nothing
hPutStr pin input
hFlush pin
@@ -107,9 +105,11 @@ 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 args = liftIO $ do
- try $ xfork $ executeFile prog True args Nothing :: IO (Either SomeException ProcessID)
- return ()
+safeSpawn prog args = io $ void $ forkProcess $ do
+ uninstallSignalHandlers
+ _ <- createSession
+ executeFile prog True args Nothing
+ where void = (>> return ()) -- TODO: replace with Control.Monad.void
-- | Simplified 'safeSpawn'; only takes a program (and no arguments):
--
@@ -117,7 +117,7 @@ safeSpawn prog args = liftIO $ do
safeSpawnProg :: MonadIO m => FilePath -> m ()
safeSpawnProg = flip safeSpawn []
--- | An alias for 'spawn'; the name emphasizes that one is calling out to a
+-- | An alias for 'spawn'; the name emphasizes that one is calling out to a
-- Turing-complete interpreter which may do things one dislikes; for details, see 'safeSpawn'.
unsafeSpawn :: MonadIO m => String -> m ()
unsafeSpawn = spawn
@@ -139,8 +139,8 @@ spawnPipe x = io $ do
setFdOption wr CloseOnExec True
h <- fdToHandle wr
hSetBuffering h LineBuffering
- xfork $ do
- dupTo rd stdInput
- executeFile "/bin/sh" False ["-c", x] Nothing
+ _ <- xfork $ do
+ _ <- dupTo rd stdInput
+ executeFile "/bin/sh" False ["-c", x] Nothing
closeFd rd
return h