summaryrefslogtreecommitdiffstats
path: root/XMonad/Main.hsc
diff options
context:
space:
mode:
Diffstat (limited to 'XMonad/Main.hsc')
-rw-r--r--XMonad/Main.hsc15
1 files changed, 5 insertions, 10 deletions
diff --git a/XMonad/Main.hsc b/XMonad/Main.hsc
index 653ec9d..19f988f 100644
--- a/XMonad/Main.hsc
+++ b/XMonad/Main.hsc
@@ -20,7 +20,6 @@ import Data.Bits
import Data.List ((\\))
import Data.Function
import qualified Data.Map as M
-import qualified Data.Set as S
import Control.Monad.Reader
import Control.Monad.State
import Data.Maybe (fromMaybe)
@@ -124,9 +123,8 @@ xmonad initxmc = do
st = XState
{ windowset = initialWinset
- , numberlockMask = 0
- , mapped = S.empty
- , waitingUnmap = M.empty
+ , numberlockMask = 0
+ , windowState = M.empty
, dragging = Nothing
, extensibleState = extState
}
@@ -205,18 +203,15 @@ handle (MapRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do
-- window gone, unmanage it
handle (DestroyWindowEvent {ev_window = w}) = whenX (isClient w) $ do
unmanage w
- modify (\s -> s { mapped = S.delete w (mapped s)
- , waitingUnmap = M.delete w (waitingUnmap s)})
+ modify (\s -> s { windowState = M.delete w (windowState s)})
-- 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.
handle (UnmapEvent {ev_window = w, ev_send_event = synthetic}) = whenX (isClient w) $ do
- e <- gets (fromMaybe 0 . M.lookup w . waitingUnmap)
+ e <- getsWindowState wsWaitingUnmap w
if (synthetic || e == 0)
then unmanage w
- else modify (\s -> s { waitingUnmap = M.update mpred w (waitingUnmap s) })
- where mpred 1 = Nothing
- mpred n = Just $ pred n
+ else modifyWindowState (\ws -> ws { wsWaitingUnmap = (wsWaitingUnmap ws) - 1 }) w
-- set keyboard mapping
handle e@(MappingNotifyEvent {}) = do