xmonad-contrib/XMonad/Util/ClickableWorkspaces.hs
Tomas Janousek e91b0fef82 X.A.WorkspaceNames, X.L.IndependentScreens, X.U.ClickableWorkspaces: Use ppRename
Also, drop now useless integrations from X.U.ClickableWorkspaces:
workspaceNamesPP, marshallPP and clickablePP can now be composed
directly using >>= and it just works.

Related: https://github.com/xmonad/xmonad-contrib/pull/390
Related: https://github.com/xmonad/xmonad-contrib/pull/462
2021-03-17 11:53:44 +00:00

60 lines
2.2 KiB
Haskell

-------------------------------------------------------------------------------
-- |
-- Module : XMonad.Util.ClickableWorkspaces
-- Copyright : (c) Geoff deRosenroll <geoffderosenroll@gmail.com>
-- License : BSD3-style (see LICENSE)
--
-- Maintainer : Geoff deRosenroll <geoffderosenroll@gmail.com>
-- Stability : unstable
-- Portability : unportable
--
-- Provides @clickablePP@, which when applied to the PP pretty-printer used by
-- the "XMonad.Hooks.DynamicLog" hook, will make the workspace tags clickable in
-- XMobar (for switching focus).
--
-----------------------------------------------------------------------------
module XMonad.Util.ClickableWorkspaces (
-- * Usage
-- $usage
clickablePP,
clickableWrap,
) where
import Control.Monad ((>=>))
import Data.Functor ((<&>))
import XMonad
import XMonad.Hooks.DynamicLog (xmobarAction, xmobarRaw, PP(..))
import XMonad.Util.WorkspaceCompare (getWsIndex)
import qualified XMonad.StackSet as W
-- $usage
-- However you have set up your PP, apply @clickablePP@ to it, and bind the result
-- to "XMonad.Hooks.DynamicLog"\'s dynamicLogWithPP like so:
--
-- > logHook = clickablePP xmobarPP { ... } >>= dynamicLogWithPP
--
-- * Requirements:
-- * @xdotool@ on system (in path)
-- * "XMonad.Hooks.EwmhDesktops" for @xdotool@ support (see Hackage docs for setup)
-- * use of UnsafeStdinReader/UnsafeXMonadLog in xmobarrc (rather than StdinReader/XMonadLog)
-- | Wrap string with an xmobar action that uses @xdotool@ to switch to
-- workspace @i@.
clickableWrap :: Int -> String -> String
clickableWrap i ws = xmobarAction ("xdotool set_desktop " ++ show i) "1" $ xmobarRaw ws
-- | Return a function that wraps workspace names in an xmobar action that
-- switches to that workspace.
--
-- This assumes that 'XMonad.Hooks.EwmhDesktops.ewmhDesktopsEventHook'
-- isn't configured to change the workspace order. We might need to add an
-- additional parameter if anyone needs that.
getClickable :: X (String -> WindowSpace -> String)
getClickable = getWsIndex <&> \idx s w -> maybe id clickableWrap (idx (W.tag w)) s
-- | Apply clickable wrapping to the given PP.
clickablePP :: PP -> X PP
clickablePP pp = getClickable <&> \ren -> pp{ ppRename = ppRename pp >=> ren }