xmonad-contrib-0.17.1.9: Community-maintained extensions for xmonad
Copyright(c) 2007 2008 Joachim Breitner <mail@joachim-breitner.de>
LicenseBSD
MaintainerJoachim Breitner <mail@joachim-breitner.de>
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Hooks.EwmhDesktops

Description

Makes xmonad use the EWMH hints to tell panel applications about its workspaces and the windows therein. It also allows the user to interact with xmonad by clicking on panels and window lists.

Synopsis

Usage

You can use this module with the following in your xmonad.hs:

import XMonad
import XMonad.Hooks.EwmhDesktops

main = xmonad $ … . ewmhFullscreen . ewmh . … $ def{…}

or, if fullscreen handling is not desired, just

main = xmonad $ … . ewmh . … $ def{…}

You may also be interested in docks and withUrgencyHook, which provide support for other parts of the EWMH specification.

ewmh :: XConfig a -> XConfig a Source #

Add EWMH support for workspaces (virtual desktops) to the given XConfig. See above for an example.

ewmhFullscreen :: XConfig a -> XConfig a Source #

Add EWMH fullscreen functionality to the given config.

ewmhDesktopsManageHook :: ManageHook Source #

A ManageHook that shifts windows to the workspace they want to be in. Useful for restoring browser windows to where they were before restart.

To only use this for browsers (which might be a good idea, as many apps try to restore their window to their original position, but it's rarely desirable outside of security updates of multi-window apps like a browser), use this:

stringProperty "WM_WINDOW_ROLE" =? "browser" --> ewmhDesktopsManageHook

ewmhDesktopsMaybeManageHook :: MaybeManageHook Source #

ewmhDesktopsManageHook as a MaybeManageHook for use with composeOne. Returns Nothing if the window didn't indicate any desktop preference, otherwise Just (even if the preferred desktop was out of bounds).

Customization

It's possible to customize the behaviour of ewmh in several ways:

Sorting/filtering of workspaces

The list of workspaces exposed to EWMH pagers (like taffybar and polybar) and clients (such as wmctrl and xdotool) may be sorted and/or filtered via a user-defined function.

To show visible workspaces first, one may switch to a Xinerama-aware sorting function:

import XMonad.Util.WorkspaceCompare

mySort = getSortByXineramaRule
main = xmonad $ … . setEwmhWorkspaceSort mySort . ewmh . … $ def{…}

Another useful example is not exposing the hidden scratchpad workspace:

import XMonad.Util.NamedScratchpad
import XMonad.Util.WorkspaceCompare

myFilter = filterOutWs [scratchpadWorkspaceTag]
main = xmonad $ … . addEwmhWorkspaceSort (pure myFilter) . ewmh . … $ def{…}

addEwmhWorkspaceSort :: X WorkspaceSort -> XConfig l -> XConfig l Source #

Add (compose after) an arbitrary user-specified function to sort/filter the workspace list. The default/initial function is getSortByIndex. This can be used to e.g. filter out scratchpad workspaces. Workspaces must not be renamed here.

setEwmhWorkspaceSort :: X WorkspaceSort -> XConfig l -> XConfig l Source #

Like addEwmhWorkspaceSort, but replace it instead of adding/composing.

Renaming of workspaces

The workspace names exposed to EWMH pagers and other clients (e.g. arbtt) may be altered using a similar interface to ppRename. To configure workspace renaming, use addEwmhWorkspaceRename.

As an example, to expose workspaces uppercased:

import Data.Char

myRename :: String -> WindowSpace -> String
myRename s _w = map toUpper s

main = xmonad $ … . addEwmhWorkspaceRename (pure myRename) . ewmh . … $ def{…}

Some modules like XMonad.Actions.WorkspaceNames provide ready-made integrations:

import XMonad.Actions.WorkspaceNames

main = xmonad $ … . workspaceNamesEwmh . ewmh . … $ def{…}

The above ensures workspace names are exposed through EWMH.

addEwmhWorkspaceRename :: X (String -> WindowSpace -> String) -> XConfig l -> XConfig l Source #

Add (compose after) an arbitrary user-specified function to rename each workspace. This works just like ppRename: the WindowSpace -> … acts as a Reader monad. Useful with XMonad.Actions.WorkspaceNames, XMonad.Layout.IndependentScreens, XMonad.Hooks.DynamicIcons.

setEwmhWorkspaceRename :: X (String -> WindowSpace -> String) -> XConfig l -> XConfig l Source #

Like addEwmhWorkspaceRename, but replace it instead of adding/composing.

Window activation

When a client sends a _NET_ACTIVE_WINDOW request to activate a window, by default that window is activated by invoking the doFocus ManageHook. The EWMH specification suggests that a window manager may instead just mark the window as urgent, and this can be achieved using the following:

import XMonad.Hooks.UrgencyHook

main = xmonad $ … . setEwmhActivateHook doAskUrgent . ewmh . … $ def{…}

One may also wish to ignore activation requests from certain applications entirely:

import XMonad.Hooks.ManageHelpers

myActivateHook :: ManageHook
myActivateHook =
  className /=? "Google-chrome" <&&> className /=? "google-chrome" --> doFocus

main = xmonad $ … . setEwmhActivateHook myActivateHook . ewmh . … $ def{…}

Arbitrarily complex hooks can be used. This last example marks Chrome windows as urgent and focuses everything else:

myActivateHook :: ManageHook
myActivateHook = composeOne
  [ className =? "Google-chrome" <||> className =? "google-chrome" -?> doAskUrgent
  , pure True -?> doFocus ]

See XMonad.ManageHook, XMonad.Hooks.ManageHelpers and XMonad.Hooks.Focus for functions that can be useful here.

setEwmhActivateHook :: ManageHook -> XConfig l -> XConfig l Source #

Set (replace) the hook which is invoked when a client sends a _NET_ACTIVE_WINDOW request to activate a window. The default is doFocus which focuses the window immediately, switching workspace if necessary. doAskUrgent is a less intrusive alternative.

More complex hooks can be constructed using combinators from XMonad.ManageHook, XMonad.Hooks.ManageHelpers and XMonad.Hooks.Focus.

Fullscreen

When a client sends a _NET_WM_STATE request to add/remove/toggle the _NET_WM_STATE_FULLSCREEN state, ewmhFullscreen uses a pair of hooks to make the window fullscreen and revert its state. The default hooks are stateless: windows are fullscreened by turning them into fullscreen floats, and reverted by sinking them into the tiling layer. This behaviour can be configured by supplying a pair of ManageHooks to setEwmhFullscreenHooks.

See XMonad.Actions.ToggleFullFloat for a pair of hooks that store the original state of floating windows.

_NET_DESKTOP_VIEWPORT

Setting _NET_DESKTOP_VIEWPORT is typically desired but can lead to a confusing workspace list in polybar, where this information is used to re-group the workspaces by monitor. See polybar#2603.

To avoid this, you can use:

main = xmonad $ … . disableEwmhManageDesktopViewport . ewmh . … $ def{…}

Note that if you apply this configuration in an already running environment, the property may remain at its previous value. It can be removed by running:

xprop -root -remove _NET_DESKTOP_VIEWPORT

Which should immediately fix your bar.

Standalone hooks (deprecated)

ewmhDesktopsStartup :: X () Source #

Deprecated: Use ewmh instead.

Initializes EwmhDesktops and advertises EWMH support to the X server.

ewmhDesktopsLogHook :: X () Source #

Deprecated: Use ewmh instead.

Notifies pagers and window lists, such as those in the gnome-panel of the current state of workspaces and windows.

ewmhDesktopsLogHookCustom :: WorkspaceSort -> X () Source #

Deprecated: Use ewmh and addEwmhWorkspaceSort instead.

Generalized version of ewmhDesktopsLogHook that allows an arbitrary user-specified function to sort/filter the workspace list (post-sorting).

ewmhDesktopsEventHook :: Event -> X All Source #

Deprecated: Use ewmh instead.

Intercepts messages from pagers and similar applications and reacts on them.

Currently supports:

  • _NET_CURRENT_DESKTOP (switching desktops)
  • _NET_WM_DESKTOP (move windows to other desktops)
  • _NET_ACTIVE_WINDOW (activate another window, changing workspace if needed)
  • _NET_CLOSE_WINDOW (close window)

ewmhDesktopsEventHookCustom :: WorkspaceSort -> Event -> X All Source #

Deprecated: Use ewmh and addEwmhWorkspaceSort instead.

Generalized version of ewmhDesktopsEventHook that allows an arbitrary user-specified function to sort/filter the workspace list (post-sorting).

fullscreenEventHook :: Event -> X All Source #

Deprecated: Use ewmhFullscreen instead.

An event hook to handle applications that wish to fullscreen using the _NET_WM_STATE protocol. This includes users of the gtk_window_fullscreen() function, such as Totem, Evince and OpenOffice.org.

Note this is not included in ewmh.

fullscreenStartup :: X () Source #

Deprecated: Use ewmhFullscreen instead.

Advertises EWMH fullscreen support to the X server.