vanadium/xmonad: show current window count in pp

This commit is contained in:
Primrose 2025-11-20 09:16:43 +08:00
parent d3489e5730
commit 60bfd4f5c9
Signed by: primrose
GPG key ID: 4E887A4CA9714ADA
3 changed files with 15 additions and 35 deletions

View file

@ -25,7 +25,6 @@ library
hs-source-dirs: lib hs-source-dirs: lib
exposed-modules: exposed-modules:
XMonad.Layout.Reflect.Message XMonad.Layout.Reflect.Message
XMonad.Layout.ResizableTile.FixDescription
Data.Char.Greek Data.Char.Greek
executable leanamonad executable leanamonad

View file

@ -1,23 +0,0 @@
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
module XMonad.Layout.ResizableTile.FixDescription
( RTFixDescription(..)
) where
import XMonad
import qualified XMonad.StackSet as W
import XMonad.Layout.ResizableTile
newtype RTFixDescription a = RTFixDescription { unwrapRT :: ResizableTall a }
deriving (Read, Show)
instance LayoutClass RTFixDescription a where
runLayout (W.Workspace t l s) =
let ws' = W.Workspace t (unwrapRT l) s
in (fmap . fmap . fmap) RTFixDescription . runLayout ws'
handleMessage (RTFixDescription l) =
(fmap . fmap) RTFixDescription . handleMessage l
description (RTFixDescription l) =
description l <> " " <> show (_nmaster l)

View file

@ -19,7 +19,6 @@ import XMonad.Layout.Reflect
import XMonad.Layout.Reflect.Message import XMonad.Layout.Reflect.Message
import XMonad.Layout.Renamed import XMonad.Layout.Renamed
import XMonad.Layout.ResizableTile import XMonad.Layout.ResizableTile
import XMonad.Layout.ResizableTile.FixDescription
import XMonad.Layout.Spacing import XMonad.Layout.Spacing
import qualified XMonad.StackSet as W import qualified XMonad.StackSet as W
import XMonad.Util.EZConfig import XMonad.Util.EZConfig
@ -64,10 +63,9 @@ main =
`additionalKeys` keybinds `additionalKeys` keybinds
myLayout = myLayout =
let tallr = renamed [ KeepWordsRight 2 ] {- keep "ResizableTall n" -} let tallr = renamed [ Replace "Tall" ]
$ smartSpacingWithEdge 5 $ smartSpacingWithEdge 5
$ reflectMsg . reflectHoriz $ reflectMsg . reflectHoriz
$ RTFixDescription
$ ResizableTall 1 (1/10) (3/7) [] $ ResizableTall 1 (1/10) (3/7) []
mag = magnifyxy 1.05 1.3 (NoMaster 3) False mag = magnifyxy 1.05 1.3 (NoMaster 3) False
in avoidStruts in avoidStruts
@ -332,15 +330,21 @@ fullFloat = W.RationalRect 0 0 1 1
buttomRightFloat = W.RationalRect (1%2) (1%2) (1%2) (1%2) buttomRightFloat = W.RationalRect (1%2) (1%2) (1%2) (1%2)
xmobarConfig :: StatusBarConfig xmobarConfig :: StatusBarConfig
xmobarConfig = statusBarProp "xmobar -x 0" (pure myPrettyPrinter) xmobarConfig = statusBarProp "xmobar -x 0" myPrettyPrinter
where where
myPrettyPrinter = windowCount :: X Int
filterOutWsPP [scratchpadWorkspaceTag] windowCount = gets $ length . W.integrate' . W.stack . W.workspace . W.current . windowset
$ def
{ ppCurrent = xmobarColor "#000000" "#ffffff" . wrap " " " " . fmap toUpper myPrettyPrinter :: X PP
, ppHiddenNoWindows = xmobarColor "#9c9c9c" "" . const "" myPrettyPrinter = do
, ppSep = " | " wCount <- windowCount
} pure
$ filterOutWsPP [scratchpadWorkspaceTag]
$ def
{ ppCurrent = xmobarColor "#000000" "#ffffff" . wrap " " " " . ( <> ":" <> show wCount)
, ppHiddenNoWindows = xmobarColor "#9c9c9c" "" . const ""
, ppSep = " | "
}
myScratchpads :: [NamedScratchpad] myScratchpads :: [NamedScratchpad]
myScratchpads = myScratchpads =