aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/MouseResize.hs
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/Actions/MouseResize.hs
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 '')
-rw-r--r--XMonad/Actions/MouseResize.hs57
1 files changed, 35 insertions, 22 deletions
diff --git a/XMonad/Actions/MouseResize.hs b/XMonad/Actions/MouseResize.hs
index 063ac0b..a0efb0d 100644
--- a/XMonad/Actions/MouseResize.hs
+++ b/XMonad/Actions/MouseResize.hs
@@ -24,6 +24,7 @@ module XMonad.Actions.MouseResize
) where
import Control.Monad
+import Data.Maybe
import XMonad
import XMonad.Layout.Decoration
@@ -59,28 +60,35 @@ import XMonad.Util.XUtils
mouseResize :: l a -> ModifiedLayout MouseResize l a
mouseResize = ModifiedLayout (MR [])
-data MouseResize a = MR [((a,Rectangle),a)]
-instance Show (MouseResize a) where show _ = []
-instance Read (MouseResize a) where readsPrec _ _ = []
+data MouseResize a = MR [((a,Rectangle),Maybe a)]
+instance Show (MouseResize a) where show _ = ""
+instance Read (MouseResize a) where readsPrec _ s = [(MR [], s)]
instance LayoutModifier MouseResize Window where
- redoLayout (MR st) _ _ wrs
- | [] <- st = do nst <- filterM (liftM not . isDecoration . fst) wrs >>= initState
- return (wrs, Just $ MR nst)
- | otherwise = do nst <- filterM (liftM not . isDecoration . fst) wrs >>= processState
- return (wrs, Just $ MR nst)
+ redoLayout (MR st) _ s wrs
+ | [] <- st = initState >>= \nst -> return (wrs, Just $ MR nst)
+ | otherwise = processState >>= \nst -> return (wrs, Just $ MR nst)
where
- initState ws = mapM createInputWindow ws
- processState ws = deleteWindows (map snd st) >> mapM createInputWindow ws
+ wrs' = wrs_to_state [] . filter (isInStack s . fst) $ wrs
+ 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
| Just e <- fromMessage m :: Maybe Event = handleResize s e >> return Nothing
| Just Hide <- 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
-handleResize :: [((Window,Rectangle),Window)] -> Event -> X ()
+handleResize :: [((Window,Rectangle),Maybe Window)] -> Event -> X ()
handleResize st ButtonEvent { ev_window = ew, ev_event_type = et }
| et == buttonPress
, 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 ())
where
- getWin w (((win,r),w'):xs)
- | w == w' = Just (win,r)
+ getWin w (((win,r),tw):xs)
+ | Just w' <- tw
+ , w == w' = Just (win,r)
| otherwise = getWin w xs
getWin _ [] = Nothing
handleResize _ _ = return ()
-createInputWindow :: (Window,Rectangle) -> X ((Window,Rectangle),Window)
-createInputWindow (w,r@(Rectangle x y wh ht)) = do
- d <- asks display
- let rect = Rectangle (x + fi wh - 5) (y + fi ht - 5) 10 10
- tw <- mkInputWindow d rect
- io $ selectInput d tw (exposureMask .|. buttonPressMask)
- showWindow tw
- return ((w,r),tw)
+createInputWindow :: ((Window,Rectangle), Maybe Rectangle) -> X ((Window,Rectangle),Maybe Window)
+createInputWindow ((w,r),mr) = do
+ case mr of
+ Just tr -> withDisplay $ \d -> do
+ tw <- mkInputWindow d tr
+ io $ selectInput d tw (exposureMask .|. buttonPressMask)
+ showWindow 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 d (Rectangle x y w h) = do