summaryrefslogtreecommitdiffstats
path: root/XMonad/Main.hsc
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Main.hsc')
-rw-r--r--XMonad/Main.hsc36
1 files changed, 33 insertions, 3 deletions
diff --git a/XMonad/Main.hsc b/XMonad/Main.hsc
index 19f988f..b5a2bf2 100644
--- a/XMonad/Main.hsc
+++ b/XMonad/Main.hsc
@@ -32,6 +32,7 @@ import System.Environment (getArgs)
import Graphics.X11.Xlib hiding (refreshKeyboardMapping)
import Graphics.X11.Xlib.Extras
+import Graphics.X11.Xlib.Types (Visual(..))
import XMonad.Core
import qualified XMonad.Config as Default
@@ -197,12 +198,16 @@ handle (MapRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do
wa <- io $ getWindowAttributes dpy w -- ignore override windows
-- need to ignore mapping requests by managed windows not on the current workspace
managed <- isClient w
- when (not (wa_override_redirect wa) && not managed) $ do manage w
+ when (not (wa_override_redirect wa) && not managed) $ do
+ reparent w
+ manage w
-- window destroyed, unmanage it
-- window gone, unmanage it
-handle (DestroyWindowEvent {ev_window = w}) = whenX (isClient w) $ do
- unmanage w
+handle (DestroyWindowEvent {ev_window = w}) = do
+ whenX (isClient w) $
+ unmanage w
+ unparent w
modify (\s -> s { windowState = M.delete w (windowState s)})
-- We track expected unmap events in waitingUnmap. We ignore this event unless
@@ -304,6 +309,31 @@ handle e@ClientMessageEvent { ev_message_type = mt } = do
handle e = broadcastMessage e -- trace (eventName e) -- ignoring
+reparent :: Window -> X ()
+reparent w = withDisplay $ \dpy -> do
+ rootw <- asks theRoot
+ p <- asks normalBorder
+ noFrame <- getsWindowState ((==0) . wsFrame) w
+ when noFrame $ do
+ trace $ "reparent: " ++ show w
+ frame <- io $ allocaSetWindowAttributes $ \swa -> do
+ set_background_pixel swa p
+ set_border_pixel swa p
+ set_override_redirect swa True
+ createWindow dpy rootw (-1) (-1) 1 1 0 copyFromParent inputOutput (Visual nullPtr) (cWBackPixel.|.cWBorderPixel.|.cWOverrideRedirect) swa
+ io $ do
+ mapWindow dpy frame
+ reparentWindow dpy w frame 0 0
+ modifyWindowState (\ws -> ws { wsFrame = frame }) w
+
+unparent :: Window -> X ()
+unparent w = withDisplay $ \dpy -> do
+ trace $ "unparent: " ++ show w
+ frame <- getsWindowState wsFrame w
+ when (frame /= 0) $ do
+ io $ destroyWindow dpy frame
+ modifyWindowState (\ws -> ws { wsFrame = 0 }) w
+
-- ---------------------------------------------------------------------
-- IO stuff. Doesn't require any X state
-- Most of these things run only on startup (bar grabkeys)