mirror of
https://github.com/xmonad/xmonad.git
synced 2025-07-31 12:11:53 -07:00
first shot at allowing click to focus windows
This commit is contained in:
19
Main.hs
19
Main.hs
@@ -120,6 +120,14 @@ grabKeys dpy rootw = do
|
|||||||
-- Window manager clients normally should ignore this window if the
|
-- Window manager clients normally should ignore this window if the
|
||||||
-- override_redirect member is True.
|
-- override_redirect member is True.
|
||||||
--
|
--
|
||||||
|
|
||||||
|
safeFocus :: Window -> X ()
|
||||||
|
safeFocus w = do ws <- gets workspace
|
||||||
|
if W.member w ws
|
||||||
|
then setFocus w
|
||||||
|
else do b <- isRoot w
|
||||||
|
when b setTopFocus
|
||||||
|
|
||||||
handle :: Event -> X ()
|
handle :: Event -> X ()
|
||||||
|
|
||||||
-- run window manager command
|
-- run window manager command
|
||||||
@@ -148,14 +156,15 @@ handle e@(MappingNotifyEvent {window = w}) = do
|
|||||||
io $ refreshKeyboardMapping m
|
io $ refreshKeyboardMapping m
|
||||||
when (request e == mappingKeyboard) $ withDisplay $ io . flip grabKeys w
|
when (request e == mappingKeyboard) $ withDisplay $ io . flip grabKeys w
|
||||||
|
|
||||||
|
-- click on an unfocussed window
|
||||||
|
handle (ButtonEvent {window = w, event_type = t})
|
||||||
|
| t == buttonPress
|
||||||
|
= safeFocus w
|
||||||
|
|
||||||
-- entered a normal window
|
-- entered a normal window
|
||||||
handle e@(CrossingEvent {window = w, event_type = t})
|
handle e@(CrossingEvent {window = w, event_type = t})
|
||||||
| t == enterNotify && mode e == notifyNormal && detail e /= notifyInferior
|
| t == enterNotify && mode e == notifyNormal && detail e /= notifyInferior
|
||||||
= do ws <- gets workspace
|
= safeFocus w
|
||||||
if W.member w ws
|
|
||||||
then setFocus w
|
|
||||||
else do b <- isRoot w
|
|
||||||
when b setTopFocus
|
|
||||||
|
|
||||||
-- 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 {event_type = t})
|
||||||
|
@@ -31,8 +31,6 @@ refresh = do
|
|||||||
d <- gets display
|
d <- gets display
|
||||||
fls <- gets layoutDescs
|
fls <- gets layoutDescs
|
||||||
dfltfl <- gets defaultLayoutDesc
|
dfltfl <- gets defaultLayoutDesc
|
||||||
-- l <- gets layout
|
|
||||||
-- ratio <- gets leftWidth
|
|
||||||
let move w a b c e = io $ moveResizeWindow d w a b c e
|
let move w a b c e = io $ moveResizeWindow d w a b c e
|
||||||
flip mapM_ (M.assocs ws2sc) $ \(n, scn) -> do
|
flip mapM_ (M.assocs ws2sc) $ \(n, scn) -> do
|
||||||
let sc = xinesc !! scn
|
let sc = xinesc !! scn
|
||||||
@@ -43,6 +41,9 @@ refresh = do
|
|||||||
fl = M.findWithDefault dfltfl n fls
|
fl = M.findWithDefault dfltfl n fls
|
||||||
l = layoutType fl
|
l = layoutType fl
|
||||||
ratio = tileFraction fl
|
ratio = tileFraction fl
|
||||||
|
mapM_ (setButtonGrab True) (W.index n ws)
|
||||||
|
when (n == W.current ws) $
|
||||||
|
maybe (return ()) (setButtonGrab False) (W.peekStack n ws)
|
||||||
case l of
|
case l of
|
||||||
Full -> whenJust (W.peekStack n ws) $ \w -> do
|
Full -> whenJust (W.peekStack n ws) $ \w -> do
|
||||||
move w sx sy sw sh
|
move w sx sy sw sh
|
||||||
@@ -96,6 +97,18 @@ hide w = withDisplay $ \d -> do
|
|||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
-- Window operations
|
-- Window operations
|
||||||
|
|
||||||
|
-- | setButtonGrab. Tell whether or not to intercept clicks on a given window
|
||||||
|
buttonsToGrab :: [ButtonMask]
|
||||||
|
buttonsToGrab = [button1, button2, button3]
|
||||||
|
|
||||||
|
setButtonGrab :: Bool -> Window -> X ()
|
||||||
|
setButtonGrab True w = withDisplay $ \d -> io $ flip mapM_ buttonsToGrab (\b ->
|
||||||
|
grabButton d b anyModifier w False
|
||||||
|
(buttonPressMask .|. buttonReleaseMask)
|
||||||
|
grabModeAsync grabModeSync none none)
|
||||||
|
setButtonGrab False w = withDisplay $ \d -> io $ flip mapM_ buttonsToGrab (\b ->
|
||||||
|
ungrabButton d b anyModifier w)
|
||||||
|
|
||||||
-- | manage. Add a new window to be managed in the current workspace. Bring it into focus.
|
-- | manage. Add a new window to be managed in the current workspace. Bring it into focus.
|
||||||
-- If the window is already under management, it is just raised.
|
-- If the window is already under management, it is just raised.
|
||||||
--
|
--
|
||||||
@@ -219,5 +232,3 @@ restart :: IO ()
|
|||||||
restart = do prog <- getProgName
|
restart = do prog <- getProgName
|
||||||
args <- getArgs
|
args <- getArgs
|
||||||
executeFile prog True args Nothing
|
executeFile prog True args Nothing
|
||||||
|
|
||||||
|
|
||||||
|
6
TODO
6
TODO
@@ -25,8 +25,8 @@
|
|||||||
- change focus in the StackSet structure on EnterNotify
|
- change focus in the StackSet structure on EnterNotify
|
||||||
- let mod+enter demote a master window
|
- let mod+enter demote a master window
|
||||||
- borders (low priority, maybe wait until 0.2)
|
- borders (low priority, maybe wait until 0.2)
|
||||||
- get this to play nicely with Xinerama (at least under TwinView, things
|
- let focus-follows-mouse also change the active workspace (not just the
|
||||||
are very strange)
|
active window); note that this currently also makes click-to-focus appear
|
||||||
- let click events/scrollwheel events change the focus
|
slightly buggy, since sometimes, the wrong window is exempted from setButtonGrab
|
||||||
|
|
||||||
* Tile vertically/ resize height.
|
* Tile vertically/ resize height.
|
||||||
|
@@ -46,10 +46,6 @@ data XState = XState
|
|||||||
, defaultLayoutDesc :: {-# UNPACK #-} !LayoutDesc
|
, defaultLayoutDesc :: {-# UNPACK #-} !LayoutDesc
|
||||||
, layoutDescs :: {-# UNPACK #-} !(M.Map Int LayoutDesc)
|
, layoutDescs :: {-# UNPACK #-} !(M.Map Int LayoutDesc)
|
||||||
-- ^ mapping of workspaces to descriptions of their layouts
|
-- ^ mapping of workspaces to descriptions of their layouts
|
||||||
|
|
||||||
-- , layout :: {-# UNPACK #-} !Layout
|
|
||||||
-- how much of the screen the main window should take
|
|
||||||
-- , leftWidth :: {-# UNPACK #-} !Rational
|
|
||||||
}
|
}
|
||||||
|
|
||||||
type WorkSpace = StackSet Window
|
type WorkSpace = StackSet Window
|
||||||
|
Reference in New Issue
Block a user