mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
Call 'broadcastMessage ReleaseResources' in restart
This commit is contained in:
parent
5b42a58d06
commit
c46f3ad549
@ -207,7 +207,7 @@ keys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
|
|||||||
|
|
||||||
-- quit, or restart
|
-- quit, or restart
|
||||||
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess)) -- %! Quit xmonad
|
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess)) -- %! Quit xmonad
|
||||||
, ((modMask , xK_q ), broadcastMessage ReleaseResources >> restart (Just "xmonad") True) -- %! Restart xmonad
|
, ((modMask , xK_q ), restart (Just "xmonad") True) -- %! Restart xmonad
|
||||||
]
|
]
|
||||||
++
|
++
|
||||||
-- mod-[1..9] %! Switch to workspace N
|
-- mod-[1..9] %! Switch to workspace N
|
||||||
|
@ -25,12 +25,12 @@ module XMonad.Core (
|
|||||||
Layout(..), readsLayout, Typeable, Message,
|
Layout(..), readsLayout, Typeable, Message,
|
||||||
SomeMessage(..), fromMessage, runLayout, LayoutMessages(..),
|
SomeMessage(..), fromMessage, runLayout, LayoutMessages(..),
|
||||||
runX, catchX, userCode, io, catchIO,
|
runX, catchX, userCode, io, catchIO,
|
||||||
withDisplay, withWindowSet, isRoot,
|
withDisplay, withWindowSet, isRoot, runOnWorkspaces, broadcastMessage,
|
||||||
getAtom, spawn, restart, getXMonadDir, recompile, trace, whenJust, whenX,
|
getAtom, spawn, restart, getXMonadDir, recompile, trace, whenJust, whenX,
|
||||||
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, ManageHook, Query(..), runManageHook
|
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, ManageHook, Query(..), runManageHook
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import XMonad.StackSet
|
import XMonad.StackSet hiding (modify)
|
||||||
|
|
||||||
import Prelude hiding ( catch )
|
import Prelude hiding ( catch )
|
||||||
import Control.Exception (catch, bracket, throw, Exception(ExitException))
|
import Control.Exception (catch, bracket, throw, Exception(ExitException))
|
||||||
@ -303,6 +303,23 @@ doubleFork m = io $ do
|
|||||||
getProcessStatus True False pid
|
getProcessStatus True False pid
|
||||||
return ()
|
return ()
|
||||||
|
|
||||||
|
-- | Send a message to all visible layouts, without necessarily refreshing.
|
||||||
|
-- This is how we implement the hooks, such as UnDoLayout.
|
||||||
|
broadcastMessage :: Message a => a -> X ()
|
||||||
|
broadcastMessage a = runOnWorkspaces $ \w -> do
|
||||||
|
ml' <- handleMessage (layout w) (SomeMessage a) `catchX` return Nothing
|
||||||
|
return $ w { layout = maybe (layout w) id ml' }
|
||||||
|
|
||||||
|
-- | This is basically a map function, running a function in the X monad on
|
||||||
|
-- each workspace with the output of that function being the modified workspace.
|
||||||
|
runOnWorkspaces :: (WindowSpace -> X WindowSpace) -> X ()
|
||||||
|
runOnWorkspaces job =do
|
||||||
|
ws <- gets windowset
|
||||||
|
h <- mapM job $ hidden ws
|
||||||
|
c:v <- mapM (\s -> (\w -> s { workspace = w}) <$> job (workspace s))
|
||||||
|
$ current ws : visible ws
|
||||||
|
modify $ \s -> s { windowset = ws { current = c, visible = v, hidden = h } }
|
||||||
|
|
||||||
-- | Restart xmonad via exec().
|
-- | Restart xmonad via exec().
|
||||||
--
|
--
|
||||||
-- If the first parameter is 'Just name', restart will attempt to execute the
|
-- If the first parameter is 'Just name', restart will attempt to execute the
|
||||||
@ -313,6 +330,7 @@ doubleFork m = io $ do
|
|||||||
-- current window state.
|
-- current window state.
|
||||||
restart :: Maybe String -> Bool -> X ()
|
restart :: Maybe String -> Bool -> X ()
|
||||||
restart mprog resume = do
|
restart mprog resume = do
|
||||||
|
broadcastMessage ReleaseResources
|
||||||
prog <- maybe (io getProgName) return mprog
|
prog <- maybe (io getProgName) return mprog
|
||||||
args <- if resume then gets (("--resume":) . return . showWs . windowset) else return []
|
args <- if resume then gets (("--resume":) . return . showWs . windowset) else return []
|
||||||
catchIO (executeFile prog True args Nothing)
|
catchIO (executeFile prog True args Nothing)
|
||||||
|
@ -324,23 +324,6 @@ sendMessageToWorkspaces a l = runOnWorkspaces $ \w ->
|
|||||||
return $ w { W.layout = maybe (W.layout w) id ml' }
|
return $ w { W.layout = maybe (W.layout w) id ml' }
|
||||||
else return w
|
else return w
|
||||||
|
|
||||||
-- | Send a message to all visible layouts, without necessarily refreshing.
|
|
||||||
-- This is how we implement the hooks, such as UnDoLayout.
|
|
||||||
broadcastMessage :: Message a => a -> X ()
|
|
||||||
broadcastMessage a = runOnWorkspaces $ \w -> do
|
|
||||||
ml' <- handleMessage (W.layout w) (SomeMessage a) `catchX` return Nothing
|
|
||||||
return $ w { W.layout = maybe (W.layout w) id ml' }
|
|
||||||
|
|
||||||
-- | This is basically a map function, running a function in the X monad on
|
|
||||||
-- each workspace with the output of that function being the modified workspace.
|
|
||||||
runOnWorkspaces :: (WindowSpace -> X WindowSpace) -> X ()
|
|
||||||
runOnWorkspaces job =do
|
|
||||||
ws <- gets windowset
|
|
||||||
h <- mapM job $ W.hidden ws
|
|
||||||
c:v <- mapM (\s -> (\w -> s { W.workspace = w}) <$> job (W.workspace s))
|
|
||||||
$ W.current ws : W.visible ws
|
|
||||||
modify $ \s -> s { windowset = ws { W.current = c, W.visible = v, W.hidden = h } }
|
|
||||||
|
|
||||||
-- | Set the layout of the currently viewed workspace
|
-- | Set the layout of the currently viewed workspace
|
||||||
setLayout :: Layout Window -> X ()
|
setLayout :: Layout Window -> X ()
|
||||||
setLayout l = do
|
setLayout l = do
|
||||||
|
@ -145,8 +145,7 @@ myKeys conf@(XConfig {XMonad.modMask = modMask}) = M.fromList $
|
|||||||
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess))
|
, ((modMask .|. shiftMask, xK_q ), io (exitWith ExitSuccess))
|
||||||
|
|
||||||
-- Restart xmonad
|
-- Restart xmonad
|
||||||
, ((modMask , xK_q ),
|
, ((modMask , xK_q ), restart (Just "xmonad") True)
|
||||||
broadcastMessage ReleaseResources >> restart (Just "xmonad") True)
|
|
||||||
]
|
]
|
||||||
++
|
++
|
||||||
|
|
||||||
|
Loading…
x
Reference in New Issue
Block a user