Merge branch 'broadcast-destroy-window-events'

This commit is contained in:
Tomas Janousek
2021-07-31 15:25:08 +01:00
3 changed files with 13 additions and 1 deletions

View File

@@ -50,6 +50,9 @@
* Document the help command in the help message.
* `DestroyWindowEvent` is now broadcasted to layouts to let them know
window-specific resources can be discarded.
## 0.15 (September 30, 2018)
* Reimplement `sendMessage` to deal properly with windowset changes made

View File

@@ -27,6 +27,7 @@ module XMonad.Layout (
import XMonad.Core
import Graphics.X11 (Rectangle(..))
import Graphics.X11.Xlib.Extras ( Event(DestroyWindowEvent) )
import qualified XMonad.StackSet as W
import Control.Arrow ((***), second)
import Control.Monad
@@ -230,6 +231,9 @@ instance (LayoutClass l a, LayoutClass r a) => LayoutClass (Choose l r) a where
handleMessage c@(Choose d l r) m | Just ReleaseResources <- fromMessage m =
join $ liftM2 (choose c d) (handle l ReleaseResources) (handle r ReleaseResources)
handleMessage c@(Choose d l r) m | Just e@DestroyWindowEvent{} <- fromMessage m =
join $ liftM2 (choose c d) (handle l e) (handle r e)
handleMessage c@(Choose d l r) m | Just (JumpToLayout desc) <- fromMessage m = do
ml <- handleMessage l m
mr <- handleMessage r m

View File

@@ -315,10 +315,15 @@ handle (MapRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do
-- window destroyed, unmanage it
-- window gone, unmanage it
handle (DestroyWindowEvent {ev_window = w}) = whenX (isClient w) $ do
-- broadcast to layouts
handle e@(DestroyWindowEvent {ev_window = w}) = do
whenX (isClient w) $ do
unmanage w
modify (\s -> s { mapped = S.delete w (mapped s)
, waitingUnmap = M.delete w (waitingUnmap s)})
-- the window is already unmanged, but we broadcast the event to all layouts
-- to trigger garbage-collection in case they hold window-specific resources
broadcastMessage e
-- We track expected unmap events in waitingUnmap. We ignore this event unless
-- it is synthetic or we are not expecting an unmap notification from a window.