{-# LANGUAGE ViewPatterns #-}

{- |
Module      :  XMonad.Actions.WindowGo
Description :  Operations for raising (traveling to) windows.
License     :  Public domain

Maintainer  :  <gwern0@gmail.com>
Stability   :  unstable
Portability :  unportable

Defines a few convenient operations for raising (traveling to) windows based on XMonad's Query
monad, such as 'runOrRaise'. runOrRaise will run a shell command unless it can
find a specified window; you would use this to automatically travel to your
Firefox or Emacs session, or start a new one (for example), instead of trying to
remember where you left it or whether you still have one running. -}

module XMonad.Actions.WindowGo (
                 -- * Usage
                 -- $usage
                 raise,
                 raiseNext,
                 runOrRaise,
                 runOrRaiseNext,
                 raiseMaybe,
                 raiseNextMaybe,
                 raiseNextMaybeCustomFocus,

                 raiseBrowser,
                 raiseEditor,
                 runOrRaiseAndDo,
                 runOrRaiseMaster,
                 raiseAndDo,
                 raiseMaster,

                 ifWindows,
                 ifWindow,
                 raiseHook,
                 module XMonad.ManageHook
                ) where

import qualified Data.List as L (nub,sortBy)
import XMonad.Prelude
import XMonad (Query(), X(), ManageHook, WindowSet, withWindowSet, runQuery, liftIO, ask)
import Graphics.X11 (Window)
import XMonad.ManageHook
import XMonad.Operations (windows)
import XMonad.Prompt.Shell (getBrowser, getEditor)
import qualified XMonad.StackSet as W (peek, swapMaster, focusWindow, workspaces, StackSet, Workspace, integrate', tag, stack)
import XMonad.Util.Run (safeSpawnProg)
{- $usage

Import the module into your @~\/.xmonad\/xmonad.hs@:

> import XMonad.Actions.WindowGo

and define appropriate key bindings:

> , ((modm .|. shiftMask, xK_g), raise (className =? "Firefox"))
> , ((modm .|. shiftMask, xK_b), runOrRaise "firefox" (className =? "Firefox"))

(Note that Firefox v3 and up have a class-name of \"Firefox\" and \"Navigator\";
lower versions use other classnames such as \"Firefox-bin\". Either choose the
appropriate one, or cover your bases by using instead something like:

> (className =? "Firefox" <||> className =? "Firefox-bin")

For detailed instructions on editing your key bindings, see
"XMonad.Doc.Extending#Editing_key_bindings". -}

-- | Get the list of workspaces sorted by their tag
workspacesSorted :: Ord i => W.StackSet i l a s sd -> [W.Workspace i l a]
workspacesSorted :: forall i l a s sd.
Ord i =>
StackSet i l a s sd -> [Workspace i l a]
workspacesSorted StackSet i l a s sd
s = (Workspace i l a -> Workspace i l a -> Ordering)
-> [Workspace i l a] -> [Workspace i l a]
forall a. (a -> a -> Ordering) -> [a] -> [a]
L.sortBy (\Workspace i l a
u Workspace i l a
t -> Workspace i l a -> i
forall i l a. Workspace i l a -> i
W.tag Workspace i l a
u i -> i -> Ordering
forall a. Ord a => a -> a -> Ordering
`compare` Workspace i l a -> i
forall i l a. Workspace i l a -> i
W.tag Workspace i l a
t) ([Workspace i l a] -> [Workspace i l a])
-> [Workspace i l a] -> [Workspace i l a]
forall a b. (a -> b) -> a -> b
$ StackSet i l a s sd -> [Workspace i l a]
forall i l a s sd. StackSet i l a s sd -> [Workspace i l a]
W.workspaces StackSet i l a s sd
s

-- | Get a list of all windows in the 'StackSet' with an absolute ordering of workspaces
allWindowsSorted :: Ord i => Eq a => W.StackSet i l a s sd -> [a]
allWindowsSorted :: forall i a l s sd. (Ord i, Eq a) => StackSet i l a s sd -> [a]
allWindowsSorted = [a] -> [a]
forall a. Eq a => [a] -> [a]
L.nub ([a] -> [a])
-> (StackSet i l a s sd -> [a]) -> StackSet i l a s sd -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Workspace i l a -> [a]) -> [Workspace i l a] -> [a]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Maybe (Stack a) -> [a]
forall a. Maybe (Stack a) -> [a]
W.integrate' (Maybe (Stack a) -> [a])
-> (Workspace i l a -> Maybe (Stack a)) -> Workspace i l a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Workspace i l a -> Maybe (Stack a)
forall i l a. Workspace i l a -> Maybe (Stack a)
W.stack) ([Workspace i l a] -> [a])
-> (StackSet i l a s sd -> [Workspace i l a])
-> StackSet i l a s sd
-> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackSet i l a s sd -> [Workspace i l a]
forall i l a s sd.
Ord i =>
StackSet i l a s sd -> [Workspace i l a]
workspacesSorted

-- | If windows that satisfy the query exist, apply the supplied
-- function to them, otherwise run the action given as
-- second parameter.
ifWindows :: Query Bool -> ([Window] -> X ()) -> X () -> X ()
ifWindows :: Query Bool -> ([Window] -> X ()) -> X () -> X ()
ifWindows Query Bool
qry [Window] -> X ()
f X ()
el = (WindowSet -> X ()) -> X ()
forall a. (WindowSet -> X a) -> X a
withWindowSet ((WindowSet -> X ()) -> X ()) -> (WindowSet -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \WindowSet
wins -> do
  [Window]
matches <- (Window -> X Bool) -> [Window] -> X [Window]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (Query Bool -> Window -> X Bool
forall a. Query a -> Window -> X a
runQuery Query Bool
qry) ([Window] -> X [Window]) -> [Window] -> X [Window]
forall a b. (a -> b) -> a -> b
$ WindowSet -> [Window]
forall i a l s sd. (Ord i, Eq a) => StackSet i l a s sd -> [a]
allWindowsSorted WindowSet
wins
  case [Window]
matches of
    [] -> X ()
el
    [Window]
ws -> [Window] -> X ()
f [Window]
ws

-- | The same as ifWindows, but applies a ManageHook to the first match
-- instead and discards the other matches
ifWindow :: Query Bool -> ManageHook -> X () -> X ()
ifWindow :: Query Bool -> Query (Endo WindowSet) -> X () -> X ()
ifWindow Query Bool
qry Query (Endo WindowSet)
mh = Query Bool -> ([Window] -> X ()) -> X () -> X ()
ifWindows Query Bool
qry ((WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (Endo WindowSet -> WindowSet -> WindowSet)
-> Endo WindowSet
-> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Endo WindowSet -> WindowSet -> WindowSet
forall a. Endo a -> a -> a
appEndo (Endo WindowSet -> X ())
-> ([Window] -> X (Endo WindowSet)) -> [Window] -> X ()
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Query (Endo WindowSet) -> Window -> X (Endo WindowSet)
forall a. Query a -> Window -> X a
runQuery Query (Endo WindowSet)
mh (Window -> X (Endo WindowSet))
-> ([Window] -> Window) -> [Window] -> X (Endo WindowSet)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Window] -> Window
forall a. [a] -> a
head)

{- | 'action' is an executable to be run via 'safeSpawnProg' (of "XMonad.Util.Run") if the Window cannot be found.
   Presumably this executable is the same one that you were looking for.
   Note that this does not go through the shell. If you wish to run an arbitrary IO action
   (such as 'spawn', which will run its String argument through the shell), then you will want to use
   'raiseMaybe' directly. -}
runOrRaise :: String -> Query Bool -> X ()
runOrRaise :: WorkspaceId -> Query Bool -> X ()
runOrRaise = X () -> Query Bool -> X ()
raiseMaybe (X () -> Query Bool -> X ())
-> (WorkspaceId -> X ()) -> WorkspaceId -> Query Bool -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WorkspaceId -> X ()
forall (m :: * -> *). MonadIO m => WorkspaceId -> m ()
safeSpawnProg

-- | See 'raiseMaybe'. If the Window can't be found, quietly give up and do nothing.
raise :: Query Bool -> X ()
raise :: Query Bool -> X ()
raise = X () -> Query Bool -> X ()
raiseMaybe (X () -> Query Bool -> X ()) -> X () -> Query Bool -> X ()
forall a b. (a -> b) -> a -> b
$ () -> X ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

{- | 'raiseMaybe' queries all Windows based on a boolean provided by the
   user. Currently, there are 3 such useful booleans defined in
   "XMonad.ManageHook": 'title', 'resource', 'className'. Each one tests based pretty
   much as you would think. ManageHook also defines several operators, the most
   useful of which is (=?). So a useful test might be finding a @Window@ whose
   class is Firefox. Firefox 3 declares the class \"Firefox\", so you'd want to
   pass in a boolean like @(className =? \"Firefox\")@.

   If the boolean returns @True@ on one or more windows, then XMonad will quickly
   make visible the first result. If no @Window@ meets the criteria, then the
   first argument comes into play.

   The first argument is an arbitrary IO function which will be executed if the
   tests fail. This is what enables 'runOrRaise' to use 'raiseMaybe': it simply runs
   the desired program if it isn't found. But you don't have to do that. Maybe
   you want to do nothing if the search fails (the definition of 'raise'), or
   maybe you want to write to a log file, or call some prompt function, or
   something crazy like that. This hook gives you that flexibility. You can do
   some cute things with this hook. Suppose you want to do the same thing for
   Mutt which you just did for Firefox - but Mutt runs inside a terminal window?
   No problem: you search for a terminal window calling itself \"mutt\", and if
   there isn't you run a terminal with a command to run Mutt! Here's an example
   (borrowing 'runInTerm' from "XMonad.Util.Run"):

  > , ((modm, xK_m), raiseMaybe (runInTerm "-title mutt" "mutt") (title =? "mutt"))
-}
raiseMaybe :: X () -> Query Bool -> X ()
raiseMaybe :: X () -> Query Bool -> X ()
raiseMaybe X ()
f Query Bool
qry = Query Bool -> Query (Endo WindowSet) -> X () -> X ()
ifWindow Query Bool
qry Query (Endo WindowSet)
raiseHook X ()
f

-- | A manage hook that raises the window.
raiseHook :: ManageHook
raiseHook :: Query (Endo WindowSet)
raiseHook = Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask Query Window
-> (Window -> Query (Endo WindowSet)) -> Query (Endo WindowSet)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (WindowSet -> WindowSet) -> Query (Endo WindowSet)
forall s. (s -> s) -> Query (Endo s)
doF ((WindowSet -> WindowSet) -> Query (Endo WindowSet))
-> (Window -> WindowSet -> WindowSet)
-> Window
-> Query (Endo WindowSet)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Window -> WindowSet -> WindowSet
forall s a i l sd.
(Eq s, Eq a, Eq i) =>
a -> StackSet i l a s sd -> StackSet i l a s sd
W.focusWindow

-- | See 'runOrRaise' and 'raiseNextMaybe'. Version that allows cycling through matches.
runOrRaiseNext :: String -> Query Bool -> X ()
runOrRaiseNext :: WorkspaceId -> Query Bool -> X ()
runOrRaiseNext = X () -> Query Bool -> X ()
raiseNextMaybe (X () -> Query Bool -> X ())
-> (WorkspaceId -> X ()) -> WorkspaceId -> Query Bool -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WorkspaceId -> X ()
forall (m :: * -> *). MonadIO m => WorkspaceId -> m ()
safeSpawnProg

-- | See 'raise' and 'raiseNextMaybe'. Version that allows cycling through matches.
raiseNext :: Query Bool -> X ()
raiseNext :: Query Bool -> X ()
raiseNext = X () -> Query Bool -> X ()
raiseNextMaybe (X () -> Query Bool -> X ()) -> X () -> Query Bool -> X ()
forall a b. (a -> b) -> a -> b
$ () -> X ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

{- | See 'raiseMaybe'.
     'raiseNextMaybe' is an alternative version that allows cycling
     through the matching windows. If the focused window matches the
     query the next matching window is raised. If no matches are found
     the function f is executed. -}
raiseNextMaybe :: X () -> Query Bool -> X ()
raiseNextMaybe :: X () -> Query Bool -> X ()
raiseNextMaybe = (Window -> WindowSet -> WindowSet) -> X () -> Query Bool -> X ()
raiseNextMaybeCustomFocus Window -> WindowSet -> WindowSet
forall s a i l sd.
(Eq s, Eq a, Eq i) =>
a -> StackSet i l a s sd -> StackSet i l a s sd
W.focusWindow

{- | See 'raiseMaybe' and 'raiseNextMaybe'.
     In addition to all of the options offered by 'raiseNextMaybe'
     'raiseNextMaybeCustomFocus' allows the user to supply the function that
     should be used to shift the focus to any window that is found. -}
raiseNextMaybeCustomFocus :: (Window -> WindowSet -> WindowSet) -> X() -> Query Bool -> X()
raiseNextMaybeCustomFocus :: (Window -> WindowSet -> WindowSet) -> X () -> Query Bool -> X ()
raiseNextMaybeCustomFocus Window -> WindowSet -> WindowSet
focusFn X ()
f Query Bool
qry = (([Window] -> X ()) -> X () -> X ())
-> X () -> ([Window] -> X ()) -> X ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Query Bool -> ([Window] -> X ()) -> X () -> X ()
ifWindows Query Bool
qry) X ()
f (([Window] -> X ()) -> X ()) -> ([Window] -> X ()) -> X ()
forall a b. (a -> b) -> a -> b
$ \[Window]
ws -> do
  Maybe Window
foc <- (WindowSet -> X (Maybe Window)) -> X (Maybe Window)
forall a. (WindowSet -> X a) -> X a
withWindowSet ((WindowSet -> X (Maybe Window)) -> X (Maybe Window))
-> (WindowSet -> X (Maybe Window)) -> X (Maybe Window)
forall a b. (a -> b) -> a -> b
$ Maybe Window -> X (Maybe Window)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Window -> X (Maybe Window))
-> (WindowSet -> Maybe Window) -> WindowSet -> X (Maybe Window)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WindowSet -> Maybe Window
forall i l a s sd. StackSet i l a s sd -> Maybe a
W.peek
  case Maybe Window
foc of
    Just Window
w | Window
w Window -> [Window] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Window]
ws ->
        let ([Window] -> NonEmpty Window
forall a. HasCallStack => [a] -> NonEmpty a
notEmpty -> Window
_ :| ([Window] -> NonEmpty Window
forall a. HasCallStack => [a] -> NonEmpty a
notEmpty -> Window
y :| [Window]
_)) = (Window -> Bool) -> [Window] -> [Window]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Window -> Window -> Bool
forall a. Eq a => a -> a -> Bool
/=Window
w) ([Window] -> [Window]) -> [Window] -> [Window]
forall a b. (a -> b) -> a -> b
$ [Window] -> [Window]
forall a. [a] -> [a]
cycle [Window]
ws
            -- cannot fail to match
        in (WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> (WindowSet -> WindowSet) -> X ()
forall a b. (a -> b) -> a -> b
$ Window -> WindowSet -> WindowSet
focusFn Window
y
    Maybe Window
_ -> (WindowSet -> WindowSet) -> X ()
windows ((WindowSet -> WindowSet) -> X ())
-> ([Window] -> WindowSet -> WindowSet) -> [Window] -> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Window -> WindowSet -> WindowSet
focusFn (Window -> WindowSet -> WindowSet)
-> ([Window] -> Window) -> [Window] -> WindowSet -> WindowSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Window] -> Window
forall a. [a] -> a
head ([Window] -> X ()) -> [Window] -> X ()
forall a b. (a -> b) -> a -> b
$ [Window]
ws

-- | Given a function which gets us a String, we try to raise a window with that classname,
--   or we then interpret that String as a executable name.
raiseVar :: IO String -> X ()
raiseVar :: IO WorkspaceId -> X ()
raiseVar IO WorkspaceId
getvar = IO WorkspaceId -> X WorkspaceId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO WorkspaceId
getvar X WorkspaceId -> (WorkspaceId -> X ()) -> X ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \WorkspaceId
var -> WorkspaceId -> Query Bool -> X ()
runOrRaise WorkspaceId
var ((WorkspaceId -> WorkspaceId)
-> Query WorkspaceId -> Query WorkspaceId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Char -> Char) -> WorkspaceId -> WorkspaceId
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower) Query WorkspaceId
className Query WorkspaceId -> WorkspaceId -> Query Bool
forall a. Eq a => Query a -> a -> Query Bool
=? WorkspaceId
var)

{- | 'raiseBrowser' and 'raiseEditor' grab $BROWSER and $EDITOR respectively and they either
     take you to the specified program's window, or they try to run it. This is most useful
     if your variables are simple and look like \"firefox\" or \"emacs\". -}
raiseBrowser, raiseEditor :: X ()
raiseBrowser :: X ()
raiseBrowser = IO WorkspaceId -> X ()
raiseVar IO WorkspaceId
getBrowser
raiseEditor :: X ()
raiseEditor  = IO WorkspaceId -> X ()
raiseVar IO WorkspaceId
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 :: X () -> Query Bool -> (Window -> X ()) -> X ()
raiseAndDo X ()
f Query Bool
qry Window -> X ()
after = Query Bool -> Query (Endo WindowSet) -> X () -> X ()
ifWindow Query Bool
qry (Query (Endo WindowSet)
afterRaise Query (Endo WindowSet)
-> Query (Endo WindowSet) -> Query (Endo WindowSet)
forall a. Monoid a => a -> a -> a
`mappend` Query (Endo WindowSet)
raiseHook) X ()
f
    where afterRaise :: Query (Endo WindowSet)
afterRaise = Query Window
forall r (m :: * -> *). MonadReader r m => m r
ask Query Window
-> (Window -> Query (Endo WindowSet)) -> Query (Endo WindowSet)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Query () -> Query (Endo WindowSet) -> Query (Endo WindowSet)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Query (Endo WindowSet)
forall m. Monoid m => m
idHook) (Query () -> Query (Endo WindowSet))
-> (Window -> Query ()) -> Window -> Query (Endo WindowSet)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. X () -> Query ()
forall a. X a -> Query a
liftX (X () -> Query ()) -> (Window -> X ()) -> Window -> Query ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Window -> X ()
after

{- | If a window matching the second argument is found, the window is focused and
     the third argument is called;
     otherwise, the first argument is called. -}
runOrRaiseAndDo :: String -> Query Bool -> (Window -> X ()) -> X ()
runOrRaiseAndDo :: WorkspaceId -> Query Bool -> (Window -> X ()) -> X ()
runOrRaiseAndDo = X () -> Query Bool -> (Window -> X ()) -> X ()
raiseAndDo (X () -> Query Bool -> (Window -> X ()) -> X ())
-> (WorkspaceId -> X ())
-> WorkspaceId
-> Query Bool
-> (Window -> X ())
-> X ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WorkspaceId -> X ()
forall (m :: * -> *). MonadIO m => WorkspaceId -> m ()
safeSpawnProg

{- | 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 :: X () -> Query Bool -> X ()
raiseMaster X ()
raisef Query Bool
thatUserQuery = X () -> Query Bool -> (Window -> X ()) -> X ()
raiseAndDo X ()
raisef Query Bool
thatUserQuery (\Window
_ -> (WindowSet -> WindowSet) -> X ()
windows WindowSet -> WindowSet
forall i l a s sd. StackSet i l a s sd -> StackSet i l a s sd
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 :: WorkspaceId -> Query Bool -> X ()
runOrRaiseMaster WorkspaceId
run Query Bool
query = WorkspaceId -> Query Bool -> (Window -> X ()) -> X ()
runOrRaiseAndDo WorkspaceId
run Query Bool
query (\Window
_ -> (WindowSet -> WindowSet) -> X ()
windows WindowSet -> WindowSet
forall i l a s sd. StackSet i l a s sd -> StackSet i l a s sd
W.swapMaster)