[Xmonad] Window tags (automagic) + assign workspace to windows on startup

Karsten Schoelzel kuser at gmx.de
Sat Sep 8 12:56:08 EDT 2007


On Sat, Sep 08, 2007 at 11:26:37AM -0400, Xiao-Yong Jin wrote:
> Karsten Schoelzel <kuser at gmx.de> writes:
> 
> > Hi,
> >
> > extending the patch with automagic-tagging and automagic-moving of
> > on window start
> >
> >   This patch needs changes to the core of xmonad to work,
> >   but most work is done is in the TagWindows module:
> >   - add/delete tags
> >   - automatically adding tags on window creation based on window class, name, command
> >   - use tags for automagically assigning workspaces to windows (including floating status)
> >       * adding a tag "~" makes the window floating initially
> 
> This could play quite well with mplayer.
> 
> >       * adding a existing workspace id will move the window to workspace with that id,
> >           e.g. adding "2" will move the window to the second workspace
> 
> Then you need to define some specific groups of tags, like
> "1", "2",... for workspace and the "~" for floating.
> Otherwise, it could easily get confused when you assign more
> integers to it, couldn't it?
> 
Currently the workspaces are named "1", "2", ... "9" by default, but you
could name them differently, e.g. "gimp". If you now automagic-assign
the tag "gimp" to a window, it will start on the workspace "gimp".

I've seen the "~" for floating in the wmii sources and thought it would
be good for the purpose, because "~" isn't a good name for a workspace
in my opinion (we have all the other strings to choose from like
"whatever i like to choose i will choose" ;-))

> >   - change focus restricted to a group of windows with a specified tag,
> >       either only on the current workspace or globally
> >   
> > The two rules in tagMatches below state:
> >   - tag every window with WM_CLASS = gimp with the tags "2" and "~",
> >         thus moving them to workspace "2" and float them
> >   - tag every xterm window which has "screen" as an argument gets with
> >     "abc"
> >
> > As it is a bit invasive I'd like to hear your comments.
> >
> > Regards,
> > Karsten
> 
> As you described, it looks quite impressive.  And I really
> like this idea.  Apart from assigning predefined tags, I'd
> like a method to change the tag dynamically.  Could it be a
> smart way to use the XPrompt code to assign the tag and
> later choose some specific tag?

Nice idea, here we go a patch to TagWindows adding to prompts:
 - tagPrompt takes an action f, asks for a tag (with the completions
   being all tags assigned to any window currently managed by xmonad)
   and calls f with tag you entered
 - tagDelPrompt lets you enter a tag to be deleted from the focused
   window (only the tags of the focused window are shown)

The function mkComplFunFromList' differs from the original, that it will
show all strings from the list if there is no input given, i.e. all tags
are shown on startup of the prompts. This shouldn't pose any problems
because the list will be small most of the times.

Regards,
Karsten

Sat Sep  8 18:29:13 CEST 2007  Karsten Schoelzel <kuser at gmx.de>
  * TagWindows prompt addition
diff -rN -u old-XMonadContrib/TagWindows.hs new-XMonadContrib/TagWindows.hs
--- old-XMonadContrib/TagWindows.hs	2007-09-08 18:44:06.000000000 +0200
+++ new-XMonadContrib/TagWindows.hs	2007-09-08 18:44:06.000000000 +0200
@@ -19,7 +19,8 @@
                  withTaggedM, withTaggedGlobalM,
                  focusTaggedUp, focusTaggedUpGlobal,
                  shiftX, shiftHere,
-                 tagManageHook, TagMatch (..), defaultTM
+                 tagManageHook, TagMatch (..), defaultTM,
+                 tagPrompt, tagDelPrompt
                  ) where
 
 import Data.Char (chr)
@@ -36,6 +37,8 @@
 
 import Graphics.X11.Xlib
 import Graphics.X11.Xlib.Extras
+
+import XMonadContrib.XPrompt
 import XMonad
 
 -- $usage
@@ -194,3 +197,36 @@
     "" -> []
     s' -> w : splitAtNull s''
           where (w, s'') = break (== (chr 0)) s'
+
+data TagPrompt = TagPrompt
+
+instance XPrompt TagPrompt where
+    showXPrompt TagPrompt = "Select Tag:   "
+
+tagPrompt :: XPConfig -> (String -> X ()) -> X ()
+tagPrompt c f = do
+  sc <- tagComplList
+  mkXPrompt TagPrompt c (mkComplFunFromList' sc) f
+
+tagComplList :: X [String]
+tagComplList = gets (Set.toList . Set.unions . Map.elems . windowtags . windowset)
+
+tagDelPrompt :: XPConfig -> X ()
+tagDelPrompt c = do
+  sc <- tagDelComplList
+  if (sc /= []) 
+    then mkXPrompt TagPrompt c (mkComplFunFromList' sc) (\s -> withFocusedX (delTag s))
+    else return ()
+
+tagDelComplList :: X [String]
+tagDelComplList = do
+    wset <- gets windowset
+    let c   = maybe [] s (peek wset)
+        s w = maybe [] Set.toList (Map.lookup w (windowtags wset))
+    return c
+
+
+mkComplFunFromList' :: [String] -> String -> IO [String]
+mkComplFunFromList' l [] = return l
+mkComplFunFromList' l s =
+  return $ filter (\x -> take (length s) x == s) l



More information about the Xmonad mailing list