first shot at allowing click to focus windows

This commit is contained in:
daniel
2007-03-28 10:15:40 +00:00
parent 97638a648c
commit 5ae3c6a1fc
4 changed files with 32 additions and 16 deletions

19
Main.hs
View File

@@ -120,6 +120,14 @@ grabKeys dpy rootw = do
-- Window manager clients normally should ignore this window if the
-- 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 ()
-- run window manager command
@@ -148,14 +156,15 @@ handle e@(MappingNotifyEvent {window = w}) = do
io $ refreshKeyboardMapping m
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
handle e@(CrossingEvent {window = w, event_type = t})
| t == enterNotify && mode e == notifyNormal && detail e /= notifyInferior
= do ws <- gets workspace
if W.member w ws
then setFocus w
else do b <- isRoot w
when b setTopFocus
= safeFocus w
-- left a window, check if we need to focus root
handle e@(CrossingEvent {event_type = t})

View File

@@ -31,8 +31,6 @@ refresh = do
d <- gets display
fls <- gets layoutDescs
dfltfl <- gets defaultLayoutDesc
-- l <- gets layout
-- ratio <- gets leftWidth
let move w a b c e = io $ moveResizeWindow d w a b c e
flip mapM_ (M.assocs ws2sc) $ \(n, scn) -> do
let sc = xinesc !! scn
@@ -43,6 +41,9 @@ refresh = do
fl = M.findWithDefault dfltfl n fls
l = layoutType 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
Full -> whenJust (W.peekStack n ws) $ \w -> do
move w sx sy sw sh
@@ -96,6 +97,18 @@ hide w = withDisplay $ \d -> do
-- ---------------------------------------------------------------------
-- 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.
-- If the window is already under management, it is just raised.
--
@@ -219,5 +232,3 @@ restart :: IO ()
restart = do prog <- getProgName
args <- getArgs
executeFile prog True args Nothing

6
TODO
View File

@@ -25,8 +25,8 @@
- change focus in the StackSet structure on EnterNotify
- let mod+enter demote a master window
- borders (low priority, maybe wait until 0.2)
- get this to play nicely with Xinerama (at least under TwinView, things
are very strange)
- let click events/scrollwheel events change the focus
- let focus-follows-mouse also change the active workspace (not just the
active window); note that this currently also makes click-to-focus appear
slightly buggy, since sometimes, the wrong window is exempted from setButtonGrab
* Tile vertically/ resize height.

View File

@@ -46,10 +46,6 @@ data XState = XState
, defaultLayoutDesc :: {-# UNPACK #-} !LayoutDesc
, layoutDescs :: {-# UNPACK #-} !(M.Map Int LayoutDesc)
-- ^ 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