xmonad-contrib-0.17.1.9: Community-maintained extensions for xmonad
Copyright(c) Joachim Breitner <mail@joachim-breitner.de>
Nelson Elhage <nelhage@mit.edu> (`toggleWS' function)
LicenseBSD3-style (see LICENSE)
MaintainerJoachim Breitner <mail@joachim-breitner.de>
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Actions.CycleWS

Description

Provides bindings to cycle forward or backward through the list of workspaces, to move windows between workspaces, and to cycle between screens. More general combinators provide ways to cycle through workspaces in various orders, to only cycle through some subset of workspaces, and to cycle by more than one workspace at a time.

Note that this module now subsumes the functionality of the former XMonad.Actions.RotView. Former users of rotView can simply replace rotView True with moveTo Next (Not emptyWS), and so on.

If you want to exactly replicate the action of rotView (cycling through workspace in order lexicographically by tag, instead of in the order specified in the config), it can be implemented as:

rotView b  = do t <- findWorkspace getSortByTag (bToDir b) (Not emptyWS) 1
                windows . greedyView $ t
  where bToDir True  = Next
        bToDir False = Prev
Synopsis

Usage

You can use this module with the following in your xmonad.hs file:

import XMonad.Actions.CycleWS

-- a basic CycleWS setup

  , ((modm,               xK_Down),  nextWS)
  , ((modm,               xK_Up),    prevWS)
  , ((modm .|. shiftMask, xK_Down),  shiftToNext)
  , ((modm .|. shiftMask, xK_Up),    shiftToPrev)
  , ((modm,               xK_Right), nextScreen)
  , ((modm,               xK_Left),  prevScreen)
  , ((modm .|. shiftMask, xK_Right), shiftNextScreen)
  , ((modm .|. shiftMask, xK_Left),  shiftPrevScreen)
  , ((modm,               xK_z),     toggleWS)

If you want to follow the moved window, you can use both actions:

  , ((modm .|. shiftMask, xK_Down), shiftToNext >> nextWS)
  , ((modm .|. shiftMask, xK_Up),   shiftToPrev >> prevWS)

You can also get fancier with moveTo, shiftTo, and findWorkspace. For example:

  , ((modm     , xK_f), moveTo Next emptyWS)  -- find a free workspace
  , ((modm .|. controlMask, xK_Right),        -- a crazy keybinding!
        do t <- findWorkspace getSortByXineramaRule Next (Not emptyWS) 2
           windows . view $ t                                         )

For detailed instructions on editing your key bindings, see the tutorial.

When using the toggle functions, in order to ensure that the workspace to which you switch is the previously viewed workspace, use the logHook in XMonad.Hooks.WorkspaceHistory.

Moving between workspaces

The following commands for moving the view and windows between workspaces are somewhat inflexible, but are very simple and probably Do The Right Thing for most users.

All of the commands in this section cycle through workspaces in the order in which they are given in your config.

nextWS :: X () Source #

Switch to the next workspace.

prevWS :: X () Source #

Switch to the previous workspace.

shiftToNext :: X () Source #

Move the focused window to the next workspace.

shiftToPrev :: X () Source #

Move the focused window to the previous workspace.

Toggling the previous workspace

 

toggleWS :: X () Source #

Toggle to the workspace displayed previously.

toggleWS' :: [WorkspaceId] -> X () Source #

Toggle to the previous workspace while excluding some workspaces.

-- Ignore the scratchpad workspace while toggling:
("M-b", toggleWS' ["NSP"])

toggleOrView :: WorkspaceId -> X () Source #

greedyView a workspace, or if already there, view the previously displayed workspace ala weechat. Change greedyView to toggleOrView in your workspace bindings as in the view faq at http://haskell.org/haskellwiki/Xmonad/Frequently_asked_questions. For more flexibility see toggleOrDoSkip.

Moving between screens (xinerama)

nextScreen :: X () Source #

View next screen

prevScreen :: X () Source #

View prev screen

shiftNextScreen :: X () Source #

Move focused window to workspace on next screen

shiftPrevScreen :: X () Source #

Move focused window to workspace on prev screen

swapNextScreen :: X () Source #

Swap current screen with next screen

swapPrevScreen :: X () Source #

Swap current screen with previous screen

Moving between workspaces, take two!

A few more general commands are also provided, which allow cycling through subsets of workspaces.

For example,

  moveTo Next emptyWS

will move to the first available workspace with no windows, and

  shiftTo Prev (WSIs $ return (('p' `elem`) . tag))

will move the focused window backwards to the first workspace containing the letter p in its name. =)

data Direction1D Source #

One-dimensional directions:

Constructors

Next 
Prev 

data WSType Source #

What type of workspaces should be included in the cycle?

Constructors

EmptyWS

Deprecated: Use emptyWS instead.

cycle through empty workspaces

NonEmptyWS

Deprecated: Use Not emptyWS instead.

cycle through non-empty workspaces

HiddenWS

Deprecated: Use hiddenWS instead.

cycle through non-visible workspaces

HiddenNonEmptyWS

Deprecated: Use hiddenWS :&: Not emptyWS instead.

cycle through non-empty non-visible workspaces

HiddenEmptyWS

Deprecated: Use hiddenWS :&: emptyWS instead.

cycle through empty non-visible workspaces

AnyWS

Deprecated: Use anyWS instead.

cycle through all workspaces

WSTagGroup Char

Deprecated: Use wsTagGroup instead.

cycle through workspaces in the same group, the group name is all characters up to the first separator character or the end of the tag

WSIs (X (WindowSpace -> Bool))

cycle through workspaces satisfying an arbitrary predicate

WSType :&: WSType

cycle through workspaces satisfying both predicates.

WSType :|: WSType

cycle through workspaces satisfying one of the predicates.

Not WSType

cycle through workspaces not satisfying the predicate

emptyWS :: WSType Source #

Cycle through empty workspaces

hiddenWS :: WSType Source #

Cycle through non-visible workspaces

anyWS :: WSType Source #

Cycle through all workspaces

wsTagGroup :: Char -> WSType Source #

Cycle through workspaces in the same group, the group name is all characters up to the first separator character or the end of the tag

ignoringWSs :: [WorkspaceId] -> WSType Source #

Cycle through workspaces that are not in the given list. This could, for example, be used for skipping the workspace reserved for XMonad.Util.NamedScratchpad:

 moveTo Next $ hiddenWS :&: Not emptyWS :&: ignoringWSs [scratchpadWorkspaceTag]

shiftTo :: Direction1D -> WSType -> X () Source #

Move the currently focused window to the next workspace in the given direction that satisfies the given condition.

moveTo :: Direction1D -> WSType -> X () Source #

View the next workspace in the given direction that satisfies the given condition.

doTo :: Direction1D -> WSType -> X WorkspaceSort -> (WorkspaceId -> X ()) -> X () Source #

Using the given sort, find the next workspace in the given direction of the given type, and perform the given action on it.

The mother-combinator

findWorkspace :: X WorkspaceSort -> Direction1D -> WSType -> Int -> X WorkspaceId Source #

Given a function s to sort workspaces, a direction dir, a predicate p on workspaces, and an integer n, find the tag of the workspace which is n away from the current workspace in direction dir (wrapping around if necessary), among those workspaces, sorted by s, which satisfy p.

For some useful workspace sorting functions, see XMonad.Util.WorkspaceCompare.

For ideas of what to do with a workspace tag once obtained, note that moveTo and shiftTo are implemented by applying (>>= (windows . greedyView)) and (>>= (windows . shift)), respectively, to the output of findWorkspace.

toggleOrDoSkip :: [WorkspaceId] -> (WorkspaceId -> WindowSet -> WindowSet) -> WorkspaceId -> X () Source #

Allows ignoring listed workspace tags (such as scratchpad's "NSP"), and running other actions such as view, shift, etc. For example:

import qualified XMonad.StackSet as W
import XMonad.Actions.CycleWS

-- toggleOrView for people who prefer view to greedyView
toggleOrView' = toggleOrDoSkip [] W.view

-- toggleOrView ignoring scratchpad and named scratchpad workspace
toggleOrViewNoSP = toggleOrDoSkip ["NSP"] W.greedyView

skipTags :: Eq i => [Workspace i l a] -> [i] -> [Workspace i l a] Source #

List difference (\\) for workspaces and tags. Removes workspaces matching listed tags from the given workspace list.

screenBy :: Int -> X ScreenId Source #

Get the ScreenId d places over. Example usage is a variation of the the default screen keybindings:

    -- mod-{w,e}, Switch to previous/next Xinerama screen
    -- mod-shift-{w,e}, Move client to previous/next Xinerama screen
    --
    [((m .|. modm, key), sc >>= screenWorkspace >>= flip whenJust (windows . f))
        | (key, sc) <- zip [xK_w, xK_e] [(screenBy (-1)),(screenBy 1)]
        , (f, m) <- [(W.view, 0), (W.shift, shiftMask)]]