Files
xmonad-contrib/XMonad/Hooks/ICCCMFocus.hs
Adam Vogt 0377a9e335 H.ICCCMFocus had atom_WM_TAKE_FOCUS incorrectly removed
It is possible that this atom should be defined in the X11 library, but fix the
build of contrib for now. In any case, this would have to wait for a change and
release of the X11 binding.

rolling back:

Wed Jan  5 22:38:39 EST 2011  Adam Vogt <vogt.adam@gmail.com>
  * Remove accidental atom_WM_TAKE_FOCUS from H.ICCCMFocus
  
  The XMonad module exports this already

    M ./XMonad/Hooks/ICCCMFocus.hs -7 +1
2011-01-06 19:20:52 +00:00

58 lines
1.5 KiB
Haskell

-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Hooks.ICCCMFocus
-- License : BSD
--
-- Maintainer : Tony Morris <haskell@tmorris.net>
--
-- Implemented in your @logHook@, Java swing applications will not misbehave
-- when it comes to taking and losing focus.
--
-- This has been done by taking the patch in <http://code.google.com/p/xmonad/issues/detail?id=177> and refactoring it so that it can be included in @~\/.xmonad\/xmonad.hs@.
--
-- @
-- conf' =
-- conf {
-- logHook = takeTopFocus
-- }
-- @
-----------------------------------------------------------------------------
module XMonad.Hooks.ICCCMFocus
(
atom_WM_TAKE_FOCUS
, takeFocusX
, takeTopFocus
) where
import XMonad
import XMonad.Hooks.SetWMName
import qualified XMonad.StackSet as W
import Control.Monad
atom_WM_TAKE_FOCUS ::
X Atom
atom_WM_TAKE_FOCUS =
getAtom "WM_TAKE_FOCUS"
takeFocusX ::
Window
-> X ()
takeFocusX w =
withWindowSet . const $ do
dpy <- asks display
wmtakef <- atom_WM_TAKE_FOCUS
wmprot <- atom_WM_PROTOCOLS
protocols <- io $ getWMProtocols dpy w
when (wmtakef `elem` protocols) $
io . allocaXEvent $ \ev -> do
setEventType ev clientMessage
setClientMessageEvent ev w wmprot 32 wmtakef currentTime
sendEvent dpy w False noEventMask ev
-- | The value to add to your log hook configuration.
takeTopFocus ::
X ()
takeTopFocus =
(withWindowSet $ maybe (setFocusX =<< asks theRoot) takeFocusX . W.peek) >> setWMName "LG3D"