From 45992336b3227ad3e0ec702f197303562502ed84 Mon Sep 17 00:00:00 2001 From: Braden Shepherdson Date: Fri, 25 Jul 2008 00:20:54 +0200 Subject: Added XMonad.Hooks.DynamicHooks Allows runtime creation and modification of ManageHooks. Also allows one-shot ManageHooks that are removed after the fire. Note that if several transient hooks fire at once, only the most recently defined is executed, and all are removed. darcs-hash:20080724222054-d53a8-91832dca40a6f0fe5799f6d0ca2033bb23c9dcc0.gz --- XMonad/Hooks/DynamicHooks.hs | 122 +++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 122 insertions(+) create mode 100644 XMonad/Hooks/DynamicHooks.hs (limited to 'XMonad/Hooks/DynamicHooks.hs') diff --git a/XMonad/Hooks/DynamicHooks.hs b/XMonad/Hooks/DynamicHooks.hs new file mode 100644 index 0000000..002853d --- /dev/null +++ b/XMonad/Hooks/DynamicHooks.hs @@ -0,0 +1,122 @@ +----------------------------------------------------------------------------- +-- | +-- Module : XMonad.Hooks.DynamicHooks +-- Copyright : (c) Braden Shepherdson 2008 +-- License : BSD-style (as xmonad) +-- +-- Maintainer : Braden.Shepherdson@gmail.com +-- Stability : unstable +-- Portability : unportable +-- +-- One-shot and permanent ManageHooks that can be updated at runtime. +-- +----------------------------------------------------------------------------- + +module XMonad.Hooks.DynamicHooks ( + -- * Usage + -- $usage + initDynamicHooks + ,dynamicMasterHook + ,addDynamicHook + ,updateDynamicHook + ,oneShotHook + ) where + +import XMonad +import System.IO + +import Data.List +import Data.Maybe (listToMaybe) +import Data.Monoid +import Data.IORef + +-- $usage +-- Provides two new kinds of 'ManageHooks' that can be defined at runtime. +-- +-- * One-shot 'ManageHooks' that are deleted after they execute. +-- +-- * Permanent 'ManageHooks' (unless you want to destroy them) +-- +-- Note that you will lose all dynamically defined 'ManageHook's when you @mod+q@! +-- If you want them to last, you should create them as normal in your @xmonad.hs@. +-- +-- First, you must execute 'initDynamicHooks' from 'main' in your @xmonad.hs@: +-- +-- > dynHooksRef <- initDynamicHooks +-- +-- and then pass this value to the other functions in this module. +-- +-- You also need to add the base 'ManageHook': +-- +-- > xmonad { manageHook = myManageHook <+> dynamicMasterHook dynHooksRef } +-- +-- You must include this @dynHooksRef@ value when using the functions in this +-- module: +-- +-- > xmonad { keys = myKeys `Data.Map.union` Data.Map.fromList +-- > [((modMask conf, xK_i), oneShotHook dynHooksRef +-- > "FFlaunchHook" (className =? "firefox") (doShift "3") +-- > >> spawn "firefox") +-- > ,((modMask conf, xK_u), addDynamicHook dynHooksRef +-- > (className =? "example" --> doFloat)) +-- > ,((modMask conf, xK_y), updatePermanentHook dynHooksRef +-- > (const idHook))) ] -- resets the permanent hook. +-- + +data DynamicHooks = DynamicHooks + { transients :: [(Query Bool, ManageHook)] + , permanent :: ManageHook } + + +-- | Creates the 'IORef' that stores the dynamically created 'ManageHook's. +initDynamicHooks :: IO (IORef DynamicHooks) +initDynamicHooks = newIORef (DynamicHooks { transients = [], + permanent = idHook }) + + +-- this hook is always executed, and the IORef's contents checked. +-- note that transient hooks are run second, therefore taking precedence +-- over permanent ones on matters such as which workspace to shift to. +-- doFloat and doIgnore are idempotent. +-- | Master 'ManageHook' that must be in your @xmonad.hs@ 'ManageHook'. +dynamicMasterHook :: IORef DynamicHooks -> ManageHook +dynamicMasterHook ref = return True --> + (ask >>= \w -> liftX (do + dh <- io $ readIORef ref + (Endo f) <- runQuery (permanent dh) w + ts <- mapM (\(q,a) -> runQuery q w >>= \x -> return (x,(q, a))) (transients dh) + let (ts',nts) = partition fst ts + gs <- mapM (flip runQuery w . snd . snd) ts' + let (Endo g) = maybe (Endo id) id $ listToMaybe gs + io $ writeIORef ref $ dh { transients = map snd nts } + return $ Endo $ f . g + )) + +-- | Appends the given 'ManageHook' to the permanent dynamic 'ManageHook'. +addDynamicHook :: IORef DynamicHooks -> ManageHook -> X () +addDynamicHook ref m = updateDynamicHook ref (<+> m) + + +-- | Modifies the permanent 'ManageHook' with an arbitrary function. +updateDynamicHook :: IORef DynamicHooks -> (ManageHook -> ManageHook) -> X () +updateDynamicHook ref f = + io $ modifyIORef ref $ \dh -> dh { permanent = f (permanent dh) } + + +-- | Creates a one-shot 'ManageHook'. Note that you have to specify the two +-- parts of the 'ManageHook' separately. Where you would usually write: +-- +-- > className =? "example" --> doFloat +-- +-- you must call 'oneShotHook' as +-- +-- > oneShotHook dynHooksRef (className =? "example) doFloat +-- +oneShotHook :: IORef DynamicHooks -> Query Bool -> ManageHook -> X () +oneShotHook ref q a = + io $ modifyIORef ref + $ \dh -> dh { transients = (q,a):(transients dh) } + + + + -- cgit v1.2.3