aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2008-01-31 09:23:14 +0100
committerAndrea Rossato <andrea.rossato@unibz.it>2008-01-31 09:23:14 +0100
commit07f59a98c143519d021bfec4b05a3cc5a569529b (patch)
tree08fe1b27fb717e5526960c60f931f8efe89b7f24
parentb1eb3fcd01b0b6dd1042d58c54f0901d658efeeb (diff)
downloadXMonadContrib-07f59a98c143519d021bfec4b05a3cc5a569529b.tar.gz
XMonadContrib-07f59a98c143519d021bfec4b05a3cc5a569529b.tar.xz
XMonadContrib-07f59a98c143519d021bfec4b05a3cc5a569529b.zip
Make LayoutHints a decoration aware layout modifier
darcs-hash:20080131082314-32816-665793ea8ce408fe0bc0f3c9ee9a16fa5404c3b7.gz
-rw-r--r--XMonad/Layout/Decoration.hs5
-rw-r--r--XMonad/Layout/LayoutHints.hs9
2 files changed, 9 insertions, 5 deletions
diff --git a/XMonad/Layout/Decoration.hs b/XMonad/Layout/Decoration.hs
index f205082..24fc133 100644
--- a/XMonad/Layout/Decoration.hs
+++ b/XMonad/Layout/Decoration.hs
@@ -24,7 +24,7 @@ module XMonad.Layout.Decoration
, shrinkText, CustomShrink ( CustomShrink )
, Shrinker (..), DefaultShrinker
, module XMonad.Layout.LayoutModifier
- , fi
+ , isDecoration, fi
) where
import Data.Maybe
@@ -215,6 +215,9 @@ updateDeco sh c fs ((w,_),(dw,Just (Rectangle _ _ wh ht))) = do
paintAndWrite dw fs wh ht 1 bc borderc tc bc AlignCenter name
updateDeco _ _ _ (_,(w,Nothing)) = hideWindow w
+isDecoration :: Window -> X Bool
+isDecoration w = withDisplay (io . flip getWindowAttributes w) >>= return . wa_override_redirect
+
shrinkWhile :: (String -> [String]) -> (String -> X Bool) -> String -> X String
shrinkWhile sh p x = sw $ sh x
where sw [n] = return n
diff --git a/XMonad/Layout/LayoutHints.hs b/XMonad/Layout/LayoutHints.hs
index 252e200..f8df071 100644
--- a/XMonad/Layout/LayoutHints.hs
+++ b/XMonad/Layout/LayoutHints.hs
@@ -21,7 +21,7 @@ module XMonad.Layout.LayoutHints (
import XMonad hiding ( trace )
import XMonad.Layout.LayoutModifier
-
+import XMonad.Layout.Decoration ( isDecoration )
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
@@ -54,8 +54,9 @@ instance LayoutModifier LayoutHints Window where
xs' <- mapM (applyHint bW) xs
return (xs', Nothing)
where
- applyHint bW (w,Rectangle a b c d) =
+ applyHint bW (w,r@(Rectangle a b c d)) =
withDisplay $ \disp -> do
- sh <- io $ getWMNormalHints disp w
+ isd <- isDecoration w
+ sh <- io $ getWMNormalHints disp w
let (c',d') = adjBorders 1 bW . applySizeHints sh . adjBorders bW (-1) $ (c,d)
- return (w, Rectangle a b c' d')
+ return (w, if isd then r else Rectangle a b c' d')