aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Util/Run.hs22
1 files changed, 20 insertions, 2 deletions
diff --git a/XMonad/Util/Run.hs b/XMonad/Util/Run.hs
index 25757d5..fad92cd 100644
--- a/XMonad/Util/Run.hs
+++ b/XMonad/Util/Run.hs
@@ -24,16 +24,18 @@ module XMonad.Util.Run (
unsafeSpawn,
runInTerm,
safeRunInTerm,
- seconds
+ seconds,
+ spawnPipe
) where
import Control.Monad.Reader
+import System.Posix.IO
import System.Posix.Process (createSession, forkProcess, executeFile,
getProcessStatus)
import Control.Concurrent (threadDelay)
import Control.Exception (try)
import System.Exit (ExitCode(ExitSuccess), exitWith)
-import System.IO (IO, FilePath, hPutStr, hGetContents, hFlush, hClose)
+import System.IO
import System.Process (runInteractiveProcess, waitForProcess)
import XMonad
@@ -114,3 +116,19 @@ safeRunInTerm command = asks (terminal . config) >>= \t -> safeSpawn t ("-e " ++
unsafeRunInTerm, runInTerm :: String -> X ()
unsafeRunInTerm command = asks (terminal . config) >>= \t -> unsafeSpawn $ t ++ " -e " ++ command
runInTerm = unsafeRunInTerm
+
+-- | Launch an external application and return a 'Handle' to its standard input.
+spawnPipe :: String -> IO Handle
+spawnPipe x = do
+ (rd, wr) <- createPipe
+ 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
+ return h