summaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorDon Stewart <dons@galois.com>2008-03-22 22:41:16 +0100
committerDon Stewart <dons@galois.com>2008-03-22 22:41:16 +0100
commitc1c9896077b03a7c343f68fbeed05b37ffe26f99 (patch)
treeee46f1a0c35bf3a284e5bf431eadd9c633507950 /XMonad
parent128621bef7d80ea9bab9195eecc22bed8510c95f (diff)
downloadmetatile-c1c9896077b03a7c343f68fbeed05b37ffe26f99.tar
metatile-c1c9896077b03a7c343f68fbeed05b37ffe26f99.zip
clean up for style
darcs-hash:20080322214116-cba2c-53cbd5c7049e9dcbdc21c16fa2a4526c9c7447a4
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Operations.hs21
1 files changed, 11 insertions, 10 deletions
diff --git a/XMonad/Operations.hs b/XMonad/Operations.hs
index fed2643..56e04bb 100644
--- a/XMonad/Operations.hs
+++ b/XMonad/Operations.hs
@@ -143,7 +143,8 @@ windows f = do
-- just the tiled windows:
-- now tile the windows on this workspace, modified by the gap
- (rs, ml') <- runLayout wsp { W.stack = tiled } viewrect`catchX` runLayout wsp { W.layout = Layout Full, W.stack = tiled } viewrect
+ (rs, ml') <- runLayout wsp { W.stack = tiled } viewrect `catchX`
+ runLayout wsp { W.stack = tiled, W.layout = Layout Full } viewrect
mapM_ (uncurry tileWindow) rs
updateLayout n ml'
@@ -340,23 +341,21 @@ sendMessage a = do
-- | Send a message to all layouts, without refreshing.
broadcastMessage :: Message a => a -> X ()
broadcastMessage a = withWindowSet $ \ws -> do
- let c = W.workspace . W.current $ ws
- v = map W.workspace . W.visible $ ws
- h = W.hidden ws
- mapM_ (sendMessageWithNoRefresh a) (c : v ++ h)
+ let c = W.workspace . W.current $ ws
+ v = map W.workspace . W.visible $ ws
+ h = W.hidden ws
+ mapM_ (sendMessageWithNoRefresh a) (c : v ++ h)
-- | Send a message to a layout, without refreshing.
sendMessageWithNoRefresh :: Message a => a -> W.Workspace WorkspaceId (Layout Window) Window -> X ()
sendMessageWithNoRefresh a w =
- handleMessage (W.layout w) (SomeMessage a) `catchX` return Nothing >>=
- updateLayout (W.tag w)
+ handleMessage (W.layout w) (SomeMessage a) `catchX` return Nothing >>=
+ updateLayout (W.tag w)
-- | Update the layout field of a workspace
updateLayout :: WorkspaceId -> Maybe (Layout Window) -> X ()
updateLayout i ml = whenJust ml $ \l ->
- runOnWorkspaces $ \ww -> if W.tag ww == i
- then return $ ww { W.layout = l}
- else return ww
+ runOnWorkspaces $ \ww -> return $ if W.tag ww == i then ww { W.layout = l} else ww
-- | Set the layout of the currently viewed workspace
setLayout :: Layout Window -> X ()
@@ -399,6 +398,8 @@ initColor dpy c = C.handle (\_ -> return Nothing) $
(Just . color_pixel . fst) <$> allocNamedColor dpy colormap c
where colormap = defaultColormap dpy (defaultScreen dpy)
+------------------------------------------------------------------------
+
-- | @restart name resume@. Attempt to restart xmonad by executing the program
-- @name@. If @resume@ is 'True', restart with the current window state.
-- When executing another window manager, @resume@ should be 'False'.