[Xmonad] more WS indicator stuff

Robert Manea rob.manea at googlemail.com
Sat Jun 16 13:52:09 EDT 2007


Hi.

So, here's a script to perfectly - well almost - mimic dwm's statusbar tag
indicator. 

Almost perfect because i haven't found a simple way to switch xmonad
workspaces with an external program.

Actually we can do something dwm does not provide, namely have the
workspaces color coded, i find this very useful as you dont have to read
the tags anymore - just look at the color and you know where you are :).


The current solution is perl pased, simply because i'm more comfortable
with perl than with haskell, though this would make a rather cool
contrib modules if anyone cares to haskellize it..

Obligatory shots:
http://omploader.org/file/xmonad-colorws1.png
http://omploader.org/file/xmonad-colorws2.png


So, here it goes:

ws-menucolor.pl:
----------------

#!/usr/bin/perl
#
# ws-color.pl (c) 2007, Robert Manea
#
# requires dzen >= 0.5.0
#
# Usage:
# xmonad | ws-menucolor.pl | dzen2 -m h -l nr_of_workspaces
#
use warnings;
use strict;

$|=1;

# define the workspace names 
# and the associated colors
my %wscolors = (
	"1:dev"	 => "^#aecf96^#000000",
	"2:mail" => "^#000000^#e6cf90",
	"3:web"  => "^#000000^#829dbd",
	"4:comm" => "^#000000^#7cab71",
	"5:ham"  => "^#aecf96^#000000",
	"6:tmp"  => "^#000000^#e7ab91"
);

while(<>) {
	chomp;
	my @wsin = split /\s+/, $_;

	for my $w (@wsin) {
		my $doprint = 1;

		for (keys %wscolors) {
			if($w =~ /\[${_}\]/) {
				print $wscolors{"$_"}, $w, "\n";
				$doprint = 0; last;
			}
		}
		print $w, "\n" if $doprint && $w;
	}
}

__END__


DynamicLogTag.hs, don's version slightly adapted:
-------------------------------------------------

module XMonadContrib.DynamicLogTag (dynamicLogTag) where

-- 
-- Useful imports
--
import XMonad
import Data.Maybe ( isJust )
import Data.List
import qualified StackSet as S

--
-- Perform an arbitrary action on each state change.
-- Examples include:
--      * do nothing
--      * log the state to stdout

--
-- An example logger, print a status bar output to dzen, in the form:
--
--  1 2 [3] 4 7
--  

dynamicLogTag :: X ()
dynamicLogTag = withWindowSet $ io . putStrLn . ppr
  where
    ppr s =  concatMap fmt $ sortBy (compare `on` S.tag)
                (map S.workspace (S.current s : S.visible s) ++ S.hidden s)
       where this     = S.tag (S.workspace (S.current s))

             fmt w | S.tag w == this         = "[" ++ pprTag w ++ "]"
                   | isJust (S.stack w)      = " •" ++ pprTag w ++ " "
                   | otherwise               = " " ++ pprTag w ++ " "


-- util functions
pprTag :: Integral i => S.Workspace i a -> String
pprTag   = name . fromIntegral . S.tag
    where
        name 0 = "1:dev"
        name 1 = "2:mail"
        name 2 = "3:web"
        name 3 = "4:comm"
        name 4 = "5:ham"
        name 5 = "6:tmp"
        name n = " " ++ show (1 + n) ++ " "

on :: (a -> a -> c) -> (b -> a) -> b -> b -> c
on f g a b = (g a) `f` (g b)


-- END




More information about the Xmonad mailing list