summaryrefslogtreecommitdiffstats
path: root/XMonad/Core.hs
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-12-19 07:57:10 +0100
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-12-19 07:57:10 +0100
commit77c511849ea79cf39d202388482ec130acee64f7 (patch)
tree03c231877441ee6bb8b32ef6e52cc8d32dd5261c /XMonad/Core.hs
parent5c9e250c5c49aa841598cf3c50334fe2d2edf5a8 (diff)
downloadmetatile-77c511849ea79cf39d202388482ec130acee64f7.tar
metatile-77c511849ea79cf39d202388482ec130acee64f7.zip
Call 'broadcastMessage ReleaseResources' in restart
darcs-hash:20071219065710-a5988-a03100cb8be702bdb1e972911e14117ed517975a
Diffstat (limited to 'XMonad/Core.hs')
-rw-r--r--XMonad/Core.hs22
1 files changed, 20 insertions, 2 deletions
diff --git a/XMonad/Core.hs b/XMonad/Core.hs
index 9a302bd..3933022 100644
--- a/XMonad/Core.hs
+++ b/XMonad/Core.hs
@@ -25,12 +25,12 @@ module XMonad.Core (
Layout(..), readsLayout, Typeable, Message,
SomeMessage(..), fromMessage, runLayout, LayoutMessages(..),
runX, catchX, userCode, io, catchIO,
- withDisplay, withWindowSet, isRoot,
+ withDisplay, withWindowSet, isRoot, runOnWorkspaces, broadcastMessage,
getAtom, spawn, restart, getXMonadDir, recompile, trace, whenJust, whenX,
atom_WM_STATE, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, ManageHook, Query(..), runManageHook
) where
-import XMonad.StackSet
+import XMonad.StackSet hiding (modify)
import Prelude hiding ( catch )
import Control.Exception (catch, bracket, throw, Exception(ExitException))
@@ -303,6 +303,23 @@ doubleFork m = io $ do
getProcessStatus True False pid
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().
--
-- If the first parameter is 'Just name', restart will attempt to execute the
@@ -313,6 +330,7 @@ doubleFork m = io $ do
-- current window state.
restart :: Maybe String -> Bool -> X ()
restart mprog resume = do
+ broadcastMessage ReleaseResources
prog <- maybe (io getProgName) return mprog
args <- if resume then gets (("--resume":) . return . showWs . windowset) else return []
catchIO (executeFile prog True args Nothing)