aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/WindowGo.hs
diff options
context:
space:
mode:
authorseanmce33 <seanmce33@gmail.com>2008-09-12 20:48:30 +0200
committerseanmce33 <seanmce33@gmail.com>2008-09-12 20:48:30 +0200
commit77fbe236449437a590e4267f97bdd985246ff1b9 (patch)
treecc6d34edfb9af03302d3037822673cc94a0d5ea7 /XMonad/Actions/WindowGo.hs
parent836be86f1f31b074189cc525d51ed789bae51632 (diff)
downloadXMonadContrib-77fbe236449437a590e4267f97bdd985246ff1b9.tar.gz
XMonadContrib-77fbe236449437a590e4267f97bdd985246ff1b9.tar.xz
XMonadContrib-77fbe236449437a590e4267f97bdd985246ff1b9.zip
raiseMaster
darcs-hash:20080912184830-d2fc6-8dbaa909dd005ac7da2e7477d6dcc1b25c371047.gz
Diffstat (limited to 'XMonad/Actions/WindowGo.hs')
-rw-r--r--XMonad/Actions/WindowGo.hs44
1 files changed, 42 insertions, 2 deletions
diff --git a/XMonad/Actions/WindowGo.hs b/XMonad/Actions/WindowGo.hs
index e5e70e0..deb67ae 100644
--- a/XMonad/Actions/WindowGo.hs
+++ b/XMonad/Actions/WindowGo.hs
@@ -24,6 +24,10 @@ module XMonad.Actions.WindowGo (
raiseBrowser,
raiseEditor,
+ runOrRaiseAndDo,
+ runOrRaiseMaster,
+ raiseAndDo,
+ raiseMaster,
module XMonad.ManageHook
) where
@@ -33,8 +37,9 @@ import Data.Char (toLower)
import XMonad (Query(), X(), withWindowSet, spawn, runQuery, liftIO, focus)
import XMonad.ManageHook
import XMonad.Prompt.Shell (getBrowser, getEditor)
-import qualified XMonad.StackSet as W (allWindows, peek)
-
+import qualified XMonad.StackSet as W (allWindows, peek, swapMaster)
+import XMonad.Operations (windows)
+import Graphics.X11 (Window)
{- $usage
Import the module into your @~\/.xmonad\/xmonad.hs@:
@@ -134,3 +139,38 @@ raiseVar getvar = liftIO getvar >>= \var -> runOrRaise var (fmap (map toLower) c
raiseBrowser, raiseEditor :: X ()
raiseBrowser = raiseVar getBrowser
raiseEditor = raiseVar getEditor
+
+{- | if the window is found the window is focused and the third argument is called
+ otherwise, the first argument is called
+ See 'raiseMaster' for an example -}
+raiseAndDo :: X () -> Query Bool -> (Window -> X ())-> X ()
+raiseAndDo raisef thatUserQuery afterRaise = withWindowSet $ \s -> do
+ maybeResult <- filterM (runQuery thatUserQuery) (W.allWindows s)
+ case maybeResult of
+ [] -> raisef
+ (x:_) -> do
+ XMonad.focus x
+ afterRaise x
+
+{- | if the window is found the window is focused and the third argument is called
+ otherwise, raisef is called -}
+runOrRaiseAndDo :: String -> Query Bool -> (Window -> X ()) -> X ()
+runOrRaiseAndDo run query afterRaise = raiseAndDo (spawn run) query afterRaise
+
+
+{- | if the window is found the window is focused and set to master
+ otherwise, the first argument is called
+
+ raiseMaster (runInTerm \"-title ghci\" \"zsh -c \'ghci\'\") (title =? \"ghci\") -}
+raiseMaster :: X () -> Query Bool -> X ()
+raiseMaster raisef thatUserQuery = raiseAndDo raisef thatUserQuery (\_ -> windows W.swapMaster)
+
+{- | if the window is found the window is focused and set to master
+ otherwise, action is run
+
+ runOrRaiseMaster \"firefox\" (className =? \"Firefox\"))
+ -}
+runOrRaiseMaster :: String -> Query Bool -> X ()
+runOrRaiseMaster run query = runOrRaiseAndDo run query (\_ -> windows W.swapMaster)
+
+