aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2008-02-18 11:57:26 +0100
committerAndrea Rossato <andrea.rossato@unibz.it>2008-02-18 11:57:26 +0100
commit8c595555ce9d1f1d2bfce4bf0ff441d75b79b1c0 (patch)
tree3df832d0e8a699f319280457884a12bdf7c9e844 /XMonad/Layout
parente891577f25c620a9726c2e7aa346391e36d8e82d (diff)
downloadXMonadContrib-8c595555ce9d1f1d2bfce4bf0ff441d75b79b1c0.tar.gz
XMonadContrib-8c595555ce9d1f1d2bfce4bf0ff441d75b79b1c0.tar.xz
XMonadContrib-8c595555ce9d1f1d2bfce4bf0ff441d75b79b1c0.zip
Refactor MouseResize, remove isDecoration and introduce isInStack, isVisible, isInvisible
This patch includes several changes, which are strictly related and cannot be recorded separately: - remove Decoraion.isDecoartion and introduce Decoration.isInStack (with the related change to LayoutHints) - in Decoration introduce useful utilities: isVisible, isInvisible, isWithin and lookFor' - MouseResize: - invisible inputOnly windows will not be created; - fix a bug in the read instance which caused a failure in the state deserialization. darcs-hash:20080218105726-32816-9d42d4fdff75fad3258aec92d059e5155f0e64bc.gz
Diffstat (limited to 'XMonad/Layout')
-rw-r--r--XMonad/Layout/Decoration.hs27
-rw-r--r--XMonad/Layout/LayoutHints.hs19
2 files changed, 34 insertions, 12 deletions
diff --git a/XMonad/Layout/Decoration.hs b/XMonad/Layout/Decoration.hs
index c5b78ae..e18a6d1 100644
--- a/XMonad/Layout/Decoration.hs
+++ b/XMonad/Layout/Decoration.hs
@@ -27,7 +27,8 @@ module XMonad.Layout.Decoration
, shrinkText, CustomShrink ( CustomShrink )
, Shrinker (..), DefaultShrinker
, module XMonad.Layout.LayoutModifier
- , isDecoration, fi, lookFor
+ , isInStack, isVisible, isInvisible, isWithin
+ , lookFor, lookFor', fi
) where
import Control.Monad (when)
@@ -224,6 +225,11 @@ lookFor w ((wr,(dw,dr)):dwrs) | w == dw = Just (wr,(dw,dr))
| otherwise = lookFor w dwrs
lookFor _ [] = Nothing
+lookFor' :: Window -> [(OrigWin,DecoWin)] -> Maybe (OrigWin,DecoWin)
+lookFor' w (((w',r),dwr):dwrs) | w == w' = Just ((w,r),dwr)
+ | otherwise = lookFor' w dwrs
+lookFor' _ [] = Nothing
+
getDWs :: [(OrigWin,DecoWin)] -> [Window]
getDWs = map (fst . snd)
@@ -271,8 +277,23 @@ updateDeco sh t 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
+isInStack :: Eq a => W.Stack a -> a -> Bool
+isInStack s = flip elem (W.integrate s)
+
+isVisible :: Rectangle -> [Rectangle] -> Bool
+isVisible r = and . foldr f []
+ where f x xs = if r `isWithin` x then False : xs else True : xs
+
+isInvisible :: Rectangle -> [Rectangle] -> Bool
+isInvisible r = not . isVisible r
+
+isWithin :: Rectangle -> Rectangle -> Bool
+isWithin (Rectangle x y w h) (Rectangle rx ry rw rh)
+ | x >= rx, x <= rx + fi rw
+ , y >= ry, y <= ry + fi rh
+ , x + fi w <= rx + fi rw
+ , y + fi h <= ry + fi rh = True
+ | otherwise = False
shrinkWhile :: (String -> [String]) -> (String -> X Bool) -> String -> X String
shrinkWhile sh p x = sw $ sh x
diff --git a/XMonad/Layout/LayoutHints.hs b/XMonad/Layout/LayoutHints.hs
index f8df071..6442934 100644
--- a/XMonad/Layout/LayoutHints.hs
+++ b/XMonad/Layout/LayoutHints.hs
@@ -13,15 +13,17 @@
-- Make layouts respect size hints.
-----------------------------------------------------------------------------
-module XMonad.Layout.LayoutHints (
- -- * usage
- -- $usage
- layoutHints,
- LayoutHints) where
+module XMonad.Layout.LayoutHints
+ ( -- * usage
+ -- $usage
+ layoutHints
+ , LayoutHints
+ ) where
import XMonad hiding ( trace )
import XMonad.Layout.LayoutModifier
-import XMonad.Layout.Decoration ( isDecoration )
+import XMonad.Layout.Decoration ( isInStack )
+
-- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@:
--
@@ -49,14 +51,13 @@ data LayoutHints a = LayoutHints deriving (Read, Show)
instance LayoutModifier LayoutHints Window where
modifierDescription _ = "Hinted"
- redoLayout _ _ _ xs = do
+ redoLayout _ _ s xs = do
bW <- asks (borderWidth . config)
xs' <- mapM (applyHint bW) xs
return (xs', Nothing)
where
applyHint bW (w,r@(Rectangle a b c d)) =
withDisplay $ \disp -> do
- isd <- isDecoration w
sh <- io $ getWMNormalHints disp w
let (c',d') = adjBorders 1 bW . applySizeHints sh . adjBorders bW (-1) $ (c,d)
- return (w, if isd then r else Rectangle a b c' d')
+ return (w, if isInStack s w then r else Rectangle a b c' d')