-
-
Notifications
You must be signed in to change notification settings - Fork 276
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
X.H.EwmhDesktops: Mostly cosmetic, mostly docs cleanups
- Loading branch information
Showing
1 changed file
with
41 additions
and
81 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
|
@@ -5,7 +5,7 @@ | |
----------------------------------------------------------------------------- | ||
-- | | ||
-- Module : XMonad.Hooks.EwmhDesktops | ||
-- Description : Make xmonad use the extended window manager hints (EWMH). | ||
-- Description : Make xmonad use the extended window manager hints (EWMH). | ||
-- Copyright : (c) 2007, 2008 Joachim Breitner <[email protected]> | ||
-- License : BSD | ||
-- | ||
|
@@ -21,19 +21,21 @@ module XMonad.Hooks.EwmhDesktops ( | |
-- * Usage | ||
-- $usage | ||
ewmh, | ||
ewmhFullscreen, | ||
addEwmhWorkspaceSort, setEwmhWorkspaceSort, | ||
addEwmhWorkspaceRename, setEwmhWorkspaceRename, | ||
ewmhDesktopsStartup, | ||
ewmhDesktopsLogHook, | ||
ewmhDesktopsLogHookCustom, | ||
NetActivated (..), | ||
activated, | ||
activateLogHook, | ||
|
||
-- * Standalone hooks (to be deprecated) | ||
ewmhDesktopsStartup, | ||
ewmhDesktopsLogHook, | ||
ewmhDesktopsLogHookCustom, | ||
ewmhDesktopsEventHook, | ||
ewmhDesktopsEventHookCustom, | ||
ewmhFullscreen, | ||
fullscreenEventHook, | ||
fullscreenStartup | ||
fullscreenStartup, | ||
) where | ||
|
||
import Codec.Binary.UTF8.String (encode) | ||
|
@@ -45,7 +47,6 @@ import XMonad.Prelude | |
import qualified XMonad.StackSet as W | ||
|
||
import XMonad.Hooks.SetWMName | ||
import qualified XMonad.Util.ExtensibleState as E | ||
import XMonad.Util.WorkspaceCompare | ||
import XMonad.Util.WindowProperties (getProp32) | ||
import qualified XMonad.Util.ExtensibleConf as XC | ||
|
@@ -63,7 +64,9 @@ import qualified XMonad.Util.ExtensibleState as XS | |
-- | ||
-- > main = xmonad $ … . ewmh . … $ def{…} | ||
-- | ||
-- You may also be interested in 'docks' from "XMonad.Hooks.ManageDocks". | ||
-- You may also be interested in 'XMonad.Hooks.ManageDocks.docks' and | ||
-- 'XMonad.Hooks.UrgencyHook.withUrgencyHook', which provide support for other | ||
-- parts of the EWMH specification. | ||
-- | ||
-- __/NOTE:/__ 'ewmh' function will call 'logHook' for handling activated | ||
-- window. | ||
|
@@ -93,7 +96,8 @@ import qualified XMonad.Util.ExtensibleState as XS | |
-- > } | ||
-- > xmonad xcf | ||
|
||
-- | Add EWMH functionality to the given config. See above for an example. | ||
-- | Add EWMH support for workspaces (virtual desktops) to the given | ||
-- 'XConfig'. See above for an example. | ||
ewmh :: XConfig a -> XConfig a | ||
ewmh c = c { startupHook = ewmhDesktopsStartup <+> startupHook c | ||
, handleEventHook = ewmhDesktopsEventHook <+> handleEventHook c | ||
|
@@ -137,28 +141,24 @@ addEwmhWorkspaceRename f = XC.modifyDef $ \c -> c{ workspaceRename = liftA2 (<=< | |
setEwmhWorkspaceRename :: X (String -> WindowSpace -> String) -> XConfig l -> XConfig l | ||
setEwmhWorkspaceRename f = XC.modifyDef $ \c -> c{ workspaceRename = f } | ||
|
||
-- | | ||
-- Initializes EwmhDesktops and advertises EWMH support to the X | ||
-- server | ||
-- | Initializes EwmhDesktops and advertises EWMH support to the X server | ||
ewmhDesktopsStartup :: X () | ||
ewmhDesktopsStartup = setSupported | ||
|
||
-- | | ||
-- Notifies pagers and window lists, such as those in the gnome-panel | ||
-- of the current state of workspaces and windows. | ||
-- | Notifies pagers and window lists, such as those in the gnome-panel of the | ||
-- current state of workspaces and windows. | ||
ewmhDesktopsLogHook :: X () | ||
ewmhDesktopsLogHook = XC.withDef ewmhDesktopsLogHook' | ||
|
||
-- | | ||
-- Generalized version of ewmhDesktopsLogHook that allows an arbitrary | ||
-- | Generalized version of ewmhDesktopsLogHook that allows an arbitrary | ||
-- user-specified function to sort/filter the workspace list (post-sorting) | ||
{-# DEPRECATED ewmhDesktopsLogHookCustom "Use addEwmhWorkspaceSort instead" #-} | ||
ewmhDesktopsLogHookCustom :: WorkspaceSort -> X () | ||
ewmhDesktopsLogHookCustom f = | ||
ewmhDesktopsLogHook' def{ workspaceSort = (f <$>) <$> workspaceSort def } | ||
|
||
-- | | ||
-- Intercepts messages from pagers and similar applications and reacts on them. | ||
-- | Intercepts messages from pagers and similar applications and reacts on them. | ||
-- | ||
-- Currently supports: | ||
-- | ||
-- * _NET_CURRENT_DESKTOP (switching desktops) | ||
|
@@ -171,72 +171,41 @@ ewmhDesktopsLogHookCustom f = | |
ewmhDesktopsEventHook :: Event -> X All | ||
ewmhDesktopsEventHook = XC.withDef . ewmhDesktopsEventHook' | ||
|
||
-- | | ||
-- Generalized version of ewmhDesktopsEventHook that allows an arbitrary | ||
-- | Generalized version of ewmhDesktopsEventHook that allows an arbitrary | ||
-- user-specified function to sort/filter the workspace list (post-sorting) | ||
{-# DEPRECATED ewmhDesktopsEventHookCustom "Use addEwmhWorkspaceSort instead" #-} | ||
ewmhDesktopsEventHookCustom :: WorkspaceSort -> Event -> X All | ||
ewmhDesktopsEventHookCustom f e = | ||
ewmhDesktopsEventHook' e def{ workspaceSort = (f <$>) <$> workspaceSort def } | ||
|
||
-- | | ||
-- Cached desktop names (e.g. @_NET_NUMBER_OF_DESKTOPS@ and | ||
-- @_NET_DESKTOP_NAMES@). | ||
newtype DesktopNames = DesktopNames [String] | ||
deriving Eq | ||
|
||
instance ExtensionClass DesktopNames where | ||
initialValue = DesktopNames [] | ||
|
||
-- | | ||
-- Cached client list (e.g. @_NET_CLIENT_LIST@). | ||
newtype ClientList = ClientList [Window] | ||
deriving Eq | ||
|
||
instance ExtensionClass ClientList where | ||
initialValue = ClientList [none] | ||
|
||
-- | | ||
-- Cached stacking client list (e.g. @_NET_CLIENT_LIST_STACKING@). | ||
newtype ClientListStacking = ClientListStacking [Window] | ||
deriving Eq | ||
|
||
instance ExtensionClass ClientListStacking where | ||
initialValue = ClientListStacking [none] | ||
|
||
-- | | ||
-- Cached current desktop (e.g. @_NET_CURRENT_DESKTOP@). | ||
newtype CurrentDesktop = CurrentDesktop Int | ||
deriving Eq | ||
-- | Cached @_NET_DESKTOP_NAMES@, @_NET_NUMBER_OF_DESKTOPS@ | ||
newtype DesktopNames = DesktopNames [String] deriving Eq | ||
instance ExtensionClass DesktopNames where initialValue = DesktopNames [] | ||
|
||
instance ExtensionClass CurrentDesktop where | ||
initialValue = CurrentDesktop (-1) | ||
-- | Cached @_NET_CLIENT_LIST@ | ||
newtype ClientList = ClientList [Window] deriving Eq | ||
instance ExtensionClass ClientList where initialValue = ClientList [none] | ||
|
||
-- | | ||
-- Cached window-desktop assignments (e.g. @_NET_CLIENT_LIST_STACKING@). | ||
newtype WindowDesktops = WindowDesktops (M.Map Window Int) | ||
deriving Eq | ||
-- | Cached @_NET_CLIENT_LIST_STACKING@ | ||
newtype ClientListStacking = ClientListStacking [Window] deriving Eq | ||
instance ExtensionClass ClientListStacking where initialValue = ClientListStacking [none] | ||
|
||
instance ExtensionClass WindowDesktops where | ||
initialValue = WindowDesktops (M.singleton none (-1)) | ||
-- | Cached @_NET_CURRENT_DESKTOP@ | ||
newtype CurrentDesktop = CurrentDesktop Int deriving Eq | ||
instance ExtensionClass CurrentDesktop where initialValue = CurrentDesktop (complement 0) | ||
|
||
-- | | ||
-- The value of @_NET_ACTIVE_WINDOW@, cached to avoid unnecessary property | ||
-- updates. | ||
newtype ActiveWindow = ActiveWindow Window | ||
deriving Eq | ||
-- | Cached @_NET_WM_DESKTOP@ | ||
newtype WindowDesktops = WindowDesktops (M.Map Window Int) deriving Eq | ||
instance ExtensionClass WindowDesktops where initialValue = WindowDesktops (M.singleton none (complement 0)) | ||
|
||
instance ExtensionClass ActiveWindow where | ||
initialValue = ActiveWindow (complement none) | ||
-- | Cached @_NET_ACTIVE_WINDOW@ | ||
newtype ActiveWindow = ActiveWindow Window deriving Eq | ||
instance ExtensionClass ActiveWindow where initialValue = ActiveWindow (complement none) | ||
|
||
-- | Compare the given value against the value in the extensible state. Run the | ||
-- action if it has changed. | ||
whenChanged :: (Eq a, ExtensionClass a) => a -> X () -> X () | ||
whenChanged v action = do | ||
v0 <- E.get | ||
unless (v == v0) $ do | ||
action | ||
E.put v | ||
whenChanged = whenX . XS.modified . const | ||
|
||
ewmhDesktopsLogHook' :: EwmhDesktopsConfig -> X () | ||
ewmhDesktopsLogHook' EwmhDesktopsConfig{workspaceSort, workspaceRename} = withWindowSet $ \s -> do | ||
|
@@ -351,14 +320,6 @@ ewmhDesktopsEventHook' | |
ewmhDesktopsEventHook' _ _ = mempty | ||
|
||
-- | Add EWMH fullscreen functionality to the given config. | ||
-- | ||
-- This must be applied after 'ewmh', like so: | ||
-- | ||
-- > main = xmonad $ ewmhFullscreen $ ewmh def | ||
-- | ||
-- NOT: | ||
-- | ||
-- > main = xmonad $ ewmh $ ewmhFullscreen def | ||
ewmhFullscreen :: XConfig a -> XConfig a | ||
ewmhFullscreen c = c { startupHook = startupHook c <+> fullscreenStartup | ||
, handleEventHook = handleEventHook c <+> fullscreenEventHook } | ||
|
@@ -367,9 +328,8 @@ ewmhFullscreen c = c { startupHook = startupHook c <+> fullscreenStartup | |
fullscreenStartup :: X () | ||
fullscreenStartup = setFullscreenSupported | ||
|
||
-- | | ||
-- An event hook to handle applications that wish to fullscreen using the | ||
-- _NET_WM_STATE protocol. This includes users of the gtk_window_fullscreen() | ||
-- | 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'. | ||
|