
Hi,
today I added the ability to add tags to windows. Some uses which are
possible with them right now:
* move a tag group of windows to another workspace at once
* get them back without switching to the other workspace
* change focus only in the group of windows with a specified tag
- if there is only one of them at the workspace this means
specifically that you can jump to a specific window wherever the
focus is and wherever the window is
Would be nice to get tags assigned automatically, but i haven't thought
about how to implement this ;-)
As it is work in progress (docs and cleanup needed) I would welcome
opinions suggestions as to what people might want to do with tagging.
Most parts of the code are in a Contrib module but where are also
changes in StackSet to store the tags therein. (Yesterday I wrote a
similar tagging module which stored the tags in the X Server in a
text-property of the window. But that turned out to be not very nice to
work with. If anybody wants to see that code, just ask :-))
Regards,
Karsten
Example settings in Config.hs
, ((modMask, xK_f ), withFocusedX (addTag "abc"))
, ((modMask .|. controlMask, xK_f ), withFocusedX (delTag "abc"))
-- Sink all windows with tag "abc" on all workspaces
, ((modMask .|. shiftMask, xK_f ), withTaggedGlobalM "abc" sink)
-- Move all windows with tag "abc" to workspace "2"
, ((modWinMask, xK_f ), withTagged "abc" (shiftX "2"))
-- Move all windows with tag "abc" from all workspaces to the current workspace
, ((modWinMask .|. shiftMask, xK_f ), withTaggedGlobal "abc" shiftHere)
-- Change focus with "abc" windows
, ((modWinMask .|. controlMask, xK_f ), focusTaggedUp "abc")
diff -rN -u old-xmonad/StackSet.hs new-xmonad/StackSet.hs
--- old-xmonad/StackSet.hs 2007-09-08 00:36:44.000000000 +0200
+++ new-xmonad/StackSet.hs 2007-09-08 00:36:44.000000000 +0200
@@ -22,11 +22,11 @@
-- * Operations on the current stack
-- $stackOperations
peek, index, integrate, integrate', differentiate,
- focusUp, focusDown,
- focusWindow, tagMember, member, findIndex,
+ focusUp, focusDown, focusUp',
+ focusWindow, workspaces, tagMember, member, findIndex,
-- * Modifying the stackset
-- $modifyStackset
- insertUp, delete, filter,
+ insertUp, delete, deletetmp, filter,
-- * Setting the master window
-- $settingMW
swapMaster, swapUp, swapDown, modify, modify', float, sink, -- needed by users
@@ -39,6 +39,7 @@
import Data.Maybe (listToMaybe)
import qualified Data.List as L (delete,deleteBy,find,splitAt,filter)
import qualified Data.Map as M (Map,insert,delete,empty)
+import Data.Set (Set)
-- $intro
--
@@ -151,6 +152,7 @@
, visible :: [Screen i a sid sd] -- ^ non-focused workspaces, visible in xinerama
, hidden :: [Workspace i a] -- ^ workspaces not visible anywhere
, floating :: M.Map a RationalRect -- ^ floating windows
+ , windowtags :: M.Map a (Set i) -- ^ window tags
} deriving (Show, Read, Eq)
-- | Visible workspaces, and their Xinerama screens.
@@ -208,7 +210,7 @@
-- Xinerama: Virtual workspaces are assigned to physical screens, starting at 0.
--
new :: (Integral s) => [i] -> [sd] -> StackSet i a s sd
-new wids m | not (null wids) && length m <= length wids = StackSet cur visi unseen M.empty
+new wids m | not (null wids) && length m <= length wids = StackSet cur visi unseen M.empty M.empty
where (seen,unseen) = L.splitAt (length m) $ map (flip Workspace Nothing) wids
(cur:visi) = [ Screen i s sd | (i, s, sd) <- zip3 seen [0..] m ]
-- now zip up visibles with their screen id
@@ -453,9 +455,16 @@
-- * otherwise, delete doesn't affect the master.
--
delete :: (Ord a, Eq s) => a -> StackSet i a s sd -> StackSet i a s sd
-delete w s = s { current = removeFromScreen (current s)
- , visible = map removeFromScreen (visible s)
- , hidden = map removeFromWorkspace (hidden s) }
+delete w s = s' { floating = M.delete w (floating s')
+ , windowtags = M.delete w (windowtags s') }
+ where s' = deletetmp w s
+
+-- only temporarily remove the window from the stack, thereby not destroying special
+-- information saved in the Stackset
+deletetmp :: (Ord a, Eq s) => a -> StackSet i a s sd -> StackSet i a s sd
+deletetmp w s = s { current = removeFromScreen (current s)
+ , visible = map removeFromScreen (visible s)
+ , hidden = map removeFromWorkspace (hidden s) }
where removeFromWorkspace ws = ws { stack = stack ws >>= filter (/=w) }
removeFromScreen scr = scr { workspace = removeFromWorkspace (workspace scr) }
@@ -495,5 +504,5 @@
shift :: (Ord a, Eq s, Eq i) => i -> StackSet i a s sd -> StackSet i a s sd
shift n s | n `tagMember` s && n /= curtag = maybe s go (peek s)
| otherwise = s
- where go w = view curtag . insertUp w . view n . delete w $ s
+ where go w = view curtag . insertUp w . view n . deletetmp w $ s
curtag = tag (workspace (current s))
TagWindows.hs
-----------------------------------------------------------------------------
-- |
-- Module : XMonadContrib.TagWindows
-- Copyright : (c) Karsten Schoelzel

On Sat, Sep 08, 2007 at 01:03:57AM +0200, Karsten Schoelzel wrote:
Hi,
today I added the ability to add tags to windows. Some uses which are possible with them right now: * move a tag group of windows to another workspace at once * get them back without switching to the other workspace * change focus only in the group of windows with a specified tag - if there is only one of them at the workspace this means specifically that you can jump to a specific window wherever the focus is and wherever the window is
Would be nice to get tags assigned automatically, but i haven't thought about how to implement this ;-)
As it is work in progress (docs and cleanup needed) I would welcome opinions suggestions as to what people might want to do with tagging. Most parts of the code are in a Contrib module but where are also changes in StackSet to store the tags therein. (Yesterday I wrote a similar tagging module which stored the tags in the X Server in a text-property of the window. But that turned out to be not very nice to work with. If anybody wants to see that code, just ask :-))
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
* 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
- 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
diff -rN -u old-xmonad/Config.hs new-xmonad/Config.hs
@@ -120,6 +133,20 @@
logHook = return ()
-- |
+-- Perform an arbitrary action on window manage event.
+--
+manageHook :: Window -> X (Bool)
+manageHook = tagManageHook tagMatches
+--manageHook = do \_ -> return (False)
+
+tagMatches :: [TagMatch]
+tagMatches = [
+ defaultTM { tmclass = ("gimp" `elem`), tmtags = ["2", "~"] }
+ , defaultTM { tmcommand = ("screen" `elem`), tmclass = ("xterm" `elem`), tmtags = ["abc"] }
+ ]
+
+-- Examples include:
+-- |
-- The key bindings list.
--
-- The unusual comment format is used to generate the documentation
@@ -152,6 +180,17 @@
, ((modMask, xK_l ), sendMessage Expand) -- @@ Expand the master area
, ((modMask, xK_t ), withFocused sink) -- @@ Push window back into tiling
+ , ((modMask, xK_f ), withFocusedX (addTag "abc"))
+ , ((modMask .|. controlMask, xK_f ), withFocusedX (delTag "abc"))
+ , ((modMask .|. shiftMask, xK_f ), withTaggedGlobalM "abc" sink)
+ , ((modWinMask, xK_f ), withTagged "abc" (shiftX "2"))
+ , ((modWinMask .|. shiftMask, xK_f ), withTaggedGlobal "abc" shiftHere)
+ , ((modWinMask .|. controlMask, xK_f ), focusTaggedUpGlobal "abc")
-- increase or decrease number of windows in the master area
, ((modMask , xK_comma ), sendMessage (IncMasterN 1)) -- @@ Increment the number of windows in the master area
diff -rN -u old-xmonad/Config.hs-boot new-xmonad/Config.hs-boot
--- old-xmonad/Config.hs-boot 2007-09-08 16:32:04.000000000 +0200
+++ new-xmonad/Config.hs-boot 2007-09-08 16:32:04.000000000 +0200
@@ -1,8 +1,9 @@
module Config where
import Graphics.X11.Xlib.Types (Dimension)
-import Graphics.X11.Xlib (KeyMask)
+import Graphics.X11.Xlib (KeyMask,Window)
import XMonad
borderWidth :: Dimension
logHook :: X ()
+manageHook :: Window -> X (Bool)
numlockMask :: KeyMask
workspaces :: [WorkspaceId]
diff -rN -u old-xmonad/Operations.hs new-xmonad/Operations.hs
--- old-xmonad/Operations.hs 2007-09-08 16:32:04.000000000 +0200
+++ new-xmonad/Operations.hs 2007-09-08 16:32:04.000000000 +0200
@@ -18,7 +18,7 @@
import XMonad
import qualified StackSet as W
-import {-# SOURCE #-} Config (borderWidth,logHook,numlockMask)
+import {-# SOURCE #-} Config (borderWidth,logHook,manageHook,numlockMask)
import Data.Maybe
import Data.List (nub, (\\), find)
@@ -49,19 +49,23 @@
--
manage :: Window -> X ()
manage w = whenX (fmap not $ isClient w) $ withDisplay $ \d -> do
- setInitialProperties w >> reveal w
-- FIXME: This is pretty awkward. We can't can't let "refresh" happen
-- before the call to float, because that will resize the window and
-- lose the default sizing.
-
- sh <- io $ getWMNormalHints d w
- let isFixedSize = sh_min_size sh /= Nothing && sh_min_size sh == sh_max_size sh
- isTransient <- isJust `liftM` io (getTransientForHint d w)
- if isFixedSize || isTransient
- then do modify $ \s -> s { windowset = W.insertUp w (windowset s) }
- float w -- \^^ now go the refresh.
- else windows $ W.insertUp w
+
+ managed <- manageHook w
+ if not managed
+ then do
+ setInitialProperties w >> reveal w
+ sh <- io $ getWMNormalHints d w
+ let isFixedSize = sh_min_size sh /= Nothing && sh_min_size sh == sh_max_size sh
+ isTransient <- isJust `liftM` io (getTransientForHint d w)
+ if isFixedSize || isTransient
+ then do modify $ \s -> s { windowset = W.insertUp w (windowset s) }
+ float w -- \^^ now go the refresh.
+ else windows $ W.insertUp w
+ else return ()
-- | unmanage. A window no longer exists, remove it from the window
-- list, on whatever workspace it is.
diff -rN -u old-xmonad/StackSet.hs new-xmonad/StackSet.hs
--- old-xmonad/StackSet.hs 2007-09-08 16:32:04.000000000 +0200
+++ new-xmonad/StackSet.hs 2007-09-08 16:32:04.000000000 +0200
@@ -22,11 +22,11 @@
-- * Operations on the current stack
-- $stackOperations
peek, index, integrate, integrate', differentiate,
- focusUp, focusDown,
- focusWindow, tagMember, member, findIndex,
+ focusUp, focusDown, focusUp',
+ focusWindow, workspaces, tagMember, member, findIndex,
-- * Modifying the stackset
-- $modifyStackset
- insertUp, delete, filter,
+ insertUp, delete, deletetmp, filter,
-- * Setting the master window
-- $settingMW
swapMaster, swapUp, swapDown, modify, modify', float, sink, -- needed by users
@@ -39,6 +39,7 @@
import Data.Maybe (listToMaybe)
import qualified Data.List as L (delete,deleteBy,find,splitAt,filter)
import qualified Data.Map as M (Map,insert,delete,empty)
+import Data.Set (Set)
-- $intro
--
@@ -151,6 +152,7 @@
, visible :: [Screen i a sid sd] -- ^ non-focused workspaces, visible in xinerama
, hidden :: [Workspace i a] -- ^ workspaces not visible anywhere
, floating :: M.Map a RationalRect -- ^ floating windows
+ , windowtags :: M.Map a (Set i) -- ^ window tags
} deriving (Show, Read, Eq)
-- | Visible workspaces, and their Xinerama screens.
@@ -208,7 +210,7 @@
-- Xinerama: Virtual workspaces are assigned to physical screens, starting at 0.
--
new :: (Integral s) => [i] -> [sd] -> StackSet i a s sd
-new wids m | not (null wids) && length m <= length wids = StackSet cur visi unseen M.empty
+new wids m | not (null wids) && length m <= length wids = StackSet cur visi unseen M.empty M.empty
where (seen,unseen) = L.splitAt (length m) $ map (flip Workspace Nothing) wids
(cur:visi) = [ Screen i s sd | (i, s, sd) <- zip3 seen [0..] m ]
-- now zip up visibles with their screen id
@@ -453,9 +455,16 @@
-- * otherwise, delete doesn't affect the master.
--
delete :: (Ord a, Eq s) => a -> StackSet i a s sd -> StackSet i a s sd
-delete w s = s { current = removeFromScreen (current s)
- , visible = map removeFromScreen (visible s)
- , hidden = map removeFromWorkspace (hidden s) }
+delete w s = s' { floating = M.delete w (floating s')
+ , windowtags = M.delete w (windowtags s') }
+ where s' = deletetmp w s
+
+-- only temporarily remove the window from the stack, thereby not destroying special
+-- information saved in the Stackset
+deletetmp :: (Ord a, Eq s) => a -> StackSet i a s sd -> StackSet i a s sd
+deletetmp w s = s { current = removeFromScreen (current s)
+ , visible = map removeFromScreen (visible s)
+ , hidden = map removeFromWorkspace (hidden s) }
where removeFromWorkspace ws = ws { stack = stack ws >>= filter (/=w) }
removeFromScreen scr = scr { workspace = removeFromWorkspace (workspace scr) }
@@ -495,5 +504,5 @@
shift :: (Ord a, Eq s, Eq i) => i -> StackSet i a s sd -> StackSet i a s sd
shift n s | n `tagMember` s && n /= curtag = maybe s go (peek s)
| otherwise = s
- where go w = view curtag . insertUp w . view n . delete w $ s
+ where go w = view curtag . insertUp w . view n . deletetmp w $ s
curtag = tag (workspace (current s))
Sat Sep 8 16:15:07 CEST 2007 Karsten Schoelzel

Karsten Schoelzel
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?
- 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? -- c/* __o/* <\ * (__ */\ <

On Sat, Sep 08, 2007 at 11:26:37AM -0400, Xiao-Yong Jin wrote:
Karsten Schoelzel
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
participants (2)
-
Karsten Schoelzel
-
Xiao-Yong Jin