Experimental support for a beefier restart.

This commit is contained in:
Spencer Janssen
2007-05-21 19:46:53 +00:00
parent 270d80297f
commit a9d7b7ef49
3 changed files with 24 additions and 10 deletions

View File

@@ -169,7 +169,7 @@ keys = M.fromList $
, ((modMask .|. shiftMask, xK_c ), kill)
, ((modMask .|. shiftMask, xK_q ), io $ exitWith ExitSuccess)
, ((modMask .|. shiftMask .|. controlMask, xK_q ), restart)
, ((modMask .|. shiftMask .|. controlMask, xK_q ), restart Nothing False)
-- Cycle the current tiling order
, ((modMask, xK_Return), swap)

10
Main.hs
View File

@@ -17,6 +17,8 @@ import Data.Bits
import qualified Data.Map as M
import Control.Monad.Reader
import System.Environment (getArgs)
import Graphics.X11.Xlib hiding (refreshKeyboardMapping)
import Graphics.X11.Xlib.Extras
import Graphics.X11.Xinerama (getScreenInfo)
@@ -41,8 +43,12 @@ main = do
xinesc <- getScreenInfo dpy
nbc <- initcolor normalBorderColor
fbc <- initcolor focusedBorderColor
args <- getArgs
let safeLayouts = case defaultLayouts of [] -> (full, []); (x:xs) -> (x, xs)
let winset | ("--resume" : s : _) <- args
, [(x, "")] <- reads s = x
| otherwise = new (fromIntegral workspaces) (fromIntegral $ length xinesc)
safeLayouts = case defaultLayouts of [] -> (full, []); (x:xs) -> (x, xs)
cf = XConf
{ display = dpy
, theRoot = rootw
@@ -53,7 +59,7 @@ main = do
, focusedBorder = fbc
}
st = XState
{ windowset = new (fromIntegral workspaces) (fromIntegral $ length xinesc)
{ windowset = winset
, layouts = M.fromList [(w, safeLayouts) | w <- [0 .. W workspaces - 1]]
, xineScreens = xinesc
, dimensions = (fromIntegral (displayWidth dpy dflt),

View File

@@ -140,13 +140,21 @@ spawn x = io $ do
getProcessStatus True False pid
return ()
-- | Restart xmonad by exec()'ing self. This doesn't save state and xmonad has
-- to be in PATH for this to work.
restart :: X ()
restart = io $ do
prog <- getProgName
args <- getArgs
catch (executeFile prog True args Nothing) (const $ return ())
-- | Restart xmonad via exec().
--
-- If the first parameter is 'Just name', restart will attempt to execute the
-- program corresponding to 'name'. Otherwise, xmonad will attempt to execute
-- the name of the current program.
--
-- When the second parameter is 'True', xmonad will attempt to resume with the
-- current window state.
restart :: Maybe String -> Bool -> X ()
restart mprog resume = do
prog <- maybe (io $ getProgName) return mprog
args <- io $ getArgs
args' <- if resume then gets (("--resume":) . return . show . windowset) else return []
io $ catch (executeFile prog True (args ++ args') Nothing)
(const $ return ()) -- ignore executable not found exception
-- | Run a side effecting action with the current workspace. Like 'when' but
whenJust :: Maybe a -> (a -> X ()) -> X ()