aboutsummaryrefslogtreecommitdiffstats
path: root/UrgencyHook.hs
blob: 341016314dc8b8c8bdaa69b434a65dfbb8787745 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonadContrib.UrgencyHook
-- Copyright   :  Devin Mullins <me@twifkak.com>
-- License     :  BSD3-style (see LICENSE)
--
-- Maintainer  :  Devin Mullins <me@twifkak.com>
-- Stability   :  unstable
-- Portability :  unportable
--
-- UrgencyHook lets you configure an action to occur when a window demands
-- your attention. (In traditional WMs, this takes the form of "flashing"
-- on your "taskbar." Blech.)
--
-----------------------------------------------------------------------------

module XMonadContrib.UrgencyHook (
                                 -- * Usage
                                 -- $usage
                                 withUrgencyHook
                                 ) where

import {-# SOURCE #-} Config (urgencyHook)
import XMonad
import XMonadContrib.LayoutModifier

import Control.Monad (when)
import Data.Bits (testBit, clearBit)
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras

-- $usage
-- To wire this up, add:
--
-- > import XMonadContrib.UrgencyHook
--
-- to your import list in Config. Change your defaultLayout such that
-- withUrgencyHook is applied along the chain. Mine, for example:
--
-- > layoutHook = Layout $ withUrgencyHook $ windowNavigation wnConfig $
-- >                       Select defaultLayouts
--
-- It shouldn't hurt to have the "withUrgencyHook $" at the outermost layer,
-- as above, as UrgencyHook is a LayoutModifier, and hence passes on any
-- messages sent to it. Next, add your actual urgencyHook to Config. This
-- needs to take a Window and return an X () action. Here's an example:
--
-- > import Dzen (dzen)
-- > import NamedWindows (getName)
-- ...
-- > urgencyHook :: Window -> X ()
-- > urgencyHook w = do
-- >     name <- getName w
-- >     ws <- gets windowset
-- >     whenJust (W.findIndex w ws) (flash name ws)
-- >   where flash name ws index =
-- >               when (index /= W.tag (W.workspace (W.current ws))) $
-- >               dzen (show name ++ " requests your attention on workspace " ++ show index)
--
-- This example stands on the shoulders of the NamedWindows and Dzen modules,
-- but you can build whatever urgencyHook you like. Finally, in order to make
-- this compile, open up your Config.hs-boot file and add the following to it:
--
-- > urgencyHook :: Window -> X ()
--
-- Compile!

data WithUrgencyHook a = WithUrgencyHook deriving (Read, Show)

instance LayoutModifier WithUrgencyHook Window where
    handleMess _ mess =
      let event = fromMessage mess :: Maybe Event in do
      case event of
          Just (PropertyEvent { ev_event_type = t, ev_atom = a, ev_window = w }) ->
              when (t == propertyNotify && a == wM_HINTS) $ withDisplay $ \dpy -> do
                  wmh@WMHints { wmh_flags = flags } <- io $ getWMHints dpy w
                  when (testBit flags urgencyHintBit) $ do
                      urgencyHook w
                      -- Is clearing the bit really necessary? Xlib manual advises it.
                      io $ setWMHints dpy w wmh { wmh_flags = clearBit flags urgencyHintBit }
                      return ()
          _ -> return ()
      return Nothing

withUrgencyHook :: LayoutClass l Window => l Window -> ModifiedLayout WithUrgencyHook l Window
withUrgencyHook = ModifiedLayout WithUrgencyHook