vanadium/xmonad: show nmaster count in description

This commit is contained in:
Primrose 2025-11-04 10:50:29 +08:00
parent b123f1650d
commit 073078a922
Signed by: primrose
GPG key ID: 4E887A4CA9714ADA
4 changed files with 35 additions and 4 deletions

View file

@ -24,7 +24,8 @@ library
import: common import: common
hs-source-dirs: lib hs-source-dirs: lib
exposed-modules: exposed-modules:
Leanamonad.Layouts.ReflectMsg Leanamonad.Layout.ReflectMsg
Leanamonad.Layout.ResizableTile
Leanamonad.GreekChar Leanamonad.GreekChar
executable leanamonad executable leanamonad

View file

@ -1,7 +1,7 @@
{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE MultiParamTypeClasses #-}
module Leanamonad.Layouts.ReflectMsg where module Leanamonad.Layout.ReflectMsg where
import XMonad ( import XMonad (
Resize (Expand, Shrink), Resize (Expand, Shrink),

View file

@ -0,0 +1,27 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
module Leanamonad.Layout.ResizableTile
( module XMonad.Layout.ResizableTile
, 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) m =
fmap (fmap RTFixDescription)
$ handleMessage l m
description (RTFixDescription l) =
description l <> " " <> show (_nmaster l)

View file

@ -26,7 +26,9 @@ import qualified Data.Map.Strict as M
import System.Posix import System.Posix
import Graphics.X11.ExtraTypes.XF86 import Graphics.X11.ExtraTypes.XF86
import Leanamonad.Layouts.ReflectMsg import Leanamonad.Layout.ReflectMsg
-- TODO: rename this module
import Leanamonad.Layout.ResizableTile
import Leanamonad.GreekChar import Leanamonad.GreekChar
main :: IO () main :: IO ()
@ -65,9 +67,10 @@ main =
putEnv "MOZ_USE_XINPUT2=1" -- Force touchpad for firefox putEnv "MOZ_USE_XINPUT2=1" -- Force touchpad for firefox
, layoutHook = , layoutHook =
let tallr = named "Normal" let tallr = renamed [ KeepWordsRight 2 ] {- keep "ResizableTall n" -}
$ 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 . smartBorders $ in avoidStruts . smartBorders $