From 3584d9a1e298f49c188da8e1a2a34c4cda52a58f Mon Sep 17 00:00:00 2001 From: Stefan O'Rear Date: Sat, 9 Jun 2007 20:58:35 +0200 Subject: UNDO: Give refresh sole responsibility for establishing window properties (-3 loc) darcs-hash:20070609185835-e3110-1eaa534465f66313044477acd9cae1bbbcf61950.gz --- Main.hs | 24 ++++++++++++++++-------- Operations.hs | 4 +--- 2 files changed, 17 insertions(+), 11 deletions(-) diff --git a/Main.hs b/Main.hs index ca7b9bd..aaa4970 100644 --- a/Main.hs +++ b/Main.hs @@ -28,6 +28,7 @@ import Graphics.X11.Xinerama (getScreenInfo) import XMonad import Config +import StackSet (new, floating, member) import qualified StackSet as W import Operations @@ -51,7 +52,7 @@ main = do let winset | ("--resume" : s : _) <- args , [(x, "")] <- reads s = x - | otherwise = W.new (fromIntegral workspaces) (fromIntegral $ length xinesc) + | otherwise = new (fromIntegral workspaces) (fromIntegral $ length xinesc) safeLayouts = case defaultLayouts of [] -> (full, []); (x:xs) -> (x,xs) cf = XConf @@ -79,11 +80,19 @@ main = do sync dpy False ws <- scan dpy rootw -- on the resume case, will pick up new windows - -- We mark the initial state as having all workspaces visible to - -- defeat the delta code in refresh. allocaXEvent $ \e -> - runX cf st{ windowset = allVisible winset } $ do - windows $ \_st -> winset + runX cf st $ do + + -- walk workspace, resetting X states/mask for windows + -- TODO, general iterators for these lists. + sequence_ [ setInitialProperties w >> reveal w + | wk <- map W.workspace (W.current winset : W.visible winset) + , w <- W.integrate (W.stack wk) ] + + sequence_ [ setInitialProperties w >> hide w + | wk <- W.hidden winset + , w <- W.integrate (W.stack wk) ] + mapM_ manage ws -- find new windows when logging $ withWindowSet (io . putStrLn . serial) @@ -91,7 +100,6 @@ main = do forever $ handle =<< io (nextEvent dpy e >> getEvent e) where forever a = a >> forever a - allVisible ss = ss{ W.hidden=[], W.visible = W.visible ss ++ [ W.Screen s (S 0) | s <- W.hidden ss ] } -- --------------------------------------------------------------------- -- IO stuff. Doesn't require any X state @@ -194,7 +202,7 @@ handle e@(ConfigureRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do ws <- gets windowset wa <- io $ getWindowAttributes dpy w - if M.member w (W.floating ws) || not (W.member w ws) + if M.member w (floating ws) || not (member w ws) then do io $ configureWindow dpy w (ev_value_mask e) $ WindowChanges { wc_x = ev_x e , wc_y = ev_y e @@ -203,7 +211,7 @@ handle e@(ConfigureRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do , wc_border_width = fromIntegral borderWidth , wc_sibling = ev_above e , wc_stack_mode = ev_detail e } - when (W.member w ws) (float w) + when (member w ws) (float w) else io $ allocaXEvent $ \ev -> do setEventType ev configureNotify setConfigureEvent ev w w diff --git a/Operations.hs b/Operations.hs index 2c290f3..0716533 100644 --- a/Operations.hs +++ b/Operations.hs @@ -45,7 +45,7 @@ import Graphics.X11.Xlib.Extras -- manage :: Window -> X () manage w = withDisplay $ \d -> do - setInitialProperties w -- we need this so that the modify below will not capture the wrong border size... + setInitialProperties w >> reveal w -- FIXME: This is pretty awkward. We can't can't let "refresh" happen -- before the call to float, because that will resize the window and @@ -201,7 +201,6 @@ setWMState w v = withDisplay $ \dpy -> do -- | hide. Hide a window by unmapping it, and setting Iconified. hide :: Window -> X () hide w = whenX (gets (S.member w . mapped)) $ withDisplay $ \d -> do - setInitialProperties w io $ do selectInput d w (clientMask .&. complement structureNotifyMask) unmapWindow d w selectInput d w clientMask @@ -215,7 +214,6 @@ hide w = whenX (gets (S.member w . mapped)) $ withDisplay $ \d -> do -- this is harmless if the window was already visible reveal :: Window -> X () reveal w = withDisplay $ \d -> do - setInitialProperties w setWMState w 1 --normal io $ mapWindow d w modify (\s -> s { mapped = S.insert w (mapped s) }) -- cgit v1.2.3