aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorDevin Mullins <me@twifkak.com>2007-10-18 04:17:42 +0200
committerDevin Mullins <me@twifkak.com>2007-10-18 04:17:42 +0200
commit6f381eb4fd9f00f229348acda35a09990441c208 (patch)
treedfef22fbe260668fe331f0255e4dcf2552bb7dec
parentd8d003eb6621245e59430ecfd5de27dcd6bcccda (diff)
downloadXMonadContrib-6f381eb4fd9f00f229348acda35a09990441c208.tar.gz
XMonadContrib-6f381eb4fd9f00f229348acda35a09990441c208.tar.xz
XMonadContrib-6f381eb4fd9f00f229348acda35a09990441c208.zip
add dzenUrgencyHook as example (and the one I use)
darcs-hash:20071018021742-78224-2e9fe5bc8704959e9ccf089b462f0da55f796893.gz
-rw-r--r--Dzen.hs24
1 files changed, 23 insertions, 1 deletions
diff --git a/Dzen.hs b/Dzen.hs
index 0438a68..5d09e5d 100644
--- a/Dzen.hs
+++ b/Dzen.hs
@@ -12,9 +12,17 @@
--
-----------------------------------------------------------------------------
-module XMonadContrib.Dzen (dzen, dzenScreen, seconds) where
+module XMonadContrib.Dzen (dzen, dzenScreen, dzenUrgencyHook, seconds) where
+import Control.Monad (when)
+import Control.Monad.State (gets)
+import qualified Data.Set as S
+import Graphics.X11.Types (Window)
+
+import qualified StackSet as W
import XMonad
+
+import XMonadContrib.NamedWindows (getName)
import XMonadContrib.Run (runProcessWithInputAndWait, seconds)
toXineramaArg :: ScreenId -> String
@@ -32,6 +40,20 @@ dzenScreen :: ScreenId -> String -> Int -> X()
dzenScreen sc str timeout = dzenWithArgs str ["-xs", screen] timeout
where screen = toXineramaArg sc
+-- | Flashes when a window requests your attention and you can't see it. For use with
+-- XMonadContrib.UrgencyHook. Usage:
+-- > urgencyHook = dzenUrgencyHook (5 `seconds`)
+-- Bug: Doesn't flash if you're on the same workspace, Full or Tabbed layout, different window.
+dzenUrgencyHook :: Int -> Window -> X ()
+dzenUrgencyHook duration w = do
+ visibles <- gets mapped
+ name <- getName w
+ ws <- gets windowset
+ whenJust (W.findIndex w ws) (flash name ws visibles)
+ where flash name ws visibles index =
+ when (index /= W.tag (W.workspace (W.current ws)) && not (S.member w visibles)) $
+ dzen (show name ++ " requests your attention on workspace " ++ index) duration
+
dzenWithArgs :: String -> [String] -> Int -> X ()
dzenWithArgs str args timeout = io $ runProcessWithInputAndWait "dzen2" args (unchomp str) timeout
-- dzen seems to require the input to terminate with exactly one newline.