xmonad-contrib/XMonad/Actions/SwapWorkspaces.hs
Tony Zorman 3d65a6bf72 Refer to the tutorial instead of X.D.Extending more often
Essentially, whenever the tutorial actually has decent material on the
subject matter.  The replacement is roughly done as follows:

  - logHook → tutorial
  - keybindings → tutorial, as this is thoroughly covered
  - manageHook → tutorial + X.D.Extending, as the manageHook stuff the
    tutorial talks about is a little bit of an afterthought.
  - X.D.Extending (on its own) → tutorial + X.D.Extending
  - layoutHook → tutorial + X.D.Extending, as the tutorial, while
    talking about layouts, doesn't necessarily have a huge focus there.
  - mouse bindings → leave this alone, as the tutorial does not at all
    talk about them.
2022-10-21 09:17:43 +02:00

67 lines
2.5 KiB
Haskell

-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Actions.SwapWorkspaces
-- Description : Swap workspace tags without having to move individual windows.
-- Copyright : (c) Devin Mullins <me@twifkak.com>
-- License : BSD3-style (see LICENSE)
--
-- Maintainer : Devin Mullins <me@twifkak.com>
-- Stability : unstable
-- Portability : unportable
--
-- Lets you swap workspace tags, so you can keep related ones next to
-- each other, without having to move individual windows.
--
-----------------------------------------------------------------------------
module XMonad.Actions.SwapWorkspaces (
-- * Usage
-- $usage
swapWithCurrent,
swapTo,
swapWorkspaces,
Direction1D(..)
) where
import XMonad (windows, X())
import XMonad.StackSet
import XMonad.Actions.CycleWS
import XMonad.Util.WorkspaceCompare
-- $usage
-- Add this import to your @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Actions.SwapWorkspaces
--
-- Then throw something like this in your keys definition:
--
-- > ++
-- > [((modm .|. controlMask, k), windows $ swapWithCurrent i)
-- > | (i, k) <- zip workspaces [xK_1 ..]]
--
-- After installing this update, if you're on workspace 1, hitting mod-ctrl-5
-- will swap workspaces 1 and 5.
--
-- For detailed instructions on editing your key bindings, see
-- <https://xmonad.org/TUTORIAL.html#customizing-xmonad the tutorial>.
-- | Swaps the currently focused workspace with the given workspace tag, via
-- @swapWorkspaces@.
swapWithCurrent :: Eq i => i -> StackSet i l a s sd -> StackSet i l a s sd
swapWithCurrent t s = swapWorkspaces t (currentTag s) s
-- | Say @swapTo Next@ or @swapTo Prev@ to move your current workspace.
-- This is an @X ()@ so can be hooked up to your keybindings directly.
swapTo :: Direction1D -> X ()
swapTo dir = findWorkspace getSortByIndex dir anyWS 1 >>= windows . swapWithCurrent
-- | Takes two workspace tags and an existing XMonad.StackSet and returns a new
-- one with the two corresponding workspaces' tags swapped.
swapWorkspaces :: Eq i => i -> i -> StackSet i l a s sd -> StackSet i l a s sd
swapWorkspaces t1 t2 = mapWorkspace swap
where swap w
| tag w == t1 = w { tag = t2 }
| tag w == t2 = w { tag = t1 }
| otherwise = w