aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad.hs
diff options
context:
space:
mode:
authorDon Stewart <dons@cse.unsw.edu.au>2007-03-12 07:26:12 +0100
committerDon Stewart <dons@cse.unsw.edu.au>2007-03-12 07:26:12 +0100
commitf2549902a0759eb7f556fe14d53295a68da4a7d6 (patch)
treebc178f82936fee78deb3f25071fe7149bd705c61 /XMonad.hs
parentab636afdf14760dea95d69445d68f8482c25e60a (diff)
downloadxmonad-f2549902a0759eb7f556fe14d53295a68da4a7d6.tar.gz
xmonad-f2549902a0759eb7f556fe14d53295a68da4a7d6.tar.xz
xmonad-f2549902a0759eb7f556fe14d53295a68da4a7d6.zip
catch exceptions in spawn, so failing to fork won't kill the wm
darcs-hash:20070312062612-9c5c1-bd010ffbd84cfe17ec71b264c390ab030b6b4a6c.gz
Diffstat (limited to '')
-rw-r--r--XMonad.hs4
1 files changed, 3 insertions, 1 deletions
diff --git a/XMonad.hs b/XMonad.hs
index 24c7899..a628fd0 100644
--- a/XMonad.hs
+++ b/XMonad.hs
@@ -26,6 +26,7 @@ import Control.Monad.State
import System.IO
import System.Process (runCommand)
import Graphics.X11.Xlib
+import Control.Exception
-- | XState, the window manager state.
-- Just the display, width, height and a window list
@@ -72,7 +73,8 @@ io = liftIO
-- | spawn. Launch an external application
spawn :: String -> X ()
-spawn x = io (runCommand x) >> return ()
+spawn x = do v <- io $ handle (return . Just) (runCommand x >> return Nothing)
+ whenJust v $ \e -> trace $ "xmonad:spawn: unable to fork "++show x++": "++show e
-- | Run a side effecting action with the current workspace. Like 'when' but
whenJust :: Maybe a -> (a -> X ()) -> X ()