xmonad-contrib-0.11.1: Third party extensions for xmonad

Portabilityunportable
Stabilityunstable
Maintainervogt.adam@gmail.com
Safe HaskellNone

XMonad.Layout.SubLayouts

Contents

Description

A layout combinator that allows layouts to be nested.

Synopsis

Usage

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

 import XMonad.Layout.SubLayouts
 import XMonad.Layout.WindowNavigation

Using XMonad.Layout.BoringWindows is optional and it allows you to add a keybinding to skip over the non-visible windows.

 import XMonad.Layout.BoringWindows

Then edit your layoutHook by adding the subTabbed layout modifier:

 myLayout = windowNavigation $ subTabbed $ boringWindows $
                        Tall 1 (3/100) (1/2) ||| etc..
 main = xmonad defaultConfig { layoutHook = myLayout }

XMonad.Layout.WindowNavigation is used to specify which windows to merge, and it is not integrated into the modifier because it can be configured, and works best as the outer modifier.

Then to your keybindings add:

 , ((modm .|. controlMask, xK_h), sendMessage $ pullGroup L)
 , ((modm .|. controlMask, xK_l), sendMessage $ pullGroup R)
 , ((modm .|. controlMask, xK_k), sendMessage $ pullGroup U)
 , ((modm .|. controlMask, xK_j), sendMessage $ pullGroup D)

 , ((modm .|. controlMask, xK_m), withFocused (sendMessage . MergeAll))
 , ((modm .|. controlMask, xK_u), withFocused (sendMessage . UnMerge))

 , ((modm .|. controlMask, xK_period), onGroup W.focusUp')
 , ((modm .|. controlMask, xK_comma), onGroup W.focusDown')

These additional keybindings require the optional XMonad.Layout.BoringWindows layoutModifier. The focus will skip over the windows that are not focused in each sublayout.

 , ((modm, xK_j), focusDown)
 , ((modm, xK_k), focusUp)

A submap can be used to make modifying the sublayouts using onGroup and toSubl simpler:

 ,((modm, xK_s), submap $ defaultSublMap conf)

NOTE: is there some reason that asks config >>= submap . defaultSublMap could not be used in the keybinding instead? It avoids having to explicitly pass the conf.

For more detailed instructions, see:

XMonad.Doc.Extending XMonad.Doc.Extending

subLayout :: [Int] -> subl a -> l a -> ModifiedLayout (Sublayout subl) l aSource

The main layout modifier arguments:

subLayout advanceInnerLayouts innerLayout outerLayout
advanceInnerLayouts
When a new group at index n in the outer layout is created (even with one element), the innerLayout is used as the layout within that group after being advanced with advanceInnerLayouts !! n NextLayout messages. If there is no corresponding element in the advanceInnerLayouts list, then innerLayout is not given any NextLayout messages.
innerLayout
The single layout given to be run as a sublayout.
outerLayout
The layout that determines the rectangles given to each group.

Ex. The second group is Tall, the third is Circle, all others are tabbed with:

 myLayout = addTabs shrinkText defaultTheme
          $ subLayout [0,1,2] (Simplest ||| Tall 1 0.2 0.5 ||| Circle)
          $ Tall 1 0.2 0.5 ||| Full

pushGroup :: Direction2D -> NavigateSource

pullGroup, pushGroup allow you to merge windows or groups inheriting the position of the current window (pull) or the other window (push).

pushWindow and pullWindow move individual windows between groups. They are less effective at preserving window positions.

pullGroup :: Direction2D -> NavigateSource

pullGroup, pushGroup allow you to merge windows or groups inheriting the position of the current window (pull) or the other window (push).

pushWindow and pullWindow move individual windows between groups. They are less effective at preserving window positions.

pushWindow :: Direction2D -> NavigateSource

pullGroup, pushGroup allow you to merge windows or groups inheriting the position of the current window (pull) or the other window (push).

pushWindow and pullWindow move individual windows between groups. They are less effective at preserving window positions.

pullWindow :: Direction2D -> NavigateSource

pullGroup, pushGroup allow you to merge windows or groups inheriting the position of the current window (pull) or the other window (push).

pushWindow and pullWindow move individual windows between groups. They are less effective at preserving window positions.

onGroup :: (Stack Window -> Stack Window) -> X ()Source

Apply a function on the stack belonging to the currently focused group. It works for rearranging windows and for changing focus.

toSubl :: Message a => a -> X ()Source

Send a message to the currently focused sublayout.

mergeDir :: (Stack Window -> Stack Window) -> Window -> GroupMsg WindowSource

merge the window that would be focused by the function when applied to the W.Stack of all windows, with the current group removed. The given window should be focused by a sublayout. Example usage: withFocused (sendMessage . mergeDir W.focusDown')

data GroupMsg a Source

GroupMsg take window parameters to determine which group the action should be applied to

Constructors

UnMerge a

free the focused window from its tab stack

UnMergeAll a

separate the focused group into singleton groups

Merge a a

merge the first group into the second group

MergeAll a

make one large group, keeping the parameter focused

Migrate a a

used to the window named in the first argument to the second argument's group, this may be replaced by a combination of UnMerge and Merge

WithGroup (Stack a -> X (Stack a)) a 
SubMessage SomeMessage a

the sublayout with the given window will get the message

data Broadcast Source

Constructors

Broadcast SomeMessage

send a message to all sublayouts

defaultSublMap :: XConfig l -> Map (KeyMask, KeySym) (X ())Source

defaultSublMap is an attempt to create a set of keybindings like the defaults ones but to be used as a submap for sending messages to the sublayout.

data Sublayout l a Source

Instances

(Read (l Window), Show (l Window), LayoutClass l Window) => LayoutModifier (Sublayout l) Window 
(Read a, Read (l a)) => Read (Sublayout l a) 
(Show a, Show (l a)) => Show (Sublayout l a) 

Screenshots

Todo

Issue 288

XMonad.Layout.ResizableTile assumes that its environment contains only the windows it is running: sublayouts are currently run with the stack containing only the windows passed to it in its environment, but any changes that the layout makes are not merged back.

Should the behavior be made optional?

Features

  • suggested managehooks for merging specific windows, or the apropriate layout based hack to find out the number of groups currently showed, but the size of current window groups is not available (outside of this growing module)

SimpleTabbed as a SubLayout

subTabbed works well, but it would be more uniform to avoid the use of addTabs, with the sublayout being Simplest (but simpleTabbed is this...). The only thing to be gained by fixing this issue is the ability to mix and match decoration styles. Better compatibility with some other layouts of which I am not aware could be another benefit.

simpleTabbed (and other decorated layouts) fail horribly when used as subLayouts:

  • decorations stick around: layout is run after being told to Hide
  • mouse events do not change focus: the group-ungroup does not respect the focus changes it wants?
  • sending ReleaseResources before running it makes xmonad very slow, and still leaves borders sticking around