aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorallbery.b <allbery.b@gmail.com>2015-04-14 17:36:57 +0200
committerallbery.b <allbery.b@gmail.com>2015-04-14 17:36:57 +0200
commite6af87d4621897713957f71a80aa5141613964de (patch)
treea5254cb2af1fee3c09af22cb95f899151fadeaa0
parent185922730d91c48a66ce6659e769d14d02b325b0 (diff)
downloadXMonadContrib-e6af87d4621897713957f71a80aa5141613964de.tar.gz
XMonadContrib-e6af87d4621897713957f71a80aa5141613964de.tar.xz
XMonadContrib-e6af87d4621897713957f71a80aa5141613964de.zip
dynamicproperty
Ignore-this: b15d78f8970d08b252ead72a19709b06 Run a ManageHook from handleEventHook when a window property changes. You would use this to match e.g. browser windows whose title is not "final" until after the on-load hooks of the loaded document complete. darcs-hash:20150414153657-181ff-1a5b0740ebcbcbcc5ca8745b8548a32ab89f369d.gz
-rw-r--r--XMonad/Hooks/DynamicProperty.hs71
-rw-r--r--xmonad-contrib.cabal1
2 files changed, 72 insertions, 0 deletions
diff --git a/XMonad/Hooks/DynamicProperty.hs b/XMonad/Hooks/DynamicProperty.hs
new file mode 100644
index 0000000..245df15
--- /dev/null
+++ b/XMonad/Hooks/DynamicProperty.hs
@@ -0,0 +1,71 @@
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Hooks.DynamicProperty
+-- Copyright : (c) Brandon S Allbery, 2015
+-- License : BSD3-style (see LICENSE)
+--
+-- Maintainer : allbery.b@gmail.com
+-- Stability : unstable
+-- Portability : not portable
+--
+-- Module to apply a ManageHook to an already-mapped window when a property
+-- changes. This would commonly be used to match browser windows by title,
+-- since the final title will only be set after (a) the window is mapped,
+-- (b) its document has been loaded, (c) all load-time scripts have run.
+-- (Don't blame browsers for this; it's inherent in HTML and the DOM. And
+-- changing title dynamically is explicitly permitted by ICCCM and EWMH;
+-- you don't really want to have your editor window umapped/remapped to
+-- show the current document and modified state in the titlebar, do you?)
+--
+-- This is a handleEventHook that triggers on a PropertyChange event. It
+-- currently ignores properties being removed, in part because you can't
+-- do anything useful in a ManageHook involving nonexistence of a property.
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Hooks.DynamicProperty where
+
+import XMonad
+import Data.Monoid
+import Control.Applicative
+import Control.Monad (when)
+
+-- |
+-- Run a 'ManageHook' when a specific property is changed on a window. Note
+-- that this will run on any window which changes the property, so you should
+-- be very specific in your 'MansgeHook' matching (lots of windows change
+-- their titles on the fly!):
+--
+-- dynamicPropertyChange "WM_NAME" (className =? "Iceweasel" <&&> title =? "whatever" --> doShift "2")
+--
+-- Note that the fixity of (-->) won't allow it to be mixed with ($), so you
+-- can't use the obvious $ shorthand.
+--
+-- > dynamicPropertyChange "WM_NAME" $ title =? "Foo" --> doFloat -- won't work!
+--
+-- Consider instead phrasing it like any
+-- other 'ManageHook':
+--
+-- > , handleEventHook = dynamicPropertyChange "WM_NAME" myDynHook <+> handleEventHook baseConfig
+-- >
+-- > {- ... -}
+-- >
+-- > myDynHook = composeAll [...]
+--
+dynamicPropertyChange :: String -> ManageHook -> Event -> X All
+dynamicPropertyChange prop hook PropertyEvent { ev_window = w, ev_atom = a, ev_propstate = ps } = do
+ pa <- getAtom prop
+ when (ps == propertyNewValue && a == pa) $ do
+ g <- appEndo <$> userCodeDef (Endo id) (runQuery hook w)
+ windows g
+ return (All False) -- so anything else also processes it
+dynamicPropertyChange _ _ _ = return (All False)
+
+-- | A shorthand for the most common case, dynamic titles
+dynamicTitle :: ManageHook -> Event -> X All
+-- strictly, this should also check _NET_WM_NAME. practically, both will
+-- change and each gets its own PropertyEvent, so we'd need to record that
+-- we saw the event for that window and ignore the second one. Instead, just
+-- trust that nobody sets only _NET_WM_NAME. (I'm sure this will prove false,
+-- since there's always someone who can't bother being compliant.)
+dynamicTitle = dynamicPropertyChange "WM_NAME"
diff --git a/xmonad-contrib.cabal b/xmonad-contrib.cabal
index ec437fc..cc437c6 100644
--- a/xmonad-contrib.cabal
+++ b/xmonad-contrib.cabal
@@ -164,6 +164,7 @@ library
XMonad.Hooks.DynamicBars
XMonad.Hooks.DynamicHooks
XMonad.Hooks.DynamicLog
+ XMonad.Hooks.DynamicProperty
XMonad.Hooks.DebugStack
XMonad.Hooks.EwmhDesktops
XMonad.Hooks.FadeInactive