mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
Broadcast DestroyWindowEvent
to layouts
Some layout and layout modifiers that keep track of some window properties don't do garbage collection and update their state when windows are destroyed. By broadcasting this event, it should be easier for layouts to clean up Related: https://github.com/xmonad/xmonad-contrib/pull/474
This commit is contained in:
parent
101c7052f4
commit
92d01e37a0
@ -50,6 +50,9 @@
|
|||||||
|
|
||||||
* Document the help command in the help message.
|
* 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)
|
## 0.15 (September 30, 2018)
|
||||||
|
|
||||||
* Reimplement `sendMessage` to deal properly with windowset changes made
|
* Reimplement `sendMessage` to deal properly with windowset changes made
|
||||||
|
@ -27,6 +27,7 @@ module XMonad.Layout (
|
|||||||
import XMonad.Core
|
import XMonad.Core
|
||||||
|
|
||||||
import Graphics.X11 (Rectangle(..))
|
import Graphics.X11 (Rectangle(..))
|
||||||
|
import Graphics.X11.Xlib.Extras ( Event(DestroyWindowEvent) )
|
||||||
import qualified XMonad.StackSet as W
|
import qualified XMonad.StackSet as W
|
||||||
import Control.Arrow ((***), second)
|
import Control.Arrow ((***), second)
|
||||||
import Control.Monad
|
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 =
|
handleMessage c@(Choose d l r) m | Just ReleaseResources <- fromMessage m =
|
||||||
join $ liftM2 (choose c d) (handle l ReleaseResources) (handle r ReleaseResources)
|
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
|
handleMessage c@(Choose d l r) m | Just (JumpToLayout desc) <- fromMessage m = do
|
||||||
ml <- handleMessage l m
|
ml <- handleMessage l m
|
||||||
mr <- handleMessage r m
|
mr <- handleMessage r m
|
||||||
|
@ -315,10 +315,15 @@ handle (MapRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do
|
|||||||
|
|
||||||
-- window destroyed, unmanage it
|
-- window destroyed, unmanage it
|
||||||
-- window gone, 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
|
unmanage w
|
||||||
modify (\s -> s { mapped = S.delete w (mapped s)
|
modify (\s -> s { mapped = S.delete w (mapped s)
|
||||||
, waitingUnmap = M.delete w (waitingUnmap 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
|
-- 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.
|
-- it is synthetic or we are not expecting an unmap notification from a window.
|
||||||
|
Loading…
x
Reference in New Issue
Block a user