[xmonad] [ANN] X.H.Focus: combinators extending MH for managing focus

Dmitriy Matrosov sgf.dma at gmail.com
Fri Oct 7 14:26:16 UTC 2016


Hi.

I want to announce a new module for xmonad: XMonad.Hooks.Focus .

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 (this can be retrieved without any additional modules,
    that's just for completeness);

And two properties in extensible state:

  - is focus lock enabled? Focus lock instructs all library's FocusHook
  functions to not move focus.
  - is new window _NET_ACTIVE_WINDOW activated? It is not really new in that
  case, but i may work with it in the same way.

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.

As far as i know, no one from xmonad-contrib modules provide this
functionality at the moment. Here is a few examples:

     activateFocusHook :: FocusHook
     activateFocusHook = composeAll
                     -- If `gmrun` is focused on workspace, on which
                     -- activated window is, keep focus unchanged. But i
                     -- may still switch workspace.
                     [ 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 =? "Iceweasel" <||> className =? 
"Firefox") <&&> isDialog)
                                                         -?> keepFocus
                     -- Default behavior for new windows: switch focus.
                     , return True                       -?> switchFocus
                     ]

And here is an example of moving all activated windows to current 
workspace by
default, but keeping focus on current window (note, i need more generic
`composeOne` and `(-?>)`, than defind in X.H.ManageHelpers):


import Data.Monoid
import Control.Applicative
import Control.Monad

import XMonad
import qualified XMonad.StackSet as W

import XMonad.Hooks.Focus
import XMonad.Hooks.ManageHelpers hiding (composeOne, (-?>))

main :: IO ()
main = do
         let xcf = handleFocusQuery (Just (0, xK_v)) (composeOne
                         [ activated -?> (newOnCur --> keepFocus)
                         , Just <$> newFocusHook
                         ])
                     $ defaultConfig
                         { modMask = mod4Mask
                         , manageHook = manageFocus activateOnCurrentWs
                         }
         xmonad xcf

activateOnCurrentWs :: FocusHook
activateOnCurrentWs = activated --> asks currentWorkspace >>=
                         new . unlessFocusLock . doShift

composeOne :: (Monoid a, Monad m) => [m (Maybe a)] -> m a
composeOne [] = return mempty
composeOne (mx : xs) = do
     x <- mx
     case x of
       Just y  -> return y
       Nothing -> composeOne xs

infixr 0 -?>
(-?>) :: Monad m => m Bool -> m a -> m (Maybe a)
(-?>) mb mx     = do
     b <- mb
     if b
       then liftM Just mx
       else return Nothing

The code is here [gist][1] . It is the version suitable for putting into
'.xmonad/lib/XMonad/Hooks/Focus.hs'. I've tried it with Haskell Platform
'2013.2.0.0' (ghc 7.6.3), xmonad 0.12 on Debian 8 (Jessie). Developing 
of this module i'm
doing in [github/sgf-xmonad-modules][2]. And my xmonad config, which 
includes
this module and is compiled by `stack` (and installed by `make install`,
assuming all dependencies are present) can be found here
[github/sgf-xmonad-config][3].

Unfortunately, there is no tests and comments are written not in haddock
format at the moment (because i don't know either (yet); though, there are
many comments and examples in the code!), thus, i can't make a PR to
'xmonad-contrib' for now.  It takes me almost three months to write this
module, and since i don't know how long it takes to complete these two 
missed
parts, i announce module now as is (well, it seems working fine and i'm 
using
it).

Please, read the long comment section near the top of the module source 
before
using, there are incompatibilities and, well.. specialities.

[1]: https://gist.github.com/sgf-dma/99712cbfedf278d2a6e871ac70749b48
[2]: https://github.com/sgf-dma/sgf-xmonad-modules
[3]: https://github.com/sgf-dma/sgf-xmonad-config



More information about the xmonad mailing list