mirror of
https://github.com/xmonad/xmonad.git
synced 2025-05-19 08:30:21 -07:00
Add configuration option clickToFocus (issue 225)
To summarize this allows clicks which change the focus to also be passed on to that window.
This commit is contained in:
parent
38faddf9de
commit
a34a5e979a
@ -27,11 +27,11 @@ module XMonad.Config (defaultConfig) where
|
|||||||
import XMonad.Core as XMonad hiding
|
import XMonad.Core as XMonad hiding
|
||||||
(workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
|
(workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
|
||||||
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
|
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
|
||||||
,handleEventHook)
|
,handleEventHook,clickJustFocuses)
|
||||||
import qualified XMonad.Core as XMonad
|
import qualified XMonad.Core as XMonad
|
||||||
(workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
|
(workspaces,manageHook,keys,logHook,startupHook,borderWidth,mouseBindings
|
||||||
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
|
,layoutHook,modMask,terminal,normalBorderColor,focusedBorderColor,focusFollowsMouse
|
||||||
,handleEventHook)
|
,handleEventHook,clickJustFocuses)
|
||||||
|
|
||||||
import XMonad.Layout
|
import XMonad.Layout
|
||||||
import XMonad.Operations
|
import XMonad.Operations
|
||||||
@ -157,6 +157,11 @@ terminal = "xterm"
|
|||||||
focusFollowsMouse :: Bool
|
focusFollowsMouse :: Bool
|
||||||
focusFollowsMouse = True
|
focusFollowsMouse = True
|
||||||
|
|
||||||
|
-- | Whether a mouse click select the focus or is just passed to the window
|
||||||
|
clickJustFocuses :: Bool
|
||||||
|
clickJustFocuses = True
|
||||||
|
|
||||||
|
|
||||||
-- | The xmonad key bindings. Add, modify or remove key bindings here.
|
-- | The xmonad key bindings. Add, modify or remove key bindings here.
|
||||||
--
|
--
|
||||||
-- (The comment formatting character is used when generating the manpage)
|
-- (The comment formatting character is used when generating the manpage)
|
||||||
@ -248,6 +253,7 @@ defaultConfig = XConfig
|
|||||||
, XMonad.manageHook = manageHook
|
, XMonad.manageHook = manageHook
|
||||||
, XMonad.handleEventHook = handleEventHook
|
, XMonad.handleEventHook = handleEventHook
|
||||||
, XMonad.focusFollowsMouse = focusFollowsMouse
|
, XMonad.focusFollowsMouse = focusFollowsMouse
|
||||||
|
, XMonad.clickJustFocuses = clickJustFocuses
|
||||||
}
|
}
|
||||||
|
|
||||||
-- | Finally, a copy of the default bindings in simple textual tabular format.
|
-- | Finally, a copy of the default bindings in simple textual tabular format.
|
||||||
|
@ -110,6 +110,7 @@ data XConfig l = XConfig
|
|||||||
, logHook :: !(X ()) -- ^ The action to perform when the windows set is changed
|
, logHook :: !(X ()) -- ^ The action to perform when the windows set is changed
|
||||||
, startupHook :: !(X ()) -- ^ The action to perform on startup
|
, startupHook :: !(X ()) -- ^ The action to perform on startup
|
||||||
, focusFollowsMouse :: !Bool -- ^ Whether window entry events can change focus
|
, focusFollowsMouse :: !Bool -- ^ Whether window entry events can change focus
|
||||||
|
, clickJustFocuses :: !Bool -- ^ False to make a click which changes focus to be additionally passed to the window
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
|
@ -253,8 +253,11 @@ handle e@(ButtonEvent {ev_window = w,ev_event_type = t,ev_button = b })
|
|||||||
m <- cleanMask $ ev_state e
|
m <- cleanMask $ ev_state e
|
||||||
mact <- asks (M.lookup (m, b) . buttonActions)
|
mact <- asks (M.lookup (m, b) . buttonActions)
|
||||||
case mact of
|
case mact of
|
||||||
(Just act) | isr -> act $ ev_subwindow e
|
Just act | isr -> act $ ev_subwindow e
|
||||||
_ -> focus w >> io (allowEvents dpy replayPointer currentTime)
|
_ -> do
|
||||||
|
focus w
|
||||||
|
ctf <- asks (clickJustFocuses . config)
|
||||||
|
unless ctf $ io (allowEvents dpy replayPointer currentTime)
|
||||||
broadcastMessage e -- Always send button events.
|
broadcastMessage e -- Always send button events.
|
||||||
|
|
||||||
-- entered a normal window: focus it if focusFollowsMouse is set to
|
-- entered a normal window: focus it if focusFollowsMouse is set to
|
||||||
|
@ -283,11 +283,14 @@ rescreen = do
|
|||||||
|
|
||||||
-- | setButtonGrab. Tell whether or not to intercept clicks on a given window
|
-- | setButtonGrab. Tell whether or not to intercept clicks on a given window
|
||||||
setButtonGrab :: Bool -> Window -> X ()
|
setButtonGrab :: Bool -> Window -> X ()
|
||||||
setButtonGrab grab w = withDisplay $ \d -> io $
|
setButtonGrab grab w = do
|
||||||
if grab
|
pointerMode <- asks $ \c -> if clickJustFocuses (config c)
|
||||||
|
then grabModeAsync
|
||||||
|
else grabModeSync
|
||||||
|
withDisplay $ \d -> io $ if grab
|
||||||
then forM_ [button1, button2, button3] $ \b ->
|
then forM_ [button1, button2, button3] $ \b ->
|
||||||
grabButton d b anyModifier w False buttonPressMask
|
grabButton d b anyModifier w False buttonPressMask
|
||||||
grabModeSync grabModeSync none none
|
pointerMode grabModeSync none none
|
||||||
else ungrabButton d anyButton anyModifier w
|
else ungrabButton d anyButton anyModifier w
|
||||||
|
|
||||||
-- ---------------------------------------------------------------------
|
-- ---------------------------------------------------------------------
|
||||||
|
Loading…
x
Reference in New Issue
Block a user