aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Util/Dzen.hs
diff options
context:
space:
mode:
authorSpencer Janssen <sjanssen@cse.unl.edu>2007-11-01 21:10:59 +0100
committerSpencer Janssen <sjanssen@cse.unl.edu>2007-11-01 21:10:59 +0100
commit4866f2e367dfcf22a9591231ba40948826a1b438 (patch)
tree7a245caee3f146826b267d773b7eaa80386a818e /XMonad/Util/Dzen.hs
parent47589e1913fb9530481caedb543978a30d4323ea (diff)
downloadXMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.tar.gz
XMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.tar.xz
XMonadContrib-4866f2e367dfcf22a9591231ba40948826a1b438.zip
Hierarchify
darcs-hash:20071101201059-a5988-fc1f1262bec1b69e13ba18ae7cefeafc8c4471d4.gz
Diffstat (limited to 'XMonad/Util/Dzen.hs')
-rw-r--r--XMonad/Util/Dzen.hs71
1 files changed, 71 insertions, 0 deletions
diff --git a/XMonad/Util/Dzen.hs b/XMonad/Util/Dzen.hs
new file mode 100644
index 0000000..02fce05
--- /dev/null
+++ b/XMonad/Util/Dzen.hs
@@ -0,0 +1,71 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Util.Dzen
+-- Copyright : (c) glasser@mit.edu
+-- License : BSD
+--
+-- Maintainer : glasser@mit.edu
+-- Stability : unstable
+-- Portability : unportable
+--
+-- Handy wrapper for dzen. Requires dzen >= 0.2.4.
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Util.Dzen (dzen, dzenWithArgs, dzenScreen,
+ dzenUrgencyHook, dzenUrgencyHookWithArgs,
+ seconds) where
+
+import Control.Monad (when)
+import Control.Monad.State (gets)
+import qualified Data.Set as S
+import Graphics.X11.Types (Window)
+
+import qualified XMonad.StackSet as W
+import XMonad
+
+import XMonad.Util.NamedWindows (getName)
+import XMonad.Util.Run (runProcessWithInputAndWait, seconds)
+
+-- | @dzen str timeout@ pipes @str@ to dzen2 for @timeout@ microseconds.
+-- Example usage:
+-- > dzen "Hi, mom!" (5 `seconds`)
+dzen :: String -> Int -> X ()
+dzen str timeout = dzenWithArgs str [] timeout
+
+-- | @dzen str args timeout@ pipes @str@ to dzen2 for @timeout@ seconds, passing @args@ to dzen.
+-- Example usage:
+-- > dzenWithArgs "Hi, dons!" ["-ta", "r"] (5 `seconds`)
+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.
+ where unchomp s@['\n'] = s
+ unchomp [] = ['\n']
+ unchomp (c:cs) = c : unchomp cs
+
+-- | @dzenScreen sc str timeout@ pipes @str@ to dzen2 for @timeout@ microseconds, and on screen @sc@.
+-- Requires dzen to be compiled with Xinerama support.
+dzenScreen :: ScreenId -> String -> Int -> X()
+dzenScreen sc str timeout = dzenWithArgs str ["-xs", screen] timeout
+ where screen = toXineramaArg sc
+ toXineramaArg n = show ( ((fromIntegral n)+1)::Int )
+
+-- | Flashes when a window requests your attention and you can't see it. For use with
+-- XMonadContrib.UrgencyHook. Usage:
+-- > urgencyHook = dzenUrgencyHook (5 `seconds`)
+dzenUrgencyHook :: Int -> Window -> X ()
+dzenUrgencyHook = dzenUrgencyHookWithArgs []
+
+-- | Flashes when a window requests your attention and you can't see it. For use with
+-- XMonadContrib.UrgencyHook. Usage:
+-- > urgencyHook = dzenUrgencyHookWithArgs ["-bg", "darkgreen"] (5 `seconds`)
+dzenUrgencyHookWithArgs :: [String] -> Int -> Window -> X ()
+dzenUrgencyHookWithArgs args duration w = do
+ visibles <- gets mapped
+ name <- getName w
+ ws <- gets windowset
+ whenJust (W.findTag w ws) (flash name visibles)
+ where flash name visibles index =
+ when (not $ S.member w visibles) $
+ dzenWithArgs (show name ++ " requests your attention on workspace " ++ index)
+ args duration