Make X.L.Minimize explicitly mark minimized windows as boring

This commit is contained in:
Jan Vornberger 2009-12-22 21:45:29 +00:00
parent d32efe75e4
commit 98fe292e9f
2 changed files with 20 additions and 13 deletions

View File

@ -181,7 +181,7 @@ bluetileManageHook = composeAll
, className =? "MPlayer" --> doFloat , className =? "MPlayer" --> doFloat
, manageDocks] , manageDocks]
bluetileLayoutHook = avoidStruts $ boringAuto $ minimize $ ( bluetileLayoutHook = avoidStruts $ minimize $ boringWindows $ (
named "Floating" floating ||| named "Floating" floating |||
named "Tiled1" tiled1 ||| named "Tiled1" tiled1 |||
named "Tiled2" tiled2 ||| named "Tiled2" tiled2 |||

View File

@ -1,4 +1,4 @@
{-# LANGUAGE MultiParamTypeClasses, DeriveDataTypeable, TypeSynonymInstances, FlexibleContexts #-} {-# LANGUAGE MultiParamTypeClasses, DeriveDataTypeable, TypeSynonymInstances, FlexibleContexts, PatternGuards #-}
---------------------------------------------------------------------------- ----------------------------------------------------------------------------
-- | -- |
-- Module : XMonad.Layout.Minimize -- Module : XMonad.Layout.Minimize
@ -54,8 +54,9 @@ import Data.List
-- "XMonad.Doc.Extending#Editing_key_bindings". -- "XMonad.Doc.Extending#Editing_key_bindings".
-- --
-- The module is designed to work together with "XMonad.Layout.BoringWindows" so -- The module is designed to work together with "XMonad.Layout.BoringWindows" so
-- that minimized windows will be skipped when switching the focus window with -- that minimized windows will be skipped over when switching the focused window with
-- the keyboard. Use the 'BW.boringAuto' function. -- the keyboard. Include 'BW.boringWindows' in your layout hook and see the
-- documentation of "XMonad.Layout.BoringWindows" on how to modify your keybindings.
-- --
-- Also see "XMonad.Hooks.RestoreMinimized" if you want to be able to restore -- Also see "XMonad.Hooks.RestoreMinimized" if you want to be able to restore
-- minimized windows from your taskbar. -- minimized windows from your taskbar.
@ -78,17 +79,23 @@ instance LayoutModifier Minimize Window where
filtStack = stack >>=W.filter (\w -> not (w `elem` minimized)) filtStack = stack >>=W.filter (\w -> not (w `elem` minimized))
runLayout (wksp {W.stack = filtStack}) rect runLayout (wksp {W.stack = filtStack}) rect
handleMess (Minimize minimized) m = case fromMessage m of handleMess (Minimize minimized) m
Just (MinimizeWin w) | Just (MinimizeWin w) <- fromMessage m =
| not (w `elem` minimized) -> do if not (w `elem` minimized)
then do
BW.focusDown BW.focusDown
return $ Just $ Minimize (w:minimized) return $ Just $ Minimize (w:minimized)
| otherwise -> return Nothing else return Nothing
Just (RestoreMinimizedWin w) -> | Just (RestoreMinimizedWin w) <- fromMessage m =
return $ Just $ Minimize (minimized \\ [w]) return $ Just $ Minimize (minimized \\ [w])
Just (RestoreNextMinimizedWin) | Just RestoreNextMinimizedWin <- fromMessage m =
| not (null minimized) -> do if not (null minimized)
then do
focus (head minimized) focus (head minimized)
return $ Just $ Minimize (tail minimized) return $ Just $ Minimize (tail minimized)
| otherwise -> return Nothing else return Nothing
_ -> return Nothing | Just BW.UpdateBoring <- fromMessage m = do
ws <- gets (W.workspace . W.current . windowset)
flip sendMessageWithNoRefresh ws $ BW.Replace "Minimize" minimized
return Nothing
| otherwise = return Nothing