mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-05-19 03:20:21 -07:00
Merge pull request #535 from slotThe/ppWindowTitle
Move `ppTitleUnfocused` to X.U.Loggers
This commit is contained in:
commit
8cbe3ecd48
@ -107,9 +107,6 @@
|
||||
- Added `filterOutWsPP` for filtering out certain workspaces from being
|
||||
displayed.
|
||||
|
||||
- Added `ppTitleUnfocused` to `PP` for showing unfocused windows on
|
||||
the current workspace in the status bar.
|
||||
|
||||
- Added `xmobarBorder` function to create borders around strings.
|
||||
|
||||
- Added `ppRename` to `PP`, which makes it possible for extensions like
|
||||
@ -417,6 +414,8 @@
|
||||
- Added `logConst` to log a constant `String`, and `logDefault` (infix: `.|`)
|
||||
to combine loggers.
|
||||
|
||||
- Added `logTitles` to log all window titles (focused and unfocused ones).
|
||||
|
||||
* `XMonad.Layout.Minimize`
|
||||
|
||||
- Export `Minimize` type constructor.
|
||||
|
@ -1,4 +1,5 @@
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
-----------------------------------------------------------------------------
|
||||
-- |
|
||||
-- Module : XMonad.Hooks.StatusBar.PP
|
||||
@ -47,7 +48,6 @@ module XMonad.Hooks.StatusBar.PP (
|
||||
|
||||
import Control.Applicative (liftA2)
|
||||
import Control.Monad (msum)
|
||||
import Data.Bool (bool)
|
||||
import Data.Char (isSpace)
|
||||
import Data.List (intercalate, isPrefixOf, sortOn, stripPrefix)
|
||||
import Data.Maybe (catMaybes, fromMaybe, isJust, mapMaybe)
|
||||
@ -102,11 +102,8 @@ data PP = PP { ppCurrent :: WorkspaceId -> String
|
||||
-- ^ separator to use between workspace tags
|
||||
, ppTitle :: String -> String
|
||||
-- ^ window title format for the focused window
|
||||
, ppTitleUnfocused :: String -> String
|
||||
-- ^ window title format for unfocused windows
|
||||
, ppTitleSanitize :: String -> String
|
||||
-- ^ escape / sanitizes input to 'ppTitle' and
|
||||
-- 'ppTitleUnfocused'
|
||||
-- ^ escape / sanitizes input to 'ppTitle'
|
||||
, ppLayout :: String -> String
|
||||
-- ^ layout name format
|
||||
, ppOrder :: [String] -> [String]
|
||||
@ -155,7 +152,6 @@ instance Default PP where
|
||||
, ppSep = " : "
|
||||
, ppWsSep = " "
|
||||
, ppTitle = shorten 80
|
||||
, ppTitleUnfocused = const ""
|
||||
, ppTitleSanitize = xmobarStrip . dzenEscape
|
||||
, ppLayout = id
|
||||
, ppOrder = id
|
||||
@ -186,22 +182,16 @@ dynamicLogString pp = do
|
||||
-- workspace list
|
||||
let ws = pprWindowSet sort' urgents pp winset
|
||||
|
||||
-- window titles
|
||||
let stack = S.index winset
|
||||
focWin = S.peek winset
|
||||
ppWin :: Window -> String -> String -- pretty print a window title
|
||||
= bool (ppTitleUnfocused pp) (ppTitle pp) . (focWin ==) . Just
|
||||
winNames <- traverse (fmap show . getName) stack
|
||||
let ppNames = unwords . filter (not . null) $
|
||||
zipWith (\w n -> ppWin w $ ppTitleSanitize pp n) stack winNames
|
||||
|
||||
-- run extra loggers, ignoring any that generate errors.
|
||||
extras <- mapM (`catchX` return Nothing) $ ppExtras pp
|
||||
|
||||
-- window title
|
||||
wt <- maybe (pure "") (fmap show . getName) . S.peek $ winset
|
||||
|
||||
return $ sepBy (ppSep pp) . ppOrder pp $
|
||||
[ ws
|
||||
, ppLayout pp ld
|
||||
, ppNames
|
||||
, ppTitle pp $ ppTitleSanitize pp wt
|
||||
]
|
||||
++ catMaybes extras
|
||||
|
||||
|
@ -31,7 +31,7 @@ module XMonad.Util.Loggers (
|
||||
|
||||
-- * XMonad Loggers
|
||||
-- $xmonad
|
||||
, logCurrent, logLayout, logTitle
|
||||
, logCurrent, logLayout, logTitle, logTitles
|
||||
, logConst, logDefault, (.|)
|
||||
-- * XMonad: Screen-specific Loggers
|
||||
-- $xmonad-screen
|
||||
@ -47,7 +47,7 @@ module XMonad.Util.Loggers (
|
||||
|
||||
) where
|
||||
|
||||
import XMonad (liftIO, Window)
|
||||
import XMonad (liftIO, Window, gets)
|
||||
import XMonad.Core
|
||||
import qualified XMonad.StackSet as W
|
||||
import XMonad.Hooks.DynamicLog
|
||||
@ -175,6 +175,35 @@ maildirNew mdir = logFileCount (mdir ++ "/new/") (not . isPrefixOf ".")
|
||||
logTitle :: Logger
|
||||
logTitle = withWindowSet $ traverse (fmap show . getName) . W.peek
|
||||
|
||||
-- | Get the titles of all windows on the current workspace and format
|
||||
-- them according to the given functions.
|
||||
--
|
||||
-- ==== __Example__
|
||||
--
|
||||
-- > myXmobarPP :: X PP
|
||||
-- > myXmobarPP = pure $ def
|
||||
-- > { ppOrder = [ws, l, _, wins] -> [ws, l, wins]
|
||||
-- > , ppExtras = [logTitles formatFocused formatUnfocused]
|
||||
-- > }
|
||||
-- > where
|
||||
-- > formatFocused = wrap "[" "]" . xmobarColor "#ff79c6" "" . shorten 50 . xmobarStrip
|
||||
-- > formatUnfocused = wrap "(" ")" . xmobarColor "#bd93f9" "" . shorten 30 . xmobarStrip
|
||||
--
|
||||
logTitles
|
||||
:: (String -> String) -- ^ Formatting for the focused window
|
||||
-> (String -> String) -- ^ Formatting for the unfocused window
|
||||
-> Logger
|
||||
logTitles formatFoc formatUnfoc = do
|
||||
winset <- gets windowset
|
||||
let focWin = W.peek winset
|
||||
wins = W.index winset
|
||||
winNames <- traverse (fmap show . getName) wins
|
||||
pure . Just
|
||||
. unwords
|
||||
$ zipWith (\w n -> if Just w == focWin then formatFoc n else formatUnfoc n)
|
||||
wins
|
||||
winNames
|
||||
|
||||
-- | Get the name of the current layout.
|
||||
logLayout :: Logger
|
||||
logLayout = withWindowSet $ return . Just . ld
|
||||
|
Loading…
x
Reference in New Issue
Block a user