mirror of
https://github.com/xmonad/xmonad-contrib.git
synced 2025-08-01 04:31:52 -07:00
Added pretty printer for empty visible workspaces
Simple extensions of the pretty printer to differentiate between empty and non-empty visible workspaces. Analogical to the existing functionality for hidden workspaces. Particularly useful if some displays managed by xmonad are turned off temporarily. The new 'ppVisibleNoWindows' function was wrapped in a Maybe data type. Its value dafaults to 'Nothing' and 'ppVisible' is used as fallback.
This commit is contained in:
@@ -62,7 +62,7 @@ import Codec.Binary.UTF8.String (encodeString)
|
||||
import Control.Monad (liftM2, msum)
|
||||
import Data.Char ( isSpace, ord )
|
||||
import Data.List (intersperse, stripPrefix, isPrefixOf, sortBy)
|
||||
import Data.Maybe ( isJust, catMaybes, mapMaybe )
|
||||
import Data.Maybe ( isJust, catMaybes, mapMaybe, fromMaybe )
|
||||
import Data.Ord ( comparing )
|
||||
import qualified Data.Map as M
|
||||
import qualified XMonad.StackSet as S
|
||||
@@ -320,7 +320,8 @@ pprWindowSet sort' urgents pp s = sepBy (ppWsSep pp) . map fmt . sort' $
|
||||
fmt w = printer pp (S.tag w)
|
||||
where printer | any (\x -> maybe False (== S.tag w) (S.findTag x s)) urgents = ppUrgent
|
||||
| S.tag w == this = ppCurrent
|
||||
| S.tag w `elem` visibles = ppVisible
|
||||
| S.tag w `elem` visibles && isJust (S.stack w) = ppVisible
|
||||
| S.tag w `elem` visibles = liftM2 fromMaybe ppVisible ppVisibleNoWindows
|
||||
| isJust (S.stack w) = ppHidden
|
||||
| otherwise = ppHiddenNoWindows
|
||||
|
||||
@@ -460,6 +461,8 @@ data PP = PP { ppCurrent :: WorkspaceId -> String
|
||||
-- contain windows
|
||||
, ppHiddenNoWindows :: WorkspaceId -> String
|
||||
-- ^ how to print tags of empty hidden workspaces
|
||||
, ppVisibleNoWindows :: Maybe (WorkspaceId -> String)
|
||||
-- ^ how to print tags of empty visible workspaces
|
||||
, ppUrgent :: WorkspaceId -> String
|
||||
-- ^ format to be applied to tags of urgent workspaces.
|
||||
, ppSep :: String
|
||||
@@ -512,6 +515,7 @@ instance Default PP where
|
||||
, ppVisible = wrap "<" ">"
|
||||
, ppHidden = id
|
||||
, ppHiddenNoWindows = const ""
|
||||
, ppVisibleNoWindows= Nothing
|
||||
, ppUrgent = id
|
||||
, ppSep = " : "
|
||||
, ppWsSep = " "
|
||||
|
Reference in New Issue
Block a user