mirror of
https://github.com/xmonad/xmonad.git
synced 2025-08-01 12:41:53 -07:00
clean up for style
This commit is contained in:
@@ -143,7 +143,8 @@ windows f = do
|
|||||||
|
|
||||||
-- just the tiled windows:
|
-- just the tiled windows:
|
||||||
-- now tile the windows on this workspace, modified by the gap
|
-- 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
|
mapM_ (uncurry tileWindow) rs
|
||||||
updateLayout n ml'
|
updateLayout n ml'
|
||||||
|
|
||||||
@@ -340,23 +341,21 @@ sendMessage a = do
|
|||||||
-- | Send a message to all layouts, without refreshing.
|
-- | Send a message to all layouts, without refreshing.
|
||||||
broadcastMessage :: Message a => a -> X ()
|
broadcastMessage :: Message a => a -> X ()
|
||||||
broadcastMessage a = withWindowSet $ \ws -> do
|
broadcastMessage a = withWindowSet $ \ws -> do
|
||||||
let c = W.workspace . W.current $ ws
|
let c = W.workspace . W.current $ ws
|
||||||
v = map W.workspace . W.visible $ ws
|
v = map W.workspace . W.visible $ ws
|
||||||
h = W.hidden ws
|
h = W.hidden ws
|
||||||
mapM_ (sendMessageWithNoRefresh a) (c : v ++ h)
|
mapM_ (sendMessageWithNoRefresh a) (c : v ++ h)
|
||||||
|
|
||||||
-- | Send a message to a layout, without refreshing.
|
-- | Send a message to a layout, without refreshing.
|
||||||
sendMessageWithNoRefresh :: Message a => a -> W.Workspace WorkspaceId (Layout Window) Window -> X ()
|
sendMessageWithNoRefresh :: Message a => a -> W.Workspace WorkspaceId (Layout Window) Window -> X ()
|
||||||
sendMessageWithNoRefresh a w =
|
sendMessageWithNoRefresh a w =
|
||||||
handleMessage (W.layout w) (SomeMessage a) `catchX` return Nothing >>=
|
handleMessage (W.layout w) (SomeMessage a) `catchX` return Nothing >>=
|
||||||
updateLayout (W.tag w)
|
updateLayout (W.tag w)
|
||||||
|
|
||||||
-- | Update the layout field of a workspace
|
-- | Update the layout field of a workspace
|
||||||
updateLayout :: WorkspaceId -> Maybe (Layout Window) -> X ()
|
updateLayout :: WorkspaceId -> Maybe (Layout Window) -> X ()
|
||||||
updateLayout i ml = whenJust ml $ \l ->
|
updateLayout i ml = whenJust ml $ \l ->
|
||||||
runOnWorkspaces $ \ww -> if W.tag ww == i
|
runOnWorkspaces $ \ww -> return $ if W.tag ww == i then ww { W.layout = l} else ww
|
||||||
then return $ ww { W.layout = l}
|
|
||||||
else return ww
|
|
||||||
|
|
||||||
-- | Set the layout of the currently viewed workspace
|
-- | Set the layout of the currently viewed workspace
|
||||||
setLayout :: Layout Window -> X ()
|
setLayout :: Layout Window -> X ()
|
||||||
@@ -399,6 +398,8 @@ initColor dpy c = C.handle (\_ -> return Nothing) $
|
|||||||
(Just . color_pixel . fst) <$> allocNamedColor dpy colormap c
|
(Just . color_pixel . fst) <$> allocNamedColor dpy colormap c
|
||||||
where colormap = defaultColormap dpy (defaultScreen dpy)
|
where colormap = defaultColormap dpy (defaultScreen dpy)
|
||||||
|
|
||||||
|
------------------------------------------------------------------------
|
||||||
|
|
||||||
-- | @restart name resume@. Attempt to restart xmonad by executing the program
|
-- | @restart name resume@. Attempt to restart xmonad by executing the program
|
||||||
-- @name@. If @resume@ is 'True', restart with the current window state.
|
-- @name@. If @resume@ is 'True', restart with the current window state.
|
||||||
-- When executing another window manager, @resume@ should be 'False'.
|
-- When executing another window manager, @resume@ should be 'False'.
|
||||||
|
Reference in New Issue
Block a user