xmonad-contrib-0.17.0: Community-maintained extensions extensions for xmonad
Copyright(c) 2019 Ningji Wei
LicenseBSD3-style (see LICENSE)
MaintainerNingji Wei <tidues@gmail.com>
Stabilityunstable
Portabilityunportable
Safe HaskellNone
LanguageHaskell2010

XMonad.Layout.TallMastersCombo

Description

A layout combinator that support Shrink, Expand, and IncMasterN just as the Tall layout, and also support operations of two master windows: a main master, which is the original master window; a sub master, the first window of the second pane. This combinator can be nested, and has a good support for using Tabbed as a sublayout.

Synopsis

Usage

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

import XMonad.Layout.TallMastersCombo

and make sure the Choose layout operator (|||) is hidden by adding the followings:

import XMonad hiding ((|||))
import XMonad.Layout hiding ((|||))

then, add something like

tmsCombineTwoDefault (Tall 0 (3/100) 0) simpleTabbed

This will make the Tall layout as the master pane, and simpleTabbed layout as the second pane. You can shrink, expand, and increase more windows to the master pane just like using the Tall layout.

To swap and/or focus the sub master window (the first window in the second pane), you can add the following key bindings

     , ((modm .|. shiftMask, m),         sendMessage $ FocusSubMaster)
     , ((modm .|. shiftMask, xK_Return), sendMessage $ SwapSubMaster)

In each pane, you can use multiple layouts with the (|||) combinator provided by this module, and switch between them with the FocusedNextLayout message. Below is one example

layout1 = Simplest ||| Tabbed
layout2 = Full ||| Tabbed ||| (RowsOrColumns True)
myLayout = tmsCombineTwoDefault layout1 layout2

then add the following key binding,

     , ((modm, w), sendMessage $ FocusedNextLayout)

Now, pressing this key will toggle the multiple layouts in the currently focused pane.

You can mirror this layout with the default Mirror key binding. But to have a more natural behaviors, you can use the SwitchOrientation message:

     , ((modm, xK_space), sendMessage $ SwitchOrientation)

This will not mirror the tabbed decoration, and will keep sub-layouts that made by TallMastersCombo and RowsOrColumns display in natural orientations.

To merge layouts more flexibly, you can use tmsCombineTwo instead.

tmsCombineTwo False 1 (3/100) (1/3) Simplest simpleTabbed

This creates a vertical merged layout with 1 window in the master pane, and the master pane shrinks and expands with a step of (3/100), and occupies (1/3) of the screen.

Each sub-layout have a focused window. To rotate between the focused windows across all the sub-layouts, using the following messages:

     , ((modm .|. mod1, j), sendMessage $ NextFocus)
     , ((modm .|. mod1, k), sendMessage $ PrevFocus)

this let you jump to the focused window in the next/previous sub-layout.

Finally, this combinator can be nested. Here is one example,

subLayout  = tmsCombineTwo False 1 (3/100) (1/2) Simplest simpleTabbed
layout1    = simpleTabbed ||| subLayout
layout2    = subLayout ||| simpleTabbed ||| (RowsOrColumns True)
baseLayout = tmsCombineTwoDefault layout1 layout2

mylayouts = smartBorders $
            avoidStruts $
            mkToggle (FULL ?? EOT) $
            baseLayout

this is a realization of the cool idea from

https://www.reddit.com/r/xmonad/comments/3vkrc3/does_this_layout_exist_if_not_can_anyone_suggest/

and is more flexible.

tmsCombineTwoDefault :: (LayoutClass l1 Window, LayoutClass l2 Window) => l1 Window -> l2 Window -> TMSCombineTwo l1 l2 Window Source #

Combine two layouts l1 l2 with default behaviors.

tmsCombineTwo :: (LayoutClass l1 Window, LayoutClass l2 Window) => Bool -> Int -> Rational -> Rational -> l1 Window -> l2 Window -> TMSCombineTwo l1 l2 Window Source #

A more flexible way of merging two layouts. User can specify if merge them vertical or horizontal, the number of windows in the first pane (master pane), the shink and expand increment, and the proportion occupied by the master pane.

data TMSCombineTwo l1 l2 a Source #

Constructors

TMSCombineTwo 

Fields

Instances

Instances details
(GetFocused l1 Window, GetFocused l2 Window) => LayoutClass (TMSCombineTwo l1 l2) Window Source # 
Instance details

Defined in XMonad.Layout.TallMastersCombo

(Read a, Read (l1 a), Read (l2 a)) => Read (TMSCombineTwo l1 l2 a) Source # 
Instance details

Defined in XMonad.Layout.TallMastersCombo

(Show a, Show (l1 a), Show (l2 a)) => Show (TMSCombineTwo l1 l2 a) Source # 
Instance details

Defined in XMonad.Layout.TallMastersCombo

Methods

showsPrec :: Int -> TMSCombineTwo l1 l2 a -> ShowS #

show :: TMSCombineTwo l1 l2 a -> String #

showList :: [TMSCombineTwo l1 l2 a] -> ShowS #

newtype RowsOrColumns a Source #

A simple layout that arranges windows in a row or a column with equal sizes. It can switch between row mode and column mode by listening to the message SwitchOrientation.

Constructors

RowsOrColumns 

Fields

(|||) :: l a -> r a -> ChooseWrapper l r a Source #

This is same as the Choose combination operator.

Messages

data SwitchOrientation Source #

A message that switches the orientation of TallMasterCombo layout and the RowsOrColumns layout. This is similar to the Mirror message, but Mirror cannot apply to hidden layouts, and when Mirror applies to the Tabbed decoration, it will also mirror the tabs, which may lead to unintended visualizations. The SwitchOrientation message refreshes layouts according to the orientation of the parent layout, and will not affect the Tabbed decoration.

Constructors

SwitchOrientation 

data SwapSubMaster Source #

This message swaps the current focused window with the sub master window (first window in the second pane).

Constructors

SwapSubMaster 

data FocusSubMaster Source #

This message changes the focus to the sub master window (first window in the second pane).

Constructors

FocusSubMaster 

data FocusedNextLayout Source #

This message triggers the NextLayout message in the pane that contains the focused window.

Constructors

FocusedNextLayout 

data ChangeFocus Source #

This is a message for changing to the previous or next focused window across all the sub-layouts.

Constructors

NextFocus 
PrevFocus 

Utilities

data ChooseWrapper l r a Source #

Constructors

ChooseWrapper LR (l a) (r a) (Choose l r a) 

Instances

Instances details
(GetFocused l a, GetFocused r a) => LayoutClass (ChooseWrapper l r) a Source # 
Instance details

Defined in XMonad.Layout.TallMastersCombo

Methods

runLayout :: Workspace WorkspaceId (ChooseWrapper l r a) a -> Rectangle -> X ([(a, Rectangle)], Maybe (ChooseWrapper l r a)) #

doLayout :: ChooseWrapper l r a -> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (ChooseWrapper l r a)) #

pureLayout :: ChooseWrapper l r a -> Rectangle -> Stack a -> [(a, Rectangle)] #

emptyLayout :: ChooseWrapper l r a -> Rectangle -> X ([(a, Rectangle)], Maybe (ChooseWrapper l r a)) #

handleMessage :: ChooseWrapper l r a -> SomeMessage -> X (Maybe (ChooseWrapper l r a)) #

pureMessage :: ChooseWrapper l r a -> SomeMessage -> Maybe (ChooseWrapper l r a) #

description :: ChooseWrapper l r a -> String #

(Read (l a), Read (r a)) => Read (ChooseWrapper l r a) Source # 
Instance details

Defined in XMonad.Layout.TallMastersCombo

(Show (l a), Show (r a)) => Show (ChooseWrapper l r a) Source # 
Instance details

Defined in XMonad.Layout.TallMastersCombo

Methods

showsPrec :: Int -> ChooseWrapper l r a -> ShowS #

show :: ChooseWrapper l r a -> String #

showList :: [ChooseWrapper l r a] -> ShowS #

swapWindow :: Eq a => a -> Stack a -> Stack a Source #

Swap a given window with the focused window.

focusWindow :: Eq a => a -> Stack a -> Stack a Source #

Focus a given window.

handleMessages :: LayoutClass l a => l a -> [SomeMessage] -> X (Maybe (l a)) Source #

Handle a list of messages one by one, then return the last refreshed layout.