aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util
diff options
context:
space:
mode:
authorSpencer Janssen <spencerjanssen@gmail.com>2009-12-23 07:45:58 +0100
committerSpencer Janssen <spencerjanssen@gmail.com>2009-12-23 07:45:58 +0100
commitbe8064767c77a02987f9eae7392f5d479ce9d5be (patch)
tree1ffc26e00a3a3d80aefca17934f044123f1dc9a9 /XMonad/Util
parentf41f402f3584bf18885bf894345cb5d007643a4d (diff)
downloadXMonadContrib-be8064767c77a02987f9eae7392f5d479ce9d5be.tar.gz
XMonadContrib-be8064767c77a02987f9eae7392f5d479ce9d5be.tar.xz
XMonadContrib-be8064767c77a02987f9eae7392f5d479ce9d5be.zip
Update all uses of forkProcess to xfork
Ignore-this: 963a4ddf1d2f4096bbb8969b173cd0c1 darcs-hash:20091223064558-25a6b-b8cdfb14005aa9b60d9cbac7b257a6fc22b8eac4.gz
Diffstat (limited to 'XMonad/Util')
-rw-r--r--XMonad/Util/NamedActions.hs13
-rw-r--r--XMonad/Util/Run.hs8
-rw-r--r--XMonad/Util/Timer.hs3
3 files changed, 8 insertions, 16 deletions
diff --git a/XMonad/Util/NamedActions.hs b/XMonad/Util/NamedActions.hs
index 70544e4..6ae7552 100644
--- a/XMonad/Util/NamedActions.hs
+++ b/XMonad/Util/NamedActions.hs
@@ -42,15 +42,8 @@ module XMonad.Util.NamedActions (
import XMonad.Actions.Submap(submap)
-import XMonad(KeySym, KeyMask, X, Layout, Message,
- XConfig(keys, layoutHook, modMask, terminal, workspaces, XConfig),
- io, spawn, whenJust, ChangeLayout(NextLayout), IncMasterN(..),
- Resize(..), kill, refresh, screenWorkspace, sendMessage, setLayout,
- windows, withFocused, controlMask, mod1Mask, mod2Mask, mod3Mask,
- mod4Mask, mod5Mask, shiftMask, xK_1, xK_9, xK_Return, xK_Tab, xK_c,
- xK_comma, xK_e, xK_h, xK_j, xK_k, xK_l, xK_m, xK_n, xK_p,
- xK_period, xK_q, xK_r, xK_space, xK_t, xK_w, keysymToString)
-import System.Posix.Process(executeFile, forkProcess)
+import XMonad
+import System.Posix.Process(executeFile)
import Control.Arrow(Arrow((&&&), second, (***)))
import Data.Bits(Bits((.&.), complement, (.|.)))
import Data.Function((.), const, ($), flip, id)
@@ -212,7 +205,7 @@ showKm keybindings = padding $ do
-- | An action to send to 'addDescrKeys' for showing the keybindings. See also 'showKm' and 'showKmSimple'
xMessage :: [((KeyMask, KeySym), NamedAction)] -> NamedAction
xMessage x = addName "Show Keybindings" $ io $ do
- forkProcess $ executeFile "xmessage" True ["-default", "okay", unlines $ showKm x] Nothing
+ xfork $ executeFile "xmessage" True ["-default", "okay", unlines $ showKm x] Nothing
return ()
-- | Merge the supplied keys with 'defaultKeysDescr', also adding a keybinding
diff --git a/XMonad/Util/Run.hs b/XMonad/Util/Run.hs
index 1e82b55..fe1949c 100644
--- a/XMonad/Util/Run.hs
+++ b/XMonad/Util/Run.hs
@@ -32,7 +32,7 @@ module XMonad.Util.Run (
) where
import System.Posix.IO
-import System.Posix.Process (executeFile, forkProcess, createSession)
+import System.Posix.Process (executeFile, createSession)
import Control.Concurrent (threadDelay)
import Control.Exception (try) -- use OldException with base 4
import System.IO
@@ -67,7 +67,7 @@ runProcessWithInput cmd args input = io $ do
-- | Wait is in µs (microseconds)
runProcessWithInputAndWait :: MonadIO m => FilePath -> [String] -> String -> Int -> m ()
runProcessWithInputAndWait cmd args input timeout = io $ do
- forkProcess $ do
+ xfork $ do
(pin, pout, perr, _) <- runInteractiveProcess cmd args Nothing Nothing
hPutStr pin input
hFlush pin
@@ -107,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 args = liftIO (try (forkProcess $ executeFile prog True args Nothing) >> return ())
+safeSpawn prog args = liftIO (try (xfork $ executeFile prog True args Nothing) >> return ())
-- | Like 'safeSpawn', but only takes a program (and no arguments for it). eg.
--
@@ -135,7 +135,7 @@ spawnPipe x = io $ do
setFdOption wr CloseOnExec True
h <- fdToHandle wr
hSetBuffering h LineBuffering
- forkProcess $ do
+ xfork $ do
createSession
uninstallSignalHandlers
dupTo rd stdInput
diff --git a/XMonad/Util/Timer.hs b/XMonad/Util/Timer.hs
index b5b6f6b..259c1ed 100644
--- a/XMonad/Util/Timer.hs
+++ b/XMonad/Util/Timer.hs
@@ -23,7 +23,6 @@ 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.
@@ -36,7 +35,7 @@ type TimerId = Int
startTimer :: Rational -> X TimerId
startTimer s = io $ do
u <- hashUnique <$> newUnique
- forkProcess $ do
+ xfork $ do
d <- openDisplay ""
rw <- rootWindow d $ defaultScreen d
threadDelay (fromEnum $ s * 1000000)