xmonad-contrib-0.17.1: Community-maintained extensions for xmonad
Copyright(c) Konstantin Sobolev <konstantin.sobolev@gmail.com>
LicenseBSD-style (see LICENSE)
MaintainerKonstantin Sobolev <konstantin.sobolev@gmail.com>
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Layout.ComboP

Contents

Description

A layout that combines multiple layouts and allows to specify where to put new windows.

Synopsis

Usage

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

import XMonad.Layout.ComboP

and add something like

combineTwoP (TwoPane 0.03 0.5) (tabbed shrinkText def) (tabbed shrinkText def) (ClassName "Firefox")

to your layouts. This way all windows with class = "Firefox" will always go to the left pane, all others - to the right.

For more detailed instructions on editing the layoutHook see:

XMonad.Doc.Extending

combineTwoP is a simple layout combinator based on combineTwo from Combo, with addition of a Property which tells where to put new windows. Windows mathing the property will go into the first part, all others will go into the second part. It supports Move messages as combineTwo does, but it also introduces SwapWindow message which sends focused window to the other part. It is required because Move commands don't work when one of the parts is empty. To use it, import "XMonad.Layout.WindowNavigation", and add the following key bindings (or something similar):

   , ((modm .|. controlMask .|. shiftMask, xK_Right), sendMessage $ Move R)
   , ((modm .|. controlMask .|. shiftMask, xK_Left ), sendMessage $ Move L)
   , ((modm .|. controlMask .|. shiftMask, xK_Up   ), sendMessage $ Move U)
   , ((modm .|. controlMask .|. shiftMask, xK_Down ), sendMessage $ Move D)
   , ((modm .|. controlMask .|. shiftMask, xK_s    ), sendMessage $ SwapWindow)

For detailed instruction on editing the key binding see XMonad.Doc.Extending.

combineTwoP :: (LayoutClass super (), LayoutClass l1 Window, LayoutClass l2 Window) => super () -> l1 Window -> l2 Window -> Property -> CombineTwoP (super ()) l1 l2 Window Source #

data CombineTwoP l l1 l2 a Source #

Instances

Instances details
(LayoutClass l (), LayoutClass l1 Window, LayoutClass l2 Window) => LayoutClass (CombineTwoP (l ()) l1 l2) Window Source # 
Instance details

Defined in XMonad.Layout.ComboP

Methods

runLayout :: Workspace WorkspaceId (CombineTwoP (l ()) l1 l2 Window) Window -> Rectangle -> X ([(Window, Rectangle)], Maybe (CombineTwoP (l ()) l1 l2 Window)) #

doLayout :: CombineTwoP (l ()) l1 l2 Window -> Rectangle -> Stack Window -> X ([(Window, Rectangle)], Maybe (CombineTwoP (l ()) l1 l2 Window)) #

pureLayout :: CombineTwoP (l ()) l1 l2 Window -> Rectangle -> Stack Window -> [(Window, Rectangle)] #

emptyLayout :: CombineTwoP (l ()) l1 l2 Window -> Rectangle -> X ([(Window, Rectangle)], Maybe (CombineTwoP (l ()) l1 l2 Window)) #

handleMessage :: CombineTwoP (l ()) l1 l2 Window -> SomeMessage -> X (Maybe (CombineTwoP (l ()) l1 l2 Window)) #

pureMessage :: CombineTwoP (l ()) l1 l2 Window -> SomeMessage -> Maybe (CombineTwoP (l ()) l1 l2 Window) #

description :: CombineTwoP (l ()) l1 l2 Window -> String #

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

Defined in XMonad.Layout.ComboP

Methods

readsPrec :: Int -> ReadS (CombineTwoP l l1 l2 a) #

readList :: ReadS [CombineTwoP l l1 l2 a] #

readPrec :: ReadPrec (CombineTwoP l l1 l2 a) #

readListPrec :: ReadPrec [CombineTwoP l l1 l2 a] #

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

Defined in XMonad.Layout.ComboP

Methods

showsPrec :: Int -> CombineTwoP l l1 l2 a -> ShowS #

show :: CombineTwoP l l1 l2 a -> String #

showList :: [CombineTwoP l l1 l2 a] -> ShowS #

data SwapWindow Source #

Constructors

SwapWindow

Swap window between panes

SwapWindowN Int

Swap window between panes in the N-th nested ComboP. SwapWindowN 0 equals to SwapWindow

Instances

Instances details
Read SwapWindow Source # 
Instance details

Defined in XMonad.Layout.ComboP

Show SwapWindow Source # 
Instance details

Defined in XMonad.Layout.ComboP

Message SwapWindow Source # 
Instance details

Defined in XMonad.Layout.ComboP

data PartitionWins Source #

Constructors

PartitionWins

Reset the layout and partition all windows into the correct sub-layout. Useful for when window properties have changed and you want ComboP to update which layout a window belongs to.

data Property Source #

Most of the property constructors are quite self-explaining.

Constructors

Title String 
ClassName String 
Resource String 
Role String

WM_WINDOW_ROLE property

Machine String

WM_CLIENT_MACHINE property

And Property Property infixr 9 
Or Property Property infixr 8 
Not Property 
Const Bool 
Tagged String

Tagged via TagWindows