aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Util')
-rw-r--r--XMonad/Util/Dmenu.hs4
-rw-r--r--XMonad/Util/Dzen.hs2
-rw-r--r--XMonad/Util/Run.hs12
3 files changed, 9 insertions, 9 deletions
diff --git a/XMonad/Util/Dmenu.hs b/XMonad/Util/Dmenu.hs
index fffba07..162e644 100644
--- a/XMonad/Util/Dmenu.hs
+++ b/XMonad/Util/Dmenu.hs
@@ -37,13 +37,13 @@ import XMonad.Util.Run
dmenuXinerama :: [String] -> X String
dmenuXinerama opts = do
curscreen <- (fromIntegral . W.screen . W.current) `fmap` gets windowset :: X Int
- io $ runProcessWithInput "dmenu" ["-xs", show (curscreen+1)] (unlines opts)
+ runProcessWithInput "dmenu" ["-xs", show (curscreen+1)] (unlines opts)
dmenu :: [String] -> X String
dmenu opts = menu "dmenu" opts
menu :: String -> [String] -> X String
-menu menuCmd opts = io $ runProcessWithInput menuCmd [] (unlines opts)
+menu menuCmd opts = runProcessWithInput menuCmd [] (unlines opts)
menuMap :: String -> M.Map String a -> X (Maybe a)
menuMap menuCmd selectionMap = do
diff --git a/XMonad/Util/Dzen.hs b/XMonad/Util/Dzen.hs
index 617e785..793d205 100644
--- a/XMonad/Util/Dzen.hs
+++ b/XMonad/Util/Dzen.hs
@@ -34,7 +34,7 @@ dzen str timeout = dzenWithArgs str [] timeout
--
-- > dzenWithArgs "Hi, dons!" ["-ta", "r"] (5 `seconds`)
dzenWithArgs :: String -> [String] -> Int -> X ()
-dzenWithArgs str args timeout = io $ runProcessWithInputAndWait "dzen2" args (unchomp str) timeout
+dzenWithArgs str args timeout = runProcessWithInputAndWait "dzen2" args (unchomp str) timeout
-- dzen seems to require the input to terminate with exactly one newline.
where unchomp s@['\n'] = s
unchomp [] = ['\n']
diff --git a/XMonad/Util/Run.hs b/XMonad/Util/Run.hs
index 2966053..1e82b55 100644
--- a/XMonad/Util/Run.hs
+++ b/XMonad/Util/Run.hs
@@ -52,8 +52,8 @@ import Control.Monad
-- "XMonad.Util.Dzen"
-- | Returns the output.
-runProcessWithInput :: FilePath -> [String] -> String -> IO String
-runProcessWithInput cmd args input = do
+runProcessWithInput :: MonadIO m => FilePath -> [String] -> String -> m String
+runProcessWithInput cmd args input = io $ do
(pin, pout, perr, _) <- runInteractiveProcess cmd args Nothing Nothing
hPutStr pin input
hClose pin
@@ -65,8 +65,8 @@ runProcessWithInput cmd args input = do
return output
-- | Wait is in µs (microseconds)
-runProcessWithInputAndWait :: FilePath -> [String] -> String -> Int -> IO ()
-runProcessWithInputAndWait cmd args input timeout = do
+runProcessWithInputAndWait :: MonadIO m => FilePath -> [String] -> String -> Int -> m ()
+runProcessWithInputAndWait cmd args input timeout = io $ do
forkProcess $ do
(pin, pout, perr, _) <- runInteractiveProcess cmd args Nothing Nothing
hPutStr pin input
@@ -129,8 +129,8 @@ safeRunInTerm :: String -> String -> X ()
safeRunInTerm options command = asks (terminal . config) >>= \t -> safeSpawn t [options, " -e " ++ command]
-- | Launch an external application through the system shell and return a @Handle@ to its standard input.
-spawnPipe :: String -> IO Handle
-spawnPipe x = do
+spawnPipe :: MonadIO m => String -> m Handle
+spawnPipe x = io $ do
(rd, wr) <- createPipe
setFdOption wr CloseOnExec True
h <- fdToHandle wr