From ee00ac8b283b139f0243e7e7845cc7a0cfb703fb Mon Sep 17 00:00:00 2001 From: Devin Mullins Date: Fri, 12 Oct 2007 05:45:06 +0200 Subject: documentation for UrgencyHook darcs-hash:20071012034506-78224-696f65ee0ba491fc134abd7c29b61e041a4e99b9.gz --- UrgencyHook.hs | 56 ++++++++++++++++++++++++++++++++++++++++++++++++++++++-- 1 file changed, 54 insertions(+), 2 deletions(-) diff --git a/UrgencyHook.hs b/UrgencyHook.hs index 95fef41..eec28f6 100644 --- a/UrgencyHook.hs +++ b/UrgencyHook.hs @@ -1,4 +1,24 @@ -module XMonadContrib.UrgencyHook where +----------------------------------------------------------------------------- +-- | +-- Module : XMonadContrib.UrgencyHook +-- Copyright : Devin Mullins +-- License : BSD3-style (see LICENSE) +-- +-- Maintainer : Devin Mullins +-- 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 @@ -9,7 +29,39 @@ import Data.Bits (testBit, clearBit) import Graphics.X11.Xlib import Graphics.X11.Xlib.Extras --- Oooh, spooky. +-- $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: +-- +-- > defaultLayout = Layout $ withUrgencyHook $ windowNavigation wnConfig $ +-- > LayoutSelection 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: +-- +-- > 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 -- cgit v1.2.3