aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorLukas Mai <l.mai@web.de>2007-12-11 19:30:40 +0100
committerLukas Mai <l.mai@web.de>2007-12-11 19:30:40 +0100
commit7986238a42c1100084e1f5525b42b8cecc30634a (patch)
tree5866e0a3708868b55d25757f277289610a523d25 /XMonad
parent47c8349cc9945be38ed29c244094c0f6e175c4fd (diff)
downloadXMonadContrib-7986238a42c1100084e1f5525b42b8cecc30634a.tar.gz
XMonadContrib-7986238a42c1100084e1f5525b42b8cecc30634a.tar.xz
XMonadContrib-7986238a42c1100084e1f5525b42b8cecc30634a.zip
new XMonad.Hooks.ManageHelpers module
darcs-hash:20071211183040-462cf-f8e47e21202ddcc60bde210469693fe70d08c337.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Hooks/ManageHelpers.hs86
1 files changed, 86 insertions, 0 deletions
diff --git a/XMonad/Hooks/ManageHelpers.hs b/XMonad/Hooks/ManageHelpers.hs
new file mode 100644
index 0000000..df94cdd
--- /dev/null
+++ b/XMonad/Hooks/ManageHelpers.hs
@@ -0,0 +1,86 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Hooks.ManageHelpers
+-- Copyright : (c) Lukas Mai
+-- License : BSD
+--
+-- Maintainer : Lukas Mai <l.mai@web.de>
+-- Stability : unstable
+-- Portability : unportable
+--
+-- This module provides helper functions to be used in @manageHook@. Here's how you
+-- might use this:
+--
+-- > import XMonad.Hooks.ManageHelpers
+-- > main =
+-- > xmonad defaultConfig{
+-- > ...
+-- > manageHook = composeOne [
+-- > isKDETrayWindow -?> doIgnore,
+-- > transience,
+-- > resource =? "stalonetray" -?> doIgnore
+-- > ],
+-- > ...
+-- > }
+
+module XMonad.Hooks.ManageHelpers (
+ composeOne,
+ (-?>),
+ isKDETrayWindow,
+ transience,
+ transience'
+) where
+
+import XMonad
+import qualified XMonad.StackSet as W
+
+import Data.Maybe
+import Data.Monoid
+
+-- | An alternative 'ManageHook' composer. Unlike 'composeAll' it stops as soon as
+-- a candidate returns a 'Just' value, effectively running only the first match
+-- (whereas 'composeAll' continues and executes all matching rules).
+composeOne :: [Query (Maybe (Endo WindowSet))] -> ManageHook
+composeOne = foldr try idHook
+ where
+ try q z = do
+ x <- q
+ case x of
+ Just h -> return h
+ Nothing -> z
+
+infixr 0 -?>
+-- | A helper operator for use in 'composeOne'. It takes a condition and an action;
+-- if the condition fails, it returns 'Nothing' from the 'Query' so 'composeOne' will
+-- go on and try the next rule.
+(-?>) :: Query Bool -> Query (Endo WindowSet) -> Query (Maybe (Endo WindowSet))
+p -?> f = do
+ x <- p
+ if x then fmap Just f else return Nothing
+
+-- | A predicate to check whether a window is a KDE system tray icon.
+isKDETrayWindow :: Query Bool
+isKDETrayWindow = ask >>= \w -> liftX $ do
+ dpy <- asks display
+ kde_tray <- getAtom "_KDE_NET_WM_SYSTEM_TRAY_WINDOW_FOR"
+ r <- io $ getWindowProperty32 dpy kde_tray w
+ return $ case r of
+ Just [_] -> True
+ _ -> False
+
+-- | A special rule that moves transient windows to the workspace of their
+-- associated primary windows.
+transience :: Query (Maybe (Endo WindowSet))
+transience = do
+ w <- ask
+ d <- (liftX . asks) display
+ x <- liftIO $ getTransientForHint d w
+ case x of
+ Nothing -> return Nothing
+ Just w' -> do
+ return . Just . Endo $ \s ->
+ maybe s (`W.shift` s) (W.findTag w' s)
+
+-- | Like 'transience' but with a type that can be used in 'composeAll'.
+transience' :: ManageHook
+transience' = fmap (fromMaybe mempty) transience