xmonad-contrib-0.17.1.9: Community-maintained extensions for xmonad
Copyrightsgf-dma 2016
Maintainersgf.dma@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010
Extensions
  • DerivingStrategies
  • DerivingVia
  • FlexibleContexts
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • GeneralizedNewtypeDeriving

XMonad.Hooks.Focus

Description

Extends XMonad.ManageHook EDSL to work on focused windows and current workspace.

Synopsis

Documentation

This module provides monad on top of Query monad providing additional information about new window:

  • workspace, where new window will appear;
  • focused window on workspace, where new window will appear;
  • current workspace;

And a property in extensible state:

  • is focus lock enabled? Focus lock instructs all library's FocusHook functions to not move focus or switch workspace.

Lifting operations for standard ManageHook EDSL combinators into FocusQuery monad allowing to run these combinators on focused window and common actions for keeping focus and/or workspace, switching focus and/or workspace are also provided.

Quick start.

I may use one of predefined configurations.

  1. The default window activation behavior (switch to workspace with activated window and switch focus to it) expressed using this module:

    import XMonad
    
    import XMonad.Hooks.EwmhDesktops
    import XMonad.Hooks.Focus
    
    main :: IO ()
    main = do
            let ah :: ManageHook
                ah = activateSwitchWs
                xcf = setEwmhActivateHook ah
                    . ewmh $ def{ modMask = mod4Mask }
            xmonad xcf
  2. Or i may move activated window to current workspace and switch focus to it:

            let ah :: ManageHook
                ah = activateOnCurrentWs
  3. Or move activated window to current workspace, but keep focus unchanged:

            let ah :: ManageHook
                ah = activateOnCurrentKeepFocus
  4. I may use regular ManageHook combinators for filtering, which windows may activate. E.g. activate all windows, except firefox:

            let ah :: ManageHook
                ah  = not <$> (className =? "Firefox" <||> className =? "Firefox-esr" <||> className =? "Iceweasel")
                        --> activateSwitchWs
  5. Or even use FocusHook combinators. E.g. activate all windows, unless xterm is focused on current workspace:

            let ah :: ManageHook
                ah  = manageFocus (not <$> focusedCur (className =? "XTerm")
                        --> liftQuery activateSwitchWs)

    or activate all windows, unless focused window on the workspace, where activated window is, is not a xterm:

            let ah :: ManageHook
                ah  = manageFocus (not <$> focused (className =? "XTerm")
                        --> liftQuery activateSwitchWs)

Defining FocusHook.

I may define my own FocusHook like:

   activateFocusHook :: FocusHook
   activateFocusHook = composeAll
           -- If 'gmrun' is focused on workspace, on which
           -- /activated window/ is, keep focus unchanged. But i
           -- may still switch workspace (thus, i use 'composeAll').
           -- See 'keepFocus' properties in the docs below.
           [ focused (className =? "Gmrun")
                           --> keepFocus
           -- Default behavior for activated windows: switch
           -- workspace and focus.
           , return True   --> switchWorkspace <> switchFocus
           ]

   newFocusHook :: FocusHook
   newFocusHook      = composeOne
           -- Always switch focus to 'gmrun'.
           [ new (className =? "Gmrun")        -?> switchFocus
           -- And always keep focus on 'gmrun'. Note, that
           -- another 'gmrun' will steal focus from already
           -- running one.
           , focused (className =? "Gmrun")    -?> keepFocus
           -- If firefox dialog prompt (e.g. master password
           -- prompt) is focused on current workspace and new
           -- window appears here too, keep focus unchanged
           -- (note, used predicates: @newOnCur <&&> focused@ is
           -- the same as @newOnCur <&&> focusedCur@, but is
           -- /not/ the same as just 'focusedCur' )
           , newOnCur <&&> focused
               ((className =? "Firefox" <||> className =? "Firefox-esr" <||> className =? "Iceweasel") <&&> isDialog)
                                               -?> keepFocus
           -- Default behavior for new windows: switch focus.
           , return True                       -?> switchFocus
           ]

And then use it:

   import XMonad
   import XMonad.Util.EZConfig

   import XMonad.Hooks.EwmhDesktops
   import XMonad.Hooks.ManageHelpers
   import XMonad.Hooks.Focus


   main :: IO ()
   main = do
           let newFh :: ManageHook
               newFh = manageFocus newFocusHook
               acFh :: ManageHook
               acFh = manageFocus activateFocusHook
               xcf = setEwmhActivateHook acFh
                   . ewmh $ def
                            { manageHook   = newFh <> manageHook def
                            , modMask      = mod4Mask
                            }
                       `additionalKeys` [((mod4Mask, xK_v), toggleLock)]
           xmonad xcf

Note:

  • mod4Mask+v key toggles focus lock (when enabled, neither focus nor workspace won't be switched).
  • I need XMonad.Hooks.EwmhDesktops module for enabling window activation.
  • FocusHook in manageHook will be called only for new windows.
  • FocusHook in setEwmhActivateHook will be called only for activated windows.

Alternatively, i may construct a single FocusHook for both new and activated windows and then just add it to both manageHook and setEwmhActivateHook:

           let fh :: Bool -> ManageHook
               fh activated = manageFocus $ composeOne
                       [ pure activated -?> activateFocusHook
                       , pure True      -?> newFocusHook
                       ]
               xcf = setEwmhActivateHook (fh True)
                   . ewmh $ def
                            { manageHook   = fh False <> manageHook def
                            , modMask      = mod4Mask
                            }
                       `additionalKeys` [((mod4Mask, xK_v), toggleLock)]

And more technical notes:

  • FocusHook will run many times, so it usually should not keep state or save results. Precisely, it may do anything, but it must be idempotent to operate properly.
  • FocusHook will see new window at workspace, where functions on the right from it in ManageHook monoid place it. In other words, in (Endo WindowSet) monoid i may see changes only from functions applied before (more to the right in function composition). Thus, it's better to add FocusHook the last.
  • FocusHook functions won't see window shift to another workspace made by function from FocusHook itself: new window workspace is determined before running FocusHook and even if later one of FocusHook functions moves window to another workspace, predicates (focused, newOn, etc) will still think new window is at workspace it was before. This can be worked around by splitting FocusHook into several different values and evaluating each one separately, like:

    (FH2 -- manageFocus --> MH2) <> (FH1 -- manageFocus --> MH1) <> ..

    E.g.

    manageFocus FH2 <> manageFocus FH1 <> ..

    now FH2 will see window shift made by FH1.

Another interesting example is moving all activated windows to current workspace by default, and applying FocusHook after:

   import XMonad
   import XMonad.Util.EZConfig

   import XMonad.Hooks.EwmhDesktops
   import XMonad.Hooks.ManageHelpers
   import XMonad.Hooks.Focus

   main :: IO ()
   main = do
           let fh :: Bool -> ManageHook
               fh activated = manageFocus $ composeOne
                       [ pure activated -?> (newOnCur --> keepFocus)
                       , pure True      -?> newFocusHook
                       ]
               xcf = setEwmhActivateHook (fh True <> activateOnCurrentWs)
                   . ewmh $ def
                            { manageHook = fh False <> manageHook def
                            , modMask    = mod4Mask
                            }
                       `additionalKeys` [((mod4Mask, xK_v), toggleLock)]
           xmonad xcf

   newFocusHook :: FocusHook
   newFocusHook      = composeOne
           -- Always switch focus to 'gmrun'.
           [ new (className =? "Gmrun")        -?> switchFocus
           -- And always keep focus on 'gmrun'. Note, that
           -- another 'gmrun' will steal focus from already
           -- running one.
           , focused (className =? "Gmrun")    -?> keepFocus
           -- If firefox dialog prompt (e.g. master password
           -- prompt) is focused on current workspace and new
           -- window appears here too, keep focus unchanged
           -- (note, used predicates: @newOnCur <&&> focused@ is
           -- the same as @newOnCur <&&> focusedCur@, but is
           -- /not/ the same as just 'focusedCur' )
           , newOnCur <&&> focused
               ((className =? "Firefox" <||> className =? "Firefox-esr" <||> className =? "Iceweasel") <&&> isDialog)
                                               -?> keepFocus
           -- Default behavior for new windows: switch focus.
           , return True                       -?> switchFocus
           ]

Note here:

  • i keep focus, when activated window appears on current workspace, in this example.
  • when pure activated -?> (newOnCur --> keepFocus) runs, activated window will be already on current workspace, thus, if i do not want to move some activated windows, i should filter them out before applying activateOnCurrentWs FocusHook.

FocusQuery.

 

data Focus Source #

Information about current workspace and focus.

Constructors

Focus 

Fields

Instances

Instances details
Show Focus Source # 
Instance details

Defined in XMonad.Hooks.Focus

Methods

showsPrec :: Int -> Focus -> ShowS #

show :: Focus -> String #

showList :: [Focus] -> ShowS #

Default Focus Source # 
Instance details

Defined in XMonad.Hooks.Focus

Methods

def :: Focus #

MonadReader Focus FocusQuery Source # 
Instance details

Defined in XMonad.Hooks.Focus

Methods

ask :: FocusQuery Focus #

local :: (Focus -> Focus) -> FocusQuery a -> FocusQuery a #

reader :: (Focus -> a) -> FocusQuery a #

newtype FocusLock Source #

Constructors

FocusLock 

Fields

Instances

Instances details
Show FocusLock Source # 
Instance details

Defined in XMonad.Hooks.Focus

ExtensionClass FocusLock Source # 
Instance details

Defined in XMonad.Hooks.Focus

toggleLock :: X () Source #

Toggle stored focus lock state.

focusLockOn :: X () Source #

Lock focus.

focusLockOff :: X () Source #

Unlock focus.

data FocusQuery a Source #

Monad on top of Query providing additional information about new window.

Instances

Instances details
MonadIO FocusQuery Source # 
Instance details

Defined in XMonad.Hooks.Focus

Methods

liftIO :: IO a -> FocusQuery a #

Applicative FocusQuery Source # 
Instance details

Defined in XMonad.Hooks.Focus

Methods

pure :: a -> FocusQuery a #

(<*>) :: FocusQuery (a -> b) -> FocusQuery a -> FocusQuery b #

liftA2 :: (a -> b -> c) -> FocusQuery a -> FocusQuery b -> FocusQuery c #

(*>) :: FocusQuery a -> FocusQuery b -> FocusQuery b #

(<*) :: FocusQuery a -> FocusQuery b -> FocusQuery a #

Functor FocusQuery Source # 
Instance details

Defined in XMonad.Hooks.Focus

Methods

fmap :: (a -> b) -> FocusQuery a -> FocusQuery b #

(<$) :: a -> FocusQuery b -> FocusQuery a #

Monad FocusQuery Source # 
Instance details

Defined in XMonad.Hooks.Focus

Methods

(>>=) :: FocusQuery a -> (a -> FocusQuery b) -> FocusQuery b #

(>>) :: FocusQuery a -> FocusQuery b -> FocusQuery b #

return :: a -> FocusQuery a #

MonadReader Focus FocusQuery Source # 
Instance details

Defined in XMonad.Hooks.Focus

Methods

ask :: FocusQuery Focus #

local :: (Focus -> Focus) -> FocusQuery a -> FocusQuery a #

reader :: (Focus -> a) -> FocusQuery a #

Monoid a => Monoid (FocusQuery a) Source # 
Instance details

Defined in XMonad.Hooks.Focus

Semigroup a => Semigroup (FocusQuery a) Source # 
Instance details

Defined in XMonad.Hooks.Focus

Lifting into FocusQuery.

 

liftQuery :: Query a -> FocusQuery a Source #

Lift Query into FocusQuery monad. The same as new.

new :: Query a -> FocusQuery a Source #

Run Query on new window.

focused :: Query Bool -> FocusQuery Bool Source #

Run Query on focused window on workspace, where new window appears. If there is no focused window, return False.

focused' :: Monoid a => Query a -> FocusQuery a Source #

More general version of focused.

focusedOn :: WorkspaceId -> Query Bool -> FocusQuery Bool Source #

Run Query on window focused at particular workspace. If there is no focused window, return False.

focusedOn' :: Monoid a => WorkspaceId -> Query a -> FocusQuery a Source #

More general version of focusedOn.

focusedCur :: Query Bool -> FocusQuery Bool Source #

Run Query on focused window on current workspace. If there is no focused window, return False. Note,

focused <&&> newOnCur != focusedCur

The first will affect only new or activated window appearing on current workspace, while the last will affect any window: focus even for windows appearing on other workpsaces will depend on focus on current workspace.

focusedCur' :: Monoid a => Query a -> FocusQuery a Source #

More general version of focusedCur.

newOn :: WorkspaceId -> FocusQuery Bool Source #

Does new window appear at particular workspace?

newOnCur :: FocusQuery Bool Source #

Does new window appear at current workspace?

unlessFocusLock :: Monoid a => Query a -> Query a Source #

Execute Query, unless focus is locked.

Commonly used actions for modifying focus.

Operations in each pair keepFocus and switchFocus, keepWorkspace and switchWorkspace overwrite each other (the letftmost will determine what happened):

keepFocus       <> switchFocus     = keepFocus
switchFocus     <> keepFocus       = switchFocus
keepWorkspace   <> switchWorkspace = keepWorkspace
switchWorkspace <> keepWorkspace   = switchWorkspace

and operations from different pairs are commutative:

keepFocus   <> switchWorkspace = switchWorkspace <> keepFocus
switchFocus <> switchWorkspace = switchWorkspace <> switchFocus

etc.

keepFocus :: FocusHook Source #

Keep focus on workspace (may not be current), where new window appears. Workspace will not be switched. This operation is idempotent and effectively returns focus to window focused on that workspace before applying (Endo WindowSet) function.

switchFocus :: FocusHook Source #

Switch focus to new window on workspace (may not be current), where new window appears. Workspace will not be switched. This operation is idempotent.

keepWorkspace :: FocusHook Source #

Keep current workspace. Focus will not be changed at either current or new window's workspace. This operation is idempotent and effectively switches to workspace, which was current before applying (Endo WindowSet) function.

switchWorkspace :: FocusHook Source #

Switch workspace to one, where new window appears. Focus will not be changed at either current or new window's workspace. This operation is idempotent.

Running FocusQuery.

 

manageFocus :: FocusHook -> ManageHook Source #

I don't know at which workspace new window will appear until (Endo WindowSet) function from windows in XMonad.Operations actually run, but in (Endo WindowSet) function i can't already execute monadic actions, because it's pure. So, i compute result for every workspace here and just use it later in (Endo WindowSet) function. Note, though, that this will execute monadic actions many times, and therefore assume, that result of FocusHook does not depend on the number of times it was executed.

Example configurations.

 

activateSwitchWs :: ManageHook Source #

Default EWMH window activation behavior: switch to workspace with activated window and switch focus to it. Not to be used in a manageHook.

activateOnCurrentWs :: ManageHook Source #

Move activated window to current workspace and switch focus to it. Note, that i need to explicitly call switchFocus here, because otherwise, when activated window is already on current workspace, focus won't be switched. Not to be used in a manageHook.

activateOnCurrentKeepFocus :: ManageHook Source #

Move activated window to current workspace, but keep focus unchanged. Not to be used in a manageHook.