mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
use prefixed record names in latest X11-extras
This commit is contained in:
parent
2b6a5d25b6
commit
0d47f6299f
48
Main.hs
48
Main.hs
@ -85,8 +85,8 @@ scan dpy rootw = do
|
|||||||
filterM ok ws
|
filterM ok ws
|
||||||
where
|
where
|
||||||
ok w = do wa <- getWindowAttributes dpy w
|
ok w = do wa <- getWindowAttributes dpy w
|
||||||
return $ not (waOverrideRedirect wa)
|
return $ not (wa_override_redirect wa)
|
||||||
&& waMapState wa == waIsViewable
|
&& wa_map_state wa == waIsViewable
|
||||||
|
|
||||||
-- | Grab the keys back
|
-- | Grab the keys back
|
||||||
grabKeys :: Display -> Window -> IO ()
|
grabKeys :: Display -> Window -> IO ()
|
||||||
@ -124,64 +124,64 @@ grabKeys dpy rootw = do
|
|||||||
handle :: Event -> X ()
|
handle :: Event -> X ()
|
||||||
|
|
||||||
-- run window manager command
|
-- run window manager command
|
||||||
handle (KeyEvent {event_type = t, state = m, keycode = code})
|
handle (KeyEvent {ev_event_type = t, ev_state = m, ev_keycode = code})
|
||||||
| t == keyPress
|
| t == keyPress
|
||||||
= withDisplay $ \dpy -> do
|
= withDisplay $ \dpy -> do
|
||||||
s <- io $ keycodeToKeysym dpy code 0
|
s <- io $ keycodeToKeysym dpy code 0
|
||||||
whenJust (M.lookup (m,s) keys) id
|
whenJust (M.lookup (m,s) keys) id
|
||||||
|
|
||||||
-- manage a new window
|
-- manage a new window
|
||||||
handle (MapRequestEvent {window = w}) = withDisplay $ \dpy -> do
|
handle (MapRequestEvent {ev_window = w}) = withDisplay $ \dpy -> do
|
||||||
wa <- io $ getWindowAttributes dpy w -- ignore override windows
|
wa <- io $ getWindowAttributes dpy w -- ignore override windows
|
||||||
when (not (waOverrideRedirect wa)) $ manage w
|
when (not (wa_override_redirect wa)) $ manage w
|
||||||
|
|
||||||
-- window destroyed, unmanage it
|
-- window destroyed, unmanage it
|
||||||
handle (DestroyWindowEvent {window = w}) = do b <- isClient w; when b $ unmanage w
|
handle (DestroyWindowEvent {ev_window = w}) = do b <- isClient w; when b $ unmanage w
|
||||||
|
|
||||||
-- window gone, unmanage it
|
-- window gone, unmanage it
|
||||||
handle (UnmapEvent {window = w}) = do b <- isClient w; when b $ unmanage w
|
handle (UnmapEvent {ev_window = w}) = do b <- isClient w; when b $ unmanage w
|
||||||
|
|
||||||
-- set keyboard mapping
|
-- set keyboard mapping
|
||||||
handle e@(MappingNotifyEvent {window = w}) = do
|
handle e@(MappingNotifyEvent {ev_window = w}) = do
|
||||||
-- this fromIntegral is only necessary with the old X11 version that uses
|
-- this fromIntegral is only necessary with the old X11 version that uses
|
||||||
-- Int instead of CInt. TODO delete it when there is a new release of X11
|
-- Int instead of CInt. TODO delete it when there is a new release of X11
|
||||||
let m = (request e, first_keycode e, fromIntegral $ count e)
|
let m = (ev_request e, ev_first_keycode e, fromIntegral $ ev_count e)
|
||||||
withDisplay $ \d -> io $ refreshKeyboardMapping d m
|
withDisplay $ \d -> io $ refreshKeyboardMapping d m
|
||||||
when (request e == mappingKeyboard) $ withDisplay $ io . flip grabKeys w
|
when (ev_request e == mappingKeyboard) $ withDisplay $ io . flip grabKeys w
|
||||||
|
|
||||||
-- click on an unfocussed window
|
-- click on an unfocussed window
|
||||||
handle (ButtonEvent {window = w, event_type = t})
|
handle (ButtonEvent {ev_window = w, ev_event_type = t})
|
||||||
| t == buttonPress
|
| t == buttonPress
|
||||||
= safeFocus w
|
= safeFocus w
|
||||||
|
|
||||||
-- entered a normal window
|
-- entered a normal window
|
||||||
handle e@(CrossingEvent {window = w, event_type = t})
|
handle e@(CrossingEvent {ev_window = w, ev_event_type = t})
|
||||||
| t == enterNotify && mode e == notifyNormal && detail e /= notifyInferior
|
| t == enterNotify && ev_mode e == notifyNormal && ev_detail e /= notifyInferior
|
||||||
= safeFocus w
|
= safeFocus w
|
||||||
|
|
||||||
-- left a window, check if we need to focus root
|
-- left a window, check if we need to focus root
|
||||||
handle e@(CrossingEvent {event_type = t})
|
handle e@(CrossingEvent {ev_event_type = t})
|
||||||
| t == leaveNotify
|
| t == leaveNotify
|
||||||
= do rootw <- gets theRoot
|
= do rootw <- gets theRoot
|
||||||
when (window e == rootw && not (same_screen e)) $ setFocus rootw
|
when (ev_window e == rootw && not (ev_same_screen e)) $ setFocus rootw
|
||||||
|
|
||||||
-- configure a window
|
-- configure a window
|
||||||
handle e@(ConfigureRequestEvent {window = w}) = do
|
handle e@(ConfigureRequestEvent {ev_window = w}) = do
|
||||||
XState { display = dpy, workspace = ws } <- get
|
XState { display = dpy, workspace = ws } <- get
|
||||||
|
|
||||||
when (W.member w ws) $ -- already managed, reconfigure (see client:configure()
|
when (W.member w ws) $ -- already managed, reconfigure (see client:configure()
|
||||||
trace ("Reconfigure already managed window: " ++ show w)
|
trace ("Reconfigure already managed window: " ++ show w)
|
||||||
|
|
||||||
io $ configureWindow dpy (window e) (value_mask e) $ WindowChanges
|
io $ configureWindow dpy (ev_window e) (ev_value_mask e) $ WindowChanges
|
||||||
{ wcX = x e
|
{ wc_x = ev_x e
|
||||||
, wcY = y e
|
, wc_y = ev_y e
|
||||||
, wcWidth = width e
|
, wc_width = ev_width e
|
||||||
, wcHeight = height e
|
, wc_height = ev_height e
|
||||||
, wcBorderWidth = border_width e
|
, wc_border_width = ev_border_width e
|
||||||
, wcSibling = above e
|
, wc_sibling = ev_above e
|
||||||
-- this fromIntegral is only necessary with the old X11 version that uses
|
-- this fromIntegral is only necessary with the old X11 version that uses
|
||||||
-- Int instead of CInt. TODO delete it when there is a new release of X11
|
-- Int instead of CInt. TODO delete it when there is a new release of X11
|
||||||
, wcStackMode = fromIntegral $ detail e
|
, wc_stack_mode = fromIntegral $ ev_detail e
|
||||||
}
|
}
|
||||||
|
|
||||||
io $ sync dpy False
|
io $ sync dpy False
|
||||||
|
@ -146,7 +146,7 @@ setButtonGrab False w = withDisplay $ \d -> io $
|
|||||||
-- rectangle, including its border.
|
-- rectangle, including its border.
|
||||||
moveWindowInside :: Display -> Window -> Rectangle -> IO ()
|
moveWindowInside :: Display -> Window -> Rectangle -> IO ()
|
||||||
moveWindowInside d w r = do
|
moveWindowInside d w r = do
|
||||||
bw <- (fromIntegral . waBorderWidth) `liftM` getWindowAttributes d w
|
bw <- (fromIntegral . wa_border_width) `liftM` getWindowAttributes d w
|
||||||
moveResizeWindow d w (rect_x r) (rect_y r)
|
moveResizeWindow d w (rect_x r) (rect_y r)
|
||||||
(rect_width r - bw*2)
|
(rect_width r - bw*2)
|
||||||
(rect_height r - bw*2)
|
(rect_height r - bw*2)
|
||||||
|
Loading…
x
Reference in New Issue
Block a user