aboutsummaryrefslogtreecommitdiffstats
path: root/UrgencyHook.hs
diff options
context:
space:
mode:
authorDevin Mullins <me@twifkak.com>2007-11-03 06:51:43 +0100
committerDevin Mullins <me@twifkak.com>2007-11-03 06:51:43 +0100
commitd457dd075acd61e22deefaa17250654b0de77ebc (patch)
tree6e1531a2c305a2073c366fd46e02167dfb08b320 /UrgencyHook.hs
parent5b58b15233772a6640b6d3fb502008c386c16826 (diff)
downloadXMonadContrib-d457dd075acd61e22deefaa17250654b0de77ebc.tar.gz
XMonadContrib-d457dd075acd61e22deefaa17250654b0de77ebc.tar.xz
XMonadContrib-d457dd075acd61e22deefaa17250654b0de77ebc.zip
changed urgent state from Set to list
darcs-hash:20071103055143-78224-378f8e91e98699668529ea8d407e3562a31c2ef2.gz
Diffstat (limited to 'UrgencyHook.hs')
-rw-r--r--UrgencyHook.hs17
1 files changed, 9 insertions, 8 deletions
diff --git a/UrgencyHook.hs b/UrgencyHook.hs
index de05282..63760f8 100644
--- a/UrgencyHook.hs
+++ b/UrgencyHook.hs
@@ -32,7 +32,8 @@ import Control.Monad (when)
import Control.Monad.State (gets)
import Data.Bits (testBit, clearBit)
import Data.IORef
-import Data.Set (Set)
+import Data.List ((\\))
+import Data.Maybe (listToMaybe)
import qualified Data.Set as S
import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras
@@ -74,13 +75,13 @@ import Foreign (unsafePerformIO)
-- | Stores the global set of all urgent windows, across workspaces. Not exported -- use
-- @readUrgents@ or @withUrgents@ instead.
{-# NOINLINE urgents #-}
-urgents :: IORef (Set Window)
-urgents = unsafePerformIO (newIORef S.empty)
+urgents :: IORef [Window]
+urgents = unsafePerformIO (newIORef [])
-readUrgents :: X (Set Window)
+readUrgents :: X [Window]
readUrgents = io $ readIORef urgents
-withUrgents :: (Set Window -> X a) -> X a
+withUrgents :: ([Window] -> X a) -> X a
withUrgents f = readUrgents >>= f
data WithUrgencyHook a = WithUrgencyHook deriving (Read, Show)
@@ -98,7 +99,7 @@ instance LayoutModifier WithUrgencyHook Window where
-- times (e.g. causing the dzen to blink) unless it's cleared. XMonad is
-- not a typical WM, so we're just breaking one more rule, here.
io $ setWMHints dpy w wmh { wmh_flags = clearBit flags urgencyHintBit }
- adjustUrgents (S.insert w)
+ adjustUrgents (\ws -> if elem w ws then ws else w : ws)
logHook -- call logHook after IORef has been modified
-- Doing the setWMHints triggers another propertyNotify with the bit
-- cleared, so we ignore that message. This has the potentially wrong
@@ -111,10 +112,10 @@ instance LayoutModifier WithUrgencyHook Window where
-- Clear the urgency bit and remove from the urgent list when the window becomes visible.
redoLayout _ _ _ windowRects = do
visibles <- gets mapped
- adjustUrgents (S.\\ visibles)
+ adjustUrgents (\\ (S.toList visibles))
return (windowRects, Nothing)
-adjustUrgents :: (Set Window -> Set Window) -> X ()
+adjustUrgents :: ([Window] -> [Window]) -> X ()
adjustUrgents f = io $ modifyIORef urgents f
withUrgencyHook :: LayoutClass l Window => l Window -> ModifiedLayout WithUrgencyHook l Window