aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Actions/TagWindows.hs
diff options
context:
space:
mode:
authorBrent Yorgey <byorgey@gmail.com>2007-11-27 20:32:13 +0100
committerBrent Yorgey <byorgey@gmail.com>2007-11-27 20:32:13 +0100
commit7049a94f71d36513df832f70b7f2b49671bff2a1 (patch)
tree0a42eb47259da97bd49a5cb7c2c0097b031050ed /XMonad/Actions/TagWindows.hs
parentab391999fabbb5d826e20fedf79dbade366cfdfd (diff)
downloadXMonadContrib-7049a94f71d36513df832f70b7f2b49671bff2a1.tar.gz
XMonadContrib-7049a94f71d36513df832f70b7f2b49671bff2a1.tar.xz
XMonadContrib-7049a94f71d36513df832f70b7f2b49671bff2a1.zip
TagWindows: haddock updates
darcs-hash:20071127193213-bd4d7-a33676bcdfe7f462fc0102a366869a110bb77f98.gz
Diffstat (limited to 'XMonad/Actions/TagWindows.hs')
-rw-r--r--XMonad/Actions/TagWindows.hs72
1 files changed, 36 insertions, 36 deletions
diff --git a/XMonad/Actions/TagWindows.hs b/XMonad/Actions/TagWindows.hs
index d28aeeb..030338c 100644
--- a/XMonad/Actions/TagWindows.hs
+++ b/XMonad/Actions/TagWindows.hs
@@ -38,45 +38,46 @@ import XMonad.Prompt
import XMonad hiding (workspaces)
-- $usage
---
--- To use window tags add in your Config.hs:
+--
+-- To use window tags, import this module into your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Actions.TagWindows
-- > import XMonad.Prompt -- to use tagPrompt
---
--- and add keybindings like as follows:
--
--- > , ((modMask, xK_f ), withFocused (addTag "abc"))
--- > , ((modMask .|. controlMask, xK_f ), withFocused (delTag "abc"))
--- > , ((modMask .|. shiftMask, xK_f ), withTaggedGlobal "abc" sink)
--- > , ((modMask, xK_d ), withTaggedP "abc" (shiftWin "2"))
--- > , ((modMask .|. shiftMask, xK_d ), withTaggedGlobalP "abc" shiftHere)
--- > , ((modMask .|. controlMask, xK_d ), focusUpTaggedGlobal "abc")
--- > , ((modMask, xK_g ), tagPrompt defaultXPConfig (\s -> withFocused (addTag s)))
--- > , ((modMask .|. controlMask, xK_g ), tagDelPrompt defaultXPConfig)
--- > , ((modMask .|. shiftMask, xK_g ), tagPrompt defaultXPConfig (\s -> withTaggedGlobal s float))
--- > , ((modWinMask, xK_g ), tagPrompt defaultXPConfig (\s -> withTaggedP s (shiftWin "2")))
--- > , ((modWinMask .|. shiftMask, xK_g ), tagPrompt defaultXPConfig (\s -> withTaggedGlobalP s shiftHere))
--- > , ((modWinMask .|. controlMask, xK_g), tagPrompt defaultXPConfig (\s -> focusUpTaggedGlobal s))
+-- and add keybindings such as the following:
--
--- NOTE: Tags are saved as space separated string and split with 'unwords' thus
--- if you add a tag "a b" the window will have the tags "a" and "b" but not "a b".
-
--- %import XMonad.Actions.TagWindows
--- %import XMonad.Prompt -- to use tagPrompt
+-- > , ((modMask x, xK_f ), withFocused (addTag "abc"))
+-- > , ((modMask x .|. controlMask, xK_f ), withFocused (delTag "abc"))
+-- > , ((modMask x .|. shiftMask, xK_f ), withTaggedGlobal "abc" sink)
+-- > , ((modMask x, xK_d ), withTaggedP "abc" (shiftWin "2"))
+-- > , ((modMask x .|. shiftMask, xK_d ), withTaggedGlobalP "abc" shiftHere)
+-- > , ((modMask x .|. controlMask, xK_d ), focusUpTaggedGlobal "abc")
+-- > , ((modMask x, xK_g ), tagPrompt defaultXPConfig (\s -> withFocused (addTag s)))
+-- > , ((modMask x .|. controlMask, xK_g ), tagDelPrompt defaultXPConfig)
+-- > , ((modMask x .|. shiftMask, xK_g ), tagPrompt defaultXPConfig (\s -> withTaggedGlobal s float))
+-- > , ((modWinMask, xK_g ), tagPrompt defaultXPConfig (\s -> withTaggedP s (shiftWin "2")))
+-- > , ((modWinMask .|. shiftMask, xK_g ), tagPrompt defaultXPConfig (\s -> withTaggedGlobalP s shiftHere))
+-- > , ((modWinMask .|. controlMask, xK_g ), tagPrompt defaultXPConfig (\s -> focusUpTaggedGlobal s))
+--
+-- NOTE: Tags are saved as space separated strings and split with
+-- 'unwords'. Thus if you add a tag \"a b\" the window will have
+-- the tags \"a\" and \"b\" but not \"a b\".
+--
+-- For detailed instructions on editing your key bindings, see
+-- "XMonad.Doc.Extending#Editing_key_bindings".
--- set multiple tags for a window at once (overriding any previous tags)
+-- | set multiple tags for a window at once (overriding any previous tags)
setTags :: [String] -> Window -> X ()
setTags = setTag . unwords
--- set a tag for a window (overriding any previous tags)
--- writes it to the "_XMONAD_TAGS" window property
+-- | set a tag for a window (overriding any previous tags)
+-- writes it to the \"_XMONAD_TAGS\" window property
setTag :: String -> Window -> X ()
setTag s w = withDisplay $ \d ->
io $ internAtom d "_XMONAD_TAGS" False >>= setTextProperty d w s
--- read all tags of a window
--- reads from the "_XMONAD_TAGS" window property
+-- | read all tags of a window
+-- reads from the \"_XMONAD_TAGS\" window property
getTags :: Window -> X [String]
getTags w = withDisplay $ \d ->
io $ catch (internAtom d "_XMONAD_TAGS" False >>=
@@ -85,36 +86,35 @@ getTags w = withDisplay $ \d ->
(\_ -> return [[]])
>>= return . words . unwords
--- check a window for the given tag
+-- | check a window for the given tag
hasTag :: String -> Window -> X Bool
hasTag s w = (s `elem`) `liftM` getTags w
--- add a tag to the existing ones
+-- | add a tag to the existing ones
addTag :: String -> Window -> X ()
addTag s w = do
tags <- getTags w
if (s `notElem` tags) then setTags (s:tags) w else return ()
--- remove a tag from a window, if it exists
+-- | remove a tag from a window, if it exists
delTag :: String -> Window -> X ()
delTag s w = do
tags <- getTags w
setTags (filter (/= s) tags) w
--- remove all tags
+-- | remove all tags
unTag :: Window -> X ()
unTag = setTag ""
--- Move the focus in a group of windows, which share the same given tag.
--- The Global variants move through all workspaces, whereas the other
--- ones operate only on the current workspace
+-- | Move the focus in a group of windows, which share the same given tag.
+-- The Global variants move through all workspaces, whereas the other
+-- ones operate only on the current workspace
focusUpTagged, focusDownTagged, focusUpTaggedGlobal, focusDownTaggedGlobal :: String -> X ()
focusUpTagged = focusTagged' (reverse . wsToList)
focusDownTagged = focusTagged' wsToList
focusUpTaggedGlobal = focusTagged' (reverse . wsToListGlobal)
focusDownTaggedGlobal = focusTagged' wsToListGlobal
---
wsToList :: (Ord i) => StackSet i l a s sd -> [a]
wsToList ws = crs ++ cls
where
@@ -140,7 +140,7 @@ findM _ [] = return Nothing
findM p (x:xs) = do b <- p x
if b then return (Just x) else findM p xs
--- apply a pure function to windows with a tag
+-- | apply a pure function to windows with a tag
withTaggedP, withTaggedGlobalP :: String -> (Window -> WindowSet -> WindowSet) -> X ()
withTaggedP t f = withTagged' t (winMap f)
withTaggedGlobalP t f = withTaggedGlobal' t (winMap f)
@@ -191,7 +191,7 @@ tagComplList = gets (concat . map (integrate' . stack) . workspaces . windowset)
tagDelPrompt :: XPConfig -> X ()
tagDelPrompt c = do
sc <- tagDelComplList
- if (sc /= [])
+ if (sc /= [])
then mkXPrompt TagPrompt c (mkComplFunFromList' sc) (\s -> withFocused (delTag s))
else return ()