aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Hooks/UrgencyHook.hs
diff options
context:
space:
mode:
authorDevin Mullins <me@twifkak.com>2008-05-15 18:44:36 +0200
committerDevin Mullins <me@twifkak.com>2008-05-15 18:44:36 +0200
commit2674799950c9e96f67c3b251fc3c6dcf460e46fb (patch)
tree05290f6c60860df1f55892b28c1eb4b6355e505a /XMonad/Hooks/UrgencyHook.hs
parent1254b083132d9af4f83e66476cb01e1d5ffbb6cd (diff)
downloadXMonadContrib-2674799950c9e96f67c3b251fc3c6dcf460e46fb.tar.gz
XMonadContrib-2674799950c9e96f67c3b251fc3c6dcf460e46fb.tar.xz
XMonadContrib-2674799950c9e96f67c3b251fc3c6dcf460e46fb.zip
UrgencyHook: removeVisiblesFromUrgents -> cleanupUrgents
Now only removes windows based on SuppressWhen setting. darcs-hash:20080515164436-78224-0ef49f8355ace31ddbef6b6264ae9f2a8a750c89.gz
Diffstat (limited to 'XMonad/Hooks/UrgencyHook.hs')
-rw-r--r--XMonad/Hooks/UrgencyHook.hs38
1 files changed, 22 insertions, 16 deletions
diff --git a/XMonad/Hooks/UrgencyHook.hs b/XMonad/Hooks/UrgencyHook.hs
index d5a6b79..9ea7ad8 100644
--- a/XMonad/Hooks/UrgencyHook.hs
+++ b/XMonad/Hooks/UrgencyHook.hs
@@ -69,11 +69,12 @@ import XMonad.Hooks.EventHook
import XMonad.Util.Dzen (dzenWithArgs, seconds)
import XMonad.Util.NamedWindows (getName)
+import Control.Applicative ((<$>))
import Control.Monad (when)
import Data.Bits (testBit)
import Data.IORef
import Data.List ((\\), delete)
-import Data.Maybe (listToMaybe)
+import Data.Maybe (listToMaybe, maybeToList)
import qualified Data.Set as S
import Foreign (unsafePerformIO)
@@ -182,10 +183,14 @@ withUrgencyHookC :: (LayoutClass l Window, UrgencyHook h) =>
h -> (WithUrgencyHook h -> WithUrgencyHook h) -> XConfig l
-> XConfig (HandleEvent (WithUrgencyHook h) l)
withUrgencyHookC hook hookMod conf = conf {
- layoutHook = eventHook (hookMod $ WithUrgencyHook hook Visible) $ layoutHook conf,
- logHook = removeVisiblesFromUrgents >> logHook conf
+ layoutHook = eventHook withUrgency $ layoutHook conf,
+ logHook = cleanupUrgents sw >> logHook conf
}
+ where withUrgency@(WithUrgencyHook _ sw) = hookMod $ WithUrgencyHook hook Visible
+-- | See 'withUrgencyHookC' for an example use. 'suppressWhen' is a global configuration
+-- option, applicable to all urgency hooks, whereas the stuff inside the @{ ... }@ is
+-- type-specific.
suppressWhen :: UrgencyHook h => SuppressWhen -> WithUrgencyHook h -> WithUrgencyHook h
suppressWhen sw (WithUrgencyHook hook _) = WithUrgencyHook hook sw
@@ -197,13 +202,6 @@ data SuppressWhen = Visible -- ^ the window is currently visible
| Never -- ^ ... aww, heck, go ahead and bug me, just in case.
deriving (Read, Show)
--- | The logHook action used by 'withUrgencyHook'.
-removeVisiblesFromUrgents :: X ()
-removeVisiblesFromUrgents = do
- visibles <- gets mapped
- adjustUrgents (\\ (S.toList visibles))
--- TODO: ^ should be based on suppressWhen
-
-- | Focuses the most recently urgent window. Good for what ails ya -- I mean, your keybindings.
-- Example keybinding:
--
@@ -211,7 +209,7 @@ removeVisiblesFromUrgents = do
focusUrgent :: X ()
focusUrgent = withUrgents $ flip whenJust (windows . W.focusWindow) . listToMaybe
--- Stores the global set of all urgent windows, across workspaces. Not exported -- use
+-- | Stores the global set of all urgent windows, across workspaces. Not exported -- use
-- 'readUrgents' or 'withUrgents' instead.
{-# NOINLINE urgents #-}
urgents :: IORef [Window]
@@ -268,14 +266,22 @@ adjustUrgents f = io $ modifyIORef urgents f
callUrgencyHook :: UrgencyHook h => WithUrgencyHook h -> Window -> X ()
callUrgencyHook (WithUrgencyHook hook sw) w =
- whenX (not `fmap` shouldSuppress sw w)
+ whenX (not <$> shouldSuppress sw w)
(userCode $ urgencyHook hook w)
shouldSuppress :: SuppressWhen -> Window -> X Bool
-shouldSuppress Visible w = gets $ S.member w . mapped
-shouldSuppress OnScreen w = gets $ elem w . W.index . windowset
-shouldSuppress Focused w = gets $ maybe False (w ==) . W.peek . windowset
-shouldSuppress Never _ = return False
+shouldSuppress sw w = elem w <$> suppressibleWindows sw
+
+cleanupUrgents :: SuppressWhen -> X ()
+cleanupUrgents sw = do
+ suppressibles <- suppressibleWindows sw
+ adjustUrgents (\\ suppressibles)
+
+suppressibleWindows :: SuppressWhen -> X [Window]
+suppressibleWindows Visible = gets $ S.toList . mapped
+suppressibleWindows OnScreen = gets $ W.index . windowset
+suppressibleWindows Focused = gets $ maybeToList . W.peek . windowset
+suppressibleWindows Never = return []
--------------------------------------------------------------------------------
-- Urgency Hooks