aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout
diff options
context:
space:
mode:
authorJan Vornberger <jan.vornberger@informatik.uni-oldenburg.de>2009-12-22 22:45:29 +0100
committerJan Vornberger <jan.vornberger@informatik.uni-oldenburg.de>2009-12-22 22:45:29 +0100
commitf41f402f3584bf18885bf894345cb5d007643a4d (patch)
treec7a49a4a9984884c4deb0af6f9306c84826ab8d2 /XMonad/Layout
parent462195411860b5ae85587529280aadde89a31cdf (diff)
downloadXMonadContrib-f41f402f3584bf18885bf894345cb5d007643a4d.tar.gz
XMonadContrib-f41f402f3584bf18885bf894345cb5d007643a4d.tar.xz
XMonadContrib-f41f402f3584bf18885bf894345cb5d007643a4d.zip
Make X.L.Minimize explicitly mark minimized windows as boring
Ignore-this: b1e8adf26ac87dede6c1b7a7d687411c darcs-hash:20091222214529-594c5-974afa4b25c95d2499b7bb8313301cad7fe335f2.gz
Diffstat (limited to 'XMonad/Layout')
-rw-r--r--XMonad/Layout/Minimize.hs31
1 files changed, 19 insertions, 12 deletions
diff --git a/XMonad/Layout/Minimize.hs b/XMonad/Layout/Minimize.hs
index f8aa4c8..07020c8 100644
--- a/XMonad/Layout/Minimize.hs
+++ b/XMonad/Layout/Minimize.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE MultiParamTypeClasses, DeriveDataTypeable, TypeSynonymInstances, FlexibleContexts #-}
+{-# LANGUAGE MultiParamTypeClasses, DeriveDataTypeable, TypeSynonymInstances, FlexibleContexts, PatternGuards #-}
----------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.Minimize
@@ -54,8 +54,9 @@ import Data.List
-- "XMonad.Doc.Extending#Editing_key_bindings".
--
-- The module is designed to work together with "XMonad.Layout.BoringWindows" so
--- that minimized windows will be skipped when switching the focus window with
--- the keyboard. Use the 'BW.boringAuto' function.
+-- that minimized windows will be skipped over when switching the focused window with
+-- 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
-- minimized windows from your taskbar.
@@ -78,17 +79,23 @@ instance LayoutModifier Minimize Window where
filtStack = stack >>=W.filter (\w -> not (w `elem` minimized))
runLayout (wksp {W.stack = filtStack}) rect
- handleMess (Minimize minimized) m = case fromMessage m of
- Just (MinimizeWin w)
- | not (w `elem` minimized) -> do
+ handleMess (Minimize minimized) m
+ | Just (MinimizeWin w) <- fromMessage m =
+ if not (w `elem` minimized)
+ then do
BW.focusDown
return $ Just $ Minimize (w:minimized)
- | otherwise -> return Nothing
- Just (RestoreMinimizedWin w) ->
+ else return Nothing
+ | Just (RestoreMinimizedWin w) <- fromMessage m =
return $ Just $ Minimize (minimized \\ [w])
- Just (RestoreNextMinimizedWin)
- | not (null minimized) -> do
+ | Just RestoreNextMinimizedWin <- fromMessage m =
+ if not (null minimized)
+ then do
focus (head minimized)
return $ Just $ Minimize (tail minimized)
- | otherwise -> return Nothing
- _ -> return Nothing
+ else 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