xmonad-contrib-0.18.0.9: Community-maintained extensions for xmonad
Copyright(c) 2018 Yclept Nemo
LicenseBSD-style (see LICENSE)
Maintainer
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Actions.SwapPromote

Description

Module for tracking master window history per workspace, and associated functions for manipulating the stack using such history.

Synopsis

Usage

Given your configuration file, import this module:

import XMonad.Actions.SwapPromote

First add masterHistoryHook to your logHook to track master windows per workspace:

myLogHook = otherHook >> masterHistoryHook

Then replace xmonad's default promote keybinding with swapPromote':

, ((mod1Mask, xK_Return), swapPromote' False)

Depending on your xmonad configuration or window actions the master history may be empty. If this is the case you can still chain another promotion function:

import XMonad.Actions.DwmPromote
, ((mod1Mask, xK_Return), whenX (swapPromote False) dwmpromote)

To be clear, this is only called when the lack of master history hindered the swap and not other conditions, such as having a only a single window.

While swapPromote preserves window focus, swapIn preserves the focus position - effectively "swapping" new windows into focus without moving the zipper. A mix of both, swapHybrid promotes focused non-master windows while swapping windows into the focused master. This works well on layouts with large masters. Both come with chainable variants, see swapIn' and swapHybrid'.

So far floating windows have been treated no differently than tiled windows even though their positions are independent of the stack. Often, yanking floating windows in and out of the workspace will obliterate the stack history - particularly frustrating with XMonad.Util.Scratchpad since it is toggled so frequenty and always replaces the master window. That's why the swap functions accept a boolean argument; when True non-focused floating windows will be ignored.

All together:

, ((mod1Mask, xK_Return), whenX (swapHybrid True) dwmpromote)

newtype MasterHistory Source #

Mapping from workspace tag to master history list. The current master is the head of the list, the previous master the second element, and so on. Without history, the list is empty.

State Accessors

getMasterHistoryMap :: X (Map WorkspaceId [Window]) Source #

Return the master history map from the state.

getMasterHistoryFromTag :: WorkspaceId -> X [Window] Source #

Return the master history list of a given tag. The master history list may be empty. An invalid tag will also result in an empty list.

getMasterHistoryCurrent :: X [Window] Source #

Return the master history list of the current workspace.

getMasterHistoryFromWindow :: Window -> X [Window] Source #

Return the master history list of the workspace containing the given window. Return an empty list if the window is not in the stackset.

modifyMasterHistoryFromTag :: WorkspaceId -> ([Window] -> [Window]) -> X () Source #

Modify the master history list of a given workspace, or the empty list of no such workspace is mapped. The result is then re-inserted into the master history map.

modifyMasterHistoryCurrent :: ([Window] -> [Window]) -> X () Source #

Modify the master history list of the current workspace. While the current workspace is guaranteed to exist; its master history may not. For more information see modifyMasterHistoryFromTag.

Log Hook

masterHistoryHook :: X () Source #

A logHook to update the master history mapping. Non-existent workspaces are removed, and the master history list for the current workspaces is updated. See masterHistoryHook'.

Log Hook Building Blocks

masterHistoryHook' Source #

Arguments

:: Bool

If True, remove non-existent workspaces.

-> ([Window] -> [Window] -> [Window])

Function used to update the master history list of the current workspace. First argument is the master history, second is the integrated stack. See updateMasterHistory for more details.

-> X () 

Backend for masterHistoryHook.

updateMasterHistory Source #

Arguments

:: [Window]

The master history list.

-> [Window]

The integrated stack.

-> [Window] 

Given the current master history list and an integrated stack, return the new master history list. The current master is either moved (if it exists within the history) or added to the head of the list, and all missing (i.e. closed) windows are removed.

Actions

swapPromote' :: Bool -> X () Source #

Like swapPromote' but discard the result.

swapIn :: Bool -> X Bool Source #

Wrap swapInStack; see also swapApply.

swapIn' :: Bool -> X () Source #

Like swapIn' but discard the result.

swapHybrid' :: Bool -> X () Source #

Like swapHybrid' but discard the result.

Action Building Blocks

swapApply :: Bool -> (Maybe Window -> Stack Window -> (Bool, Stack Window)) -> X Bool Source #

Apply the given master history stack modifier to the current stack. If given True, all non-focused floating windows will be ignored. Return True if insufficient history; if so use whenX to sequence a backup promotion function.

swapPromoteStack :: Maybe Window -> Stack Window -> (Bool, Stack Window) Source #

If the focused window is the master window and there is no previous master, do nothing. Otherwise swap the master with the previous master. If the focused window is not the master window, swap it with the master window. In either case focus follows the original window, i.e. the focused window does not change, only its position.

The first argument is the previous master (which may not exist), the second a window stack. Return True if the master history hindered the swap; the history is either empty or out-of-sync. Though the latter shouldn't happen this function never changes the stack under such circumstances.

swapInStack :: Maybe Window -> Stack Window -> (Bool, Stack Window) Source #

Perform the same swap as swapPromoteStack. However the new window receives the focus; it appears to "swap into" the position of the original window. Under this model focus follows stack position and the zipper does not move.

See swapPromoteStack for more details regarding the parameters.

swapHybridStack :: Maybe Window -> Stack Window -> (Bool, Stack Window) Source #

If the focused window is the master window, use swapInStack. Otherwise use swapPromoteStack.

See swapPromoteStack for more details regarding the parameters.

List Utilities

cycleN :: Int -> [a] -> [a] Source #

Cycle a list by the given count. If positive, cycle to the left. If negative, cycle to the right:

>>> cycleN 2 [1,2,3,4,5]
[3,4,5,1,2]
>>> cycleN (-2) [1,2,3,4,5]
[4,5,1,2,3]

split :: (Num a, Enum a) => (b -> Bool) -> [b] -> ([(a, b)], [b]) Source #

Wrap split' with an initial index of 0, discarding the list's length.

split' :: (Num a, Enum a) => (b -> Bool) -> a -> [b] -> (a, [(a, b)], [b]) Source #

Given a predicate, an initial index and a list, return a tuple containing:

  • List length.
  • Indexed list of elements which satisfy the predicate. An indexed element is a tuple containing the element index (offset by the initial index) and the element.
  • List of elements which do not satisfy the predicate.

The initial index and length of the list simplify chaining calls to this function, such as for zippers of lists.

merge :: (Ord a, Num a) => [(a, b)] -> [b] -> [b] Source #

Wrap merge' with an initial virtual index of 0. Return only the unindexed list with elements from the leftover indexed list appended.

merge' :: (Ord a, Num a) => a -> [(a, b)] -> [b] -> (a, [(a, b)], [b]) Source #

Inverse of split. Merge an indexed list with an unindexed list (see split'). Given a virtual index, an indexed list and an unindexed list, return a tuple containing:

  • Virtual index after the unindexed list
  • Remainder of the indexed list
  • Merged unindexed list

If the indexed list is empty, this functions consumes the entire unindexed list. If the unindexed list is empty, this function consumes only adjacent indexed elements. For example, [(10,"ten"),(12,"twelve")] implies missing unindexed elements and so once (10,"ten") is consumed this function concludes.

The indexed list is assumed to have been created by split' and not checked for correctness. Indices are assumed to be ascending, i.e. > [(1,"one"),(2,"two"),(4,"four")]

The initial and final virtual indices simplify chaining calls to the this function, as as for zippers of lists. Positive values shift the unindexed list towards the tail, as if preceded by that many elements.

Stack Utilities

stackSplit :: (Num a, Enum a, Ord b) => Stack b -> Set b -> ([(a, b)], Stack b) Source #

Remove all elements of the set from the stack. Skip the currently focused member. Return an indexed list of excluded elements and the modified stack. Use stackMerge to re-insert the elements using this list.

stackMerge :: (Ord a, Num a) => Stack b -> [(a, b)] -> Stack b Source #

Inverse of stackSplit. Given a list of elements and their original indices, re-insert the elements into these same positions within the stack. Skip the currently focused member. Works best if the stack's length hasn't changed, though if shorter any leftover elements will be tacked on.