xmonad-contrib-0.17.1: Community-maintained extensions for xmonad
Copyright(c) 2009 Adam Vogt <vogt.adam@gmail.com>
LicenseBSD
MaintainerAdam Vogt
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Actions.WorkspaceCursors

Description

Like XMonad.Actions.Plane for an arbitrary number of dimensions.

Synopsis

Usage

Here is an example config:

import XMonad
import XMonad.Actions.WorkspaceCursors
import XMonad.Util.EZConfig
import qualified XMonad.StackSet as W

main = xmonad conf

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"]]

makeCursors :: [[String]] -> Cursors String Source #

makeCursors requires a nonempty string, and each sublist must be nonempty

toList :: Foldable t => t a -> [a] #

List of elements of a structure, from left to right. If the entire list is intended to be reduced via a fold, just fold the structure directly bypassing the list.

Examples

Expand

Basic usage:

>>> toList Nothing
[]
>>> toList (Just 42)
[42]
>>> toList (Left "foo")
[]
>>> toList (Node (Leaf 5) 17 (Node Empty 12 (Leaf 8)))
[5,17,12,8]

For lists, toList is the identity:

>>> toList [1, 2, 3]
[1,2,3]

Since: base-4.8.0.0

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

Instances details
LayoutModifier WorkspaceCursors a Source # 
Instance details

Defined in XMonad.Actions.WorkspaceCursors

Read (WorkspaceCursors a) Source # 
Instance details

Defined in XMonad.Actions.WorkspaceCursors

Show (WorkspaceCursors a) Source # 
Instance details

Defined in XMonad.Actions.WorkspaceCursors

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

focusNth' :: Int -> Stack a -> Stack a Source #

noWrapUp :: Stack t -> Stack t Source #

non-wrapping version of focusUp'

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 XMonad.Hooks.StatusBar.PP 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

Types

data Cursors a Source #

Instances

Instances details
Foldable Cursors Source # 
Instance details

Defined in XMonad.Actions.WorkspaceCursors

Methods

fold :: Monoid m => Cursors m -> m #

foldMap :: Monoid m => (a -> m) -> Cursors a -> m #

foldMap' :: Monoid m => (a -> m) -> Cursors a -> m #

foldr :: (a -> b -> b) -> b -> Cursors a -> b #

foldr' :: (a -> b -> b) -> b -> Cursors a -> b #

foldl :: (b -> a -> b) -> b -> Cursors a -> b #

foldl' :: (b -> a -> b) -> b -> Cursors a -> b #

foldr1 :: (a -> a -> a) -> Cursors a -> a #

foldl1 :: (a -> a -> a) -> Cursors a -> a #

toList :: Cursors a -> [a] #

null :: Cursors a -> Bool #

length :: Cursors a -> Int #

elem :: Eq a => a -> Cursors a -> Bool #

maximum :: Ord a => Cursors a -> a #

minimum :: Ord a => Cursors a -> a #

sum :: Num a => Cursors a -> a #

product :: Num a => Cursors a -> a #

Functor Cursors Source # 
Instance details

Defined in XMonad.Actions.WorkspaceCursors

Methods

fmap :: (a -> b) -> Cursors a -> Cursors b #

(<$) :: a -> Cursors b -> Cursors a #

Read a => Read (Cursors a) Source # 
Instance details

Defined in XMonad.Actions.WorkspaceCursors

Show a => Show (Cursors a) Source # 
Instance details

Defined in XMonad.Actions.WorkspaceCursors

Methods

showsPrec :: Int -> Cursors a -> ShowS #

show :: Cursors a -> String #

showList :: [Cursors a] -> ShowS #

Eq a => Eq (Cursors a) Source # 
Instance details

Defined in XMonad.Actions.WorkspaceCursors

Methods

(==) :: Cursors a -> Cursors a -> Bool #

(/=) :: Cursors a -> Cursors a -> Bool #