aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Hooks/ManageHelpers.hs
diff options
context:
space:
mode:
authorxmonad-contrib <xmonad-contrib@hexago.nl>2008-01-01 18:44:46 +0100
committerxmonad-contrib <xmonad-contrib@hexago.nl>2008-01-01 18:44:46 +0100
commita3d481a9c29e0ab4c57cb9691d937bea24c56b09 (patch)
tree530fcc326fd73767f887694df018944205ed810c /XMonad/Hooks/ManageHelpers.hs
parent68909d8a174fac503e68dc7f2174a39c9d4c9e4e (diff)
downloadXMonadContrib-a3d481a9c29e0ab4c57cb9691d937bea24c56b09.tar.gz
XMonadContrib-a3d481a9c29e0ab4c57cb9691d937bea24c56b09.tar.xz
XMonadContrib-a3d481a9c29e0ab4c57cb9691d937bea24c56b09.zip
expands the EDSL for performing actions on windows
This patch adds a few types of relationships and operators for managing windows with rules. It provides grouping operators so the X action can access the quantifier that was matched or not matched. It provides a formalism for predicates that work in both grouping and non grouping rules. It could do with some classes, so that there are fewer operators that always do the Right Thing (TM), but the Haskell Type system currently has some problems resolving types. Since I don't know enough about these high level things, it would be hard to create a GHC patch just to make it all work. darcs-hash:20080101174446-cfbce-3367d42b5411b92083a0e95cfc91d2e79770c527.gz
Diffstat (limited to 'XMonad/Hooks/ManageHelpers.hs')
-rw-r--r--XMonad/Hooks/ManageHelpers.hs84
1 files changed, 65 insertions, 19 deletions
diff --git a/XMonad/Hooks/ManageHelpers.hs b/XMonad/Hooks/ManageHelpers.hs
index df94cdd..a6dcc58 100644
--- a/XMonad/Hooks/ManageHelpers.hs
+++ b/XMonad/Hooks/ManageHelpers.hs
@@ -25,8 +25,11 @@
module XMonad.Hooks.ManageHelpers (
composeOne,
- (-?>),
+ (-?>), (/=?), (<==?), (</=?), (-->>), (-?>>),
isKDETrayWindow,
+ transientTo,
+ maybeToDefinite,
+ MaybeManageHook,
transience,
transience'
) where
@@ -37,10 +40,17 @@ import qualified XMonad.StackSet as W
import Data.Maybe
import Data.Monoid
+-- | A ManageHook that may or may not have been executed; the outcome is embedded in the Maybe
+type MaybeManageHook = Query (Maybe (Endo WindowSet))
+-- | A grouping type, which can hold the outcome of a predicate Query
+-- This is analogous to group types in regular expressions
+-- TODO create a better API for aggregating multiple Matches logically
+data Match a = Match Bool a
+
-- | 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 :: [MaybeManageHook] -> ManageHook
composeOne = foldr try idHook
where
try q z = do
@@ -49,15 +59,40 @@ composeOne = foldr try idHook
Just h -> return h
Nothing -> z
-infixr 0 -?>
+infixr 0 -?>, -->>, -?>>
+
+-- | q \/=? x. if the result of q equals x, return False
+(/=?) :: Eq a => Query a -> a -> Query Bool
+q /=? x = fmap (/= x) q
+
+-- | q <==? x. if the result of q equals x, return True grouped with q
+(<==?) :: Eq a => Query a -> a -> Query (Match a)
+q <==? x = fmap (`eq` x) q
+ where eq q' x' = Match (q' == x') q'
+
+-- | q <\/=? x. if the result of q notequals x, return True grouped with q
+(</=?) :: Eq a => Query a -> a -> Query (Match a)
+q </=? x = fmap (`neq` x) q
+ where neq q' x' = Match (q' /= x') q'
+
-- | 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))
+(-?>) :: Query Bool -> ManageHook -> MaybeManageHook
p -?> f = do
x <- p
if x then fmap Just f else return Nothing
+-- | A helper operator for use in 'composeAll'. It takes a condition and a function taking a grouped datum to action. If 'p' is true, it executes the resulting action.
+(-->>) :: Query (Match a) -> (a -> ManageHook) -> ManageHook
+p -->> f = do Match b m <- p
+ if b then (f m) else mempty
+
+-- | A helper operator for use in 'composeOne'. It takes a condition and a function taking a groupdatum to action. If 'p' is true, it executes the resulting action. If it fails, it returns 'Nothing' from the 'Query' so 'composeOne' will go on and try the next rule.
+(-?>>) :: Query (Match a) -> (a -> ManageHook) -> MaybeManageHook
+p -?>> f = do Match b m <- p
+ if b then fmap Just (f m) else return Nothing
+
-- | A predicate to check whether a window is a KDE system tray icon.
isKDETrayWindow :: Query Bool
isKDETrayWindow = ask >>= \w -> liftX $ do
@@ -68,19 +103,30 @@ isKDETrayWindow = ask >>= \w -> liftX $ do
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'.
+-- | A predicate to check whether a window is Transient.
+-- It holds the result which might be the window it is transient to
+-- or it might be 'Nothing'.
+transientTo :: Query (Maybe Window)
+transientTo = do w <- ask
+ d <- (liftX . asks) display
+ liftIO $ getTransientForHint d w
+
+-- | A convenience 'MaybeManageHook' that will check to see if a window
+-- is transient, and then move it to it's parent.
+transience :: MaybeManageHook
+transience = transientTo </=? Nothing
+ -?>> move
+ where move :: Maybe Window -> ManageHook
+ move mw = do
+ case mw of
+ Just w -> do return . Endo $ \s ->
+ maybe s (`W.shift` s) (W.findTag w s)
+ Nothing -> do return . Endo $ \s -> s
+
+-- | 'transience' set to a 'ManageHook'
transience' :: ManageHook
-transience' = fmap (fromMaybe mempty) transience
+transience' = maybeToDefinite transience
+
+-- | converts 'MaybeManageHook's to 'ManageHook's
+maybeToDefinite :: MaybeManageHook -> ManageHook
+maybeToDefinite = fmap (fromMaybe mempty)