| Copyright | (c) 2009 Adam Vogt <vogt.adam@gmail.com> | 
|---|---|
| License | BSD | 
| Maintainer | Adam Vogt | 
| Stability | unstable | 
| Portability | unportable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
XMonad.Actions.WorkspaceCursors
Description
Like XMonad.Actions.Plane for an arbitrary number of dimensions.
- focusDepth :: Cursors t -> Int
- makeCursors :: [[String]] -> Cursors String
- toList :: Foldable t => forall a. t a -> [a]
- workspaceCursors :: Cursors String -> l a -> ModifiedLayout WorkspaceCursors l a
- data WorkspaceCursors a
- getFocus :: Cursors b -> b
- modifyLayer :: (Stack (Cursors String) -> Stack (Cursors String)) -> Int -> X ()
- modifyLayer' :: (Stack (Cursors String) -> X (Stack (Cursors String))) -> Int -> X ()
- shiftModifyLayer :: (Stack (Cursors String) -> Stack (Cursors WorkspaceId)) -> Int -> X ()
- shiftLayer :: (Stack (Cursors String) -> Stack (Cursors WorkspaceId)) -> Int -> X ()
- focusNth' :: Int -> Stack a -> Stack a
- noWrapUp :: Stack t -> Stack t
- noWrapDown :: Stack t -> Stack t
- data Cursors a
Usage
Here is an example config:
import XMonad
import XMonad.Actions.WorkspaceCursors
import XMonad.Hooks.DynamicLog
import XMonad.Util.EZConfig
import qualified XMonad.StackSet as W
main = do
    x <- xmobar conf
    xmonad x
conf = additionalKeysP def
       { layoutHook = workspaceCursors myCursors $ layoutHook def
       , workspaces = toList myCursors } $
       [("M-"++shift++control++[k], f direction depth)
         | (f,shift) <- zip [modifyLayer,shiftModifyLayer] ["","S-"]
         , (direction,control) <- zip [W.focusUp',W.focusDown'] ["C-",""]
         , (depth,k) <- zip (reverse [1..focusDepth myCursors]) "asdf"]
       ++ moreKeybindings
moreKeybindings = []
myCursors = makeCursors $ map (map (\x -> [x])) [ "1234", "abc", "xyz"]
-- myCursors = makeCursors [["wsA","wsB","wsC"],["-alpha-","-beta-","-gamma-"],["x","y"]]focusDepth :: Cursors t -> Int Source
makeCursors :: [[String]] -> Cursors String Source
makeCursors requires a nonempty string, and each sublist must be nonempty
workspaceCursors :: Cursors String -> l a -> ModifiedLayout WorkspaceCursors l a Source
The state is stored in the WorkspaceCursors layout modifier. Put this as
 your outermost modifier, unless you want different cursors at different
 times (using XMonad.Layout.MultiToggle)
data WorkspaceCursors a Source
Instances
Modifying the focus
modifyLayer :: (Stack (Cursors String) -> Stack (Cursors String)) -> Int -> X () Source
modifyLayer is used to change the focus at a given depth
modifyLayer' :: (Stack (Cursors String) -> X (Stack (Cursors String))) -> Int -> X () Source
example usages are shiftLayer and shiftModifyLayer
shiftModifyLayer :: (Stack (Cursors String) -> Stack (Cursors WorkspaceId)) -> Int -> X () Source
shiftModifyLayer is the same as modifyLayer, but also shifts the
 currently focused window to the new workspace
shiftLayer :: (Stack (Cursors String) -> Stack (Cursors WorkspaceId)) -> Int -> X () Source
shiftLayer is the same as shiftModifyLayer, but the focus remains on
 the current workspace.
Functions to pass to modifyLayer
noWrapDown :: Stack t -> Stack t Source
non-wrapping version of focusDown'
Todo
- Find and document how to raise the allowable length of arguments:
   restoring xmonad's state results in: xmonad: executeFile: resource exhausted (Argument list too long)when you specify more than about 50 workspaces. Or change it such that workspaces are created when you try to view it.
- Function for pretty printing for DynamicLog that groups workspaces by common prefixes
- Examples of adding workspaces to the cursors, having them appear multiple times for being able to show jumping to some n'th multiple workspace