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.
This commit is contained in:
Andrea Rossato 2008-02-18 10:57:26 +00:00
parent cb3f424823
commit 651acdbc3e
3 changed files with 69 additions and 34 deletions

View File

@ -24,6 +24,7 @@ module XMonad.Actions.MouseResize
) where ) where
import Control.Monad import Control.Monad
import Data.Maybe
import XMonad import XMonad
import XMonad.Layout.Decoration import XMonad.Layout.Decoration
@ -59,28 +60,35 @@ import XMonad.Util.XUtils
mouseResize :: l a -> ModifiedLayout MouseResize l a mouseResize :: l a -> ModifiedLayout MouseResize l a
mouseResize = ModifiedLayout (MR []) mouseResize = ModifiedLayout (MR [])
data MouseResize a = MR [((a,Rectangle),a)] data MouseResize a = MR [((a,Rectangle),Maybe a)]
instance Show (MouseResize a) where show _ = [] instance Show (MouseResize a) where show _ = ""
instance Read (MouseResize a) where readsPrec _ _ = [] instance Read (MouseResize a) where readsPrec _ s = [(MR [], s)]
instance LayoutModifier MouseResize Window where instance LayoutModifier MouseResize Window where
redoLayout (MR st) _ _ wrs redoLayout (MR st) _ s wrs
| [] <- st = do nst <- filterM (liftM not . isDecoration . fst) wrs >>= initState | [] <- st = initState >>= \nst -> return (wrs, Just $ MR nst)
return (wrs, Just $ MR nst) | otherwise = processState >>= \nst -> return (wrs, Just $ MR nst)
| otherwise = do nst <- filterM (liftM not . isDecoration . fst) wrs >>= processState
return (wrs, Just $ MR nst)
where where
initState ws = mapM createInputWindow ws wrs' = wrs_to_state [] . filter (isInStack s . fst) $ wrs
processState ws = deleteWindows (map snd st) >> mapM createInputWindow ws initState = mapM createInputWindow wrs'
processState = mapM (deleteInputWin . snd) st >> mapM createInputWindow wrs'
inputRectangle (Rectangle x y wh ht) = Rectangle (x + fi wh - 5) (y + fi ht - 5) 10 10
wrs_to_state rs ((w,r):xs)
| ir `isVisible` rs = ((w,r),Just ir) : wrs_to_state (r:ir:rs) xs
| otherwise = ((w,r),Nothing) : wrs_to_state (r: rs) xs
where ir = inputRectangle r
wrs_to_state _ [] = []
handleMess (MR s) m handleMess (MR s) m
| Just e <- fromMessage m :: Maybe Event = handleResize s e >> return Nothing | Just e <- fromMessage m :: Maybe Event = handleResize s e >> return Nothing
| Just Hide <- fromMessage m = releaseResources >> return (Just $ MR []) | Just Hide <- fromMessage m = releaseResources >> return (Just $ MR [])
| Just ReleaseResources <- fromMessage m = releaseResources >> return (Just $ MR []) | Just ReleaseResources <- fromMessage m = releaseResources >> return (Just $ MR [])
where releaseResources = deleteWindows (map snd s) where releaseResources = mapM_ (deleteInputWin . snd) s
handleMess _ _ = return Nothing handleMess _ _ = return Nothing
handleResize :: [((Window,Rectangle),Window)] -> Event -> X () handleResize :: [((Window,Rectangle),Maybe Window)] -> Event -> X ()
handleResize st ButtonEvent { ev_window = ew, ev_event_type = et } handleResize st ButtonEvent { ev_window = ew, ev_event_type = et }
| et == buttonPress | et == buttonPress
, Just (w,Rectangle wx wy _ _) <- getWin ew st = do , Just (w,Rectangle wx wy _ _) <- getWin ew st = do
@ -92,20 +100,25 @@ handleResize st ButtonEvent { ev_window = ew, ev_event_type = et }
sendMessage (SetGeometry rect)) (return ()) sendMessage (SetGeometry rect)) (return ())
where where
getWin w (((win,r),w'):xs) getWin w (((win,r),tw):xs)
| w == w' = Just (win,r) | Just w' <- tw
, w == w' = Just (win,r)
| otherwise = getWin w xs | otherwise = getWin w xs
getWin _ [] = Nothing getWin _ [] = Nothing
handleResize _ _ = return () handleResize _ _ = return ()
createInputWindow :: (Window,Rectangle) -> X ((Window,Rectangle),Window) createInputWindow :: ((Window,Rectangle), Maybe Rectangle) -> X ((Window,Rectangle),Maybe Window)
createInputWindow (w,r@(Rectangle x y wh ht)) = do createInputWindow ((w,r),mr) = do
d <- asks display case mr of
let rect = Rectangle (x + fi wh - 5) (y + fi ht - 5) 10 10 Just tr -> withDisplay $ \d -> do
tw <- mkInputWindow d rect tw <- mkInputWindow d tr
io $ selectInput d tw (exposureMask .|. buttonPressMask) io $ selectInput d tw (exposureMask .|. buttonPressMask)
showWindow tw showWindow tw
return ((w,r),tw) return ((w,r), Just tw)
Nothing -> return ((w,r), Nothing)
deleteInputWin :: Maybe Window -> X ()
deleteInputWin = maybe (return ()) deleteWindow
mkInputWindow :: Display -> Rectangle -> X Window mkInputWindow :: Display -> Rectangle -> X Window
mkInputWindow d (Rectangle x y w h) = do mkInputWindow d (Rectangle x y w h) = do

View File

@ -27,7 +27,8 @@ module XMonad.Layout.Decoration
, shrinkText, CustomShrink ( CustomShrink ) , shrinkText, CustomShrink ( CustomShrink )
, Shrinker (..), DefaultShrinker , Shrinker (..), DefaultShrinker
, module XMonad.Layout.LayoutModifier , module XMonad.Layout.LayoutModifier
, isDecoration, fi, lookFor , isInStack, isVisible, isInvisible, isWithin
, lookFor, lookFor', fi
) where ) where
import Control.Monad (when) import Control.Monad (when)
@ -224,6 +225,11 @@ lookFor w ((wr,(dw,dr)):dwrs) | w == dw = Just (wr,(dw,dr))
| otherwise = lookFor w dwrs | otherwise = lookFor w dwrs
lookFor _ [] = Nothing 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 :: [(OrigWin,DecoWin)] -> [Window]
getDWs = map (fst . snd) 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 paintAndWrite dw fs wh ht 1 bc borderc tc bc AlignCenter name
updateDeco _ _ _ (_,(w,Nothing)) = hideWindow w updateDeco _ _ _ (_,(w,Nothing)) = hideWindow w
isDecoration :: Window -> X Bool isInStack :: Eq a => W.Stack a -> a -> Bool
isDecoration w = withDisplay (io . flip getWindowAttributes w) >>= return . wa_override_redirect 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 :: (String -> [String]) -> (String -> X Bool) -> String -> X String
shrinkWhile sh p x = sw $ sh x shrinkWhile sh p x = sw $ sh x

View File

@ -13,15 +13,17 @@
-- Make layouts respect size hints. -- Make layouts respect size hints.
----------------------------------------------------------------------------- -----------------------------------------------------------------------------
module XMonad.Layout.LayoutHints ( module XMonad.Layout.LayoutHints
-- * usage ( -- * usage
-- $usage -- $usage
layoutHints, layoutHints
LayoutHints) where , LayoutHints
) where
import XMonad hiding ( trace ) import XMonad hiding ( trace )
import XMonad.Layout.LayoutModifier import XMonad.Layout.LayoutModifier
import XMonad.Layout.Decoration ( isDecoration ) import XMonad.Layout.Decoration ( isInStack )
-- $usage -- $usage
-- You can use this module with the following in your @~\/.xmonad\/xmonad.hs@: -- 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 instance LayoutModifier LayoutHints Window where
modifierDescription _ = "Hinted" modifierDescription _ = "Hinted"
redoLayout _ _ _ xs = do redoLayout _ _ s xs = do
bW <- asks (borderWidth . config) bW <- asks (borderWidth . config)
xs' <- mapM (applyHint bW) xs xs' <- mapM (applyHint bW) xs
return (xs', Nothing) return (xs', Nothing)
where where
applyHint bW (w,r@(Rectangle a b c d)) = applyHint bW (w,r@(Rectangle a b c d)) =
withDisplay $ \disp -> do withDisplay $ \disp -> do
isd <- isDecoration w
sh <- io $ getWMNormalHints disp w sh <- io $ getWMNormalHints disp w
let (c',d') = adjBorders 1 bW . applySizeHints sh . adjBorders bW (-1) $ (c,d) 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')