[Xmonad] Show windows in status bar?

Donald Bruce Stewart dons at cse.unsw.edu.au
Mon Jun 11 06:10:49 EDT 2007


buisse:
> On Mon, Jun 11, 2007 at 11:45:49 +0200, Kai Grossjohann wrote:
> 
> > What I like about dwm is that it shows me the title of the currently
> > focussed window in the status bar.  Has anyone done this for xmonad?
> > 
> > Furthermore, it would be cool to get some indication of other windows on
> > the current workspace: One could display a list of titles and highlight
> > the currently focussed window.  The difficult part is that the list of
> > titles is likely long, so one would have to shorten it somehow.
> > 
> > List of titles:
> > 
> > Emacs / xterm 1 / [xterm 2] / Gaim / xload
> > 

Here's a quick example to get you going. It's a variant of the existing
DynamicLog idea, 

    1 [2] 3 7

And also prints the title of the focused window on the current
workspace,

    1 [2 urxvt] 3 7

Screenshot,

    http://www.cse.unsw.edu.au/~dons//tmp/dzen-fetchname.png

Here's the code, the first block is the interesting part:

 logHook = withWindowSet $ \s -> do

                -- here's the S.peek/fetchName
                 ws <- gets windowset
                 n  <- case S.peek ws of
                             Nothing -> return ""
                             Just w  -> do d <- asks display
                                           maybe "-" id `fmap` io (fetchName d w)
 
                 io . putStrLn . (ppr n) $ s
 
    -- and the rest is pretty much unchanged from DynamicLog.hs
   where
     ppr n s =  concatMap fmt $ sortBy tags
                  (map S.workspace (S.current s : S.visible s) ++ S.hidden s)
 
        where tags a b = S.tag a `compare` S.tag b
              this     = S.tag (S.workspace (S.current s))
              pprTag   = show . (+(1::Int)) . fromIntegral . S.tag
              visibles = map (S.tag . S.workspace) (S.visible s)
 
              fmt w | S.tag w == this         = "[" ++ pprTag w ++ " " ++ n ++  "]"
                    | S.tag w `elem` visibles = "<" ++ pprTag w ++ ">"
                    | S.stack w /= S.Empty    = " " ++ pprTag w ++ " "
                    | otherwise               = ""

-- Don


More information about the Xmonad mailing list