xmonad-contrib-0.16: Third party extensions for xmonad

Copyright(c) 2009 Anders Engstrom <ankaan@gmail.com>
2011 Ilya Portnov <portnov84@rambler.ru>
2015 Peter Jones <pjones@devalot.com>
LicenseBSD3-style (see LICENSE)
MaintainerAnders Engstrom <ankaan@gmail.com>, Ilya Portnov <portnov84@rambler.ru>, Peter Jones <pjones@devalot.com>
Stabilityunstable
Portabilityunportable
Safe HaskellNone
LanguageHaskell98

XMonad.Layout.LayoutBuilder

Contents

Description

A layout combinator that sends a specified number of windows to one rectangle and the rest to another. Each of these rectangles are given a layout that is used within them. This can be chained to provide an arbitrary number of rectangles. The layout combinator allows overlapping rectangles, but such layouts does not work well together with hinting (XMonad.Layout.LayoutHints, XMonad.Layout.HintedGrid etc.)

Synopsis

Usage

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

import XMonad.Layout.LayoutBuilder

Then edit your layoutHook by adding something like:

myLayout = ( (layoutN 1 (relBox 0 0 0.5 1) (Just $ relBox 0 0 1 1) $ simpleTabbed)
            $ (layoutAll (relBox 0.5 0 1 1)                         $ simpleTabbed)
            ) |||
            ( (layoutN 1       (relBox (1/3) 0 (1/2) 1) (Just $ relBox 0 0 1 1) $ Tall 0 0.01 0.5)
            $ (layoutR 0.1 0.5 (relBox (2/3) 0 1     1) Nothing                 $ Tall 0 0.01 0.5)
            $ (layoutAll       (relBox 0     0 (1/3) 1)                         $ Tall 0 0.01 0.5)
            ) |||
            ( (layoutN 1 (absBox (-512-200) 0 512        0) (Just $ relBox 0 0 1 1) $ simpleTabbed)
            $ (layoutN 1 (absBox (-200)     0 0          0) Nothing                 $ simpleTabbed)
            $ (layoutAll (absBox 0          0 (-512-200) 0)                         $ simpleTabbed)
            ) |||
            ( (layoutN 1 (absBox 10 0 0 (-10)) Nothing $ Tall 0 0.01 0.5)
            $ (layoutN 1 (absBox 0 0 200 0) Nothing $ Tall 0 0.01 0.5)
            $ (layoutAll (absBox 10 10 0 0) $ Tall 2 0.01 0.5)
            ) ||| Full ||| etc...
main = xmonad def { layoutHook = myLayout }

This will produce a layout similar to DragPane, but with the possibility to have multiple windows in the left half and tabs that show the available windows. It will also produce a layout similar to ThreeColMid and a special layout created for use with a 80 columns wide Emacs window, its sidebar and a tabbed area for all other windows.

The final layout is for applications that use a toolbar in a separate window, shown on a low resolution screen. It has a master area that cover almost the whole screen. It leaves 10 px to the left and 10 px at the bottom. To the left the toolbar is located and can be accessed by focusing this area. It is actually 200 px wide, but usually below the other windows. Similarly all other windows are tiled, but behind the master window and can be accessed by moving the mouse to the bottom of the screen. Everything can also be accessed by the standard focus changing key bindings.

This module can be used to create many different custom layouts, but there are limitations. The primary limitation can be observed in the second and third example when there are only two columns with windows in them. The leftmost area is left blank. These blank areas can be avoided by placing the rectangles appropriately.

These examples require XMonad.Layout.Tabbed.

For more detailed instructions on editing the layoutHook see:

XMonad.Doc.Extending

You may wish to add the following keybindings:

   , ((modm .|. shiftMask, xK_h ), sendMessage $ IncLayoutN (-1))
   , ((modm .|. shiftMask, xK_l ), sendMessage $ IncLayoutN 1)

For detailed instruction on editing the key binding see:

XMonad.Doc.Extending.

layoutN Source #

Arguments

:: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a, LayoutClass l3 a) 
=> Int

The number of windows to handle

-> SubBox

The box to place the windows in

-> Maybe SubBox

Possibly an alternative box that is used when this layout handles all windows that are left

-> l1 a

The layout to use in the specified area

-> LayoutB l2 l3 p a

Where to send the remaining windows

-> LayoutB l1 (LayoutB l2 l3 p) () a

The resulting layout

Use the specified layout in the described area for N windows and send the rest of the windows to the next layout in the chain. It is possible to supply an alternative area that will then be used instead, if there are no windows to send to the next layout.

layoutR Source #

Arguments

:: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a, LayoutClass l3 a) 
=> Rational

How much to change the ratio with each IncLayoutN

-> Rational

The ratio of the remaining windows to handle

-> SubBox

The box to place the windows in

-> Maybe SubBox

Possibly an alternative box that is used when this layout handles all windows that are left

-> l1 a

The layout to use in the specified area

-> LayoutB l2 l3 p a

Where to send the remaining windows

-> LayoutB l1 (LayoutB l2 l3 p) p a

The resulting layout

As layoutN, but the number of windows is given relative to the total number of windows remaining to be handled. The first argument is how much to change the ratio when using IncLayoutN, and the second is the initial ratio.

layoutP Source #

Arguments

:: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a, LayoutClass l3 a, Predicate p a, Predicate p' a) 
=> p

The predicate to use

-> SubBox

The box to place the windows in

-> Maybe SubBox

Possibly an alternative box that is used when this layout handles all windows that are left

-> l1 a

The layout to use in the specified area

-> LayoutB l2 l3 p' a

Where to send the remaining windows

-> LayoutB l1 (LayoutB l2 l3 p') p a

The resulting layout

Use the specified layout in the described area windows that match given predicate and send the rest of the windows to the next layout in the chain. It is possible to supply an alternative area that will then be used instead, if there are no windows to send to the next layout.

layoutAll Source #

Arguments

:: (Read a, Eq a, LayoutClass l1 a) 
=> SubBox

The box to place the windows in

-> l1 a

The layout to use in the specified area

-> LayoutB l1 Full () a

The resulting layout

Use the specified layout in the described area for all remaining windows.

Selecting Windows

Predicate exists because layouts are required to be serializable, and XMonad.Util.WindowProperties is not sufficient (for example it does not allow using regular expressions).

compare XMonad.Util.Invisible

class Predicate p w where Source #

Type class for predicates. This enables us to manage not only Windows, but any objects, for which instance Predicate is defined.

Another instance exists in XMonad.Util.WindowPropertiesRE in xmonad-extras

Methods

alwaysTrue Source #

Arguments

:: Proxy w 
-> p

A predicate that is always True.

checkPredicate Source #

Arguments

:: p 
-> w 
-> X Bool

Check if given object (window or smth else) matches that predicate

Instances
Predicate () a Source # 
Instance details

Defined in XMonad.Layout.LayoutBuilder

Methods

alwaysTrue :: Proxy a -> () Source #

checkPredicate :: () -> a -> X Bool Source #

Predicate Property Window Source # 
Instance details

Defined in XMonad.Layout.LayoutBuilder

data Proxy a Source #

Contains no actual data, but is needed to help select the correct instance of Predicate

Constructors

Proxy 

Messages

data IncLayoutN Source #

Change the number of windows handled by the focused layout.

Constructors

IncLayoutN Int 
Instances
Message IncLayoutN Source # 
Instance details

Defined in XMonad.Layout.LayoutBuilder

Utilities

data SubMeasure Source #

The absolute or relative measures used to describe the area a layout should be placed in. For negative absolute values the total remaining space will be added. For sizes, the remaining space will also be added for zeroes. Relative values are applied on the remaining space after the top-left corner of the box have been removed.

Constructors

Abs Int 
Rel Rational 

data SubBox Source #

A box to place a layout in. The stored values are xpos, ypos, width and height.

absBox Source #

Arguments

:: Int

Absolute X-Position

-> Int

Absolute Y-Position

-> Int

Absolute width

-> Int

Absolute height

-> SubBox

The resulting SubBox describing the area

Create a box with only absolute measurements. If the values are negative, the total remaining space will be added. For sizes it will also be added for zeroes.

relBox Source #

Arguments

:: Rational

Relative X-Position with respect to the surrounding area

-> Rational

Relative Y-Position with respect to the surrounding area

-> Rational

Relative width with respect to the remaining width

-> Rational

Relative height with respect to the remaining height

-> SubBox

The resulting SubBox describing the area

Create a box with only relative measurements.

data LayoutB l1 l2 p a Source #

Use one layout in the specified area for a number of windows and possibly let another layout handle the rest.

Instances
(LayoutClass l1 a, LayoutClass l2 a, Read a, Show a, Show p, Eq a, Typeable a, Predicate p a) => LayoutClass (LayoutB l1 l2 p) a Source # 
Instance details

Defined in XMonad.Layout.LayoutBuilder

Methods

runLayout :: Workspace WorkspaceId (LayoutB l1 l2 p a) a -> Rectangle -> X ([(a, Rectangle)], Maybe (LayoutB l1 l2 p a)) #

doLayout :: LayoutB l1 l2 p a -> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (LayoutB l1 l2 p a)) #

pureLayout :: LayoutB l1 l2 p a -> Rectangle -> Stack a -> [(a, Rectangle)] #

emptyLayout :: LayoutB l1 l2 p a -> Rectangle -> X ([(a, Rectangle)], Maybe (LayoutB l1 l2 p a)) #

handleMessage :: LayoutB l1 l2 p a -> SomeMessage -> X (Maybe (LayoutB l1 l2 p a)) #

pureMessage :: LayoutB l1 l2 p a -> SomeMessage -> Maybe (LayoutB l1 l2 p a) #

description :: LayoutB l1 l2 p a -> String #

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

Defined in XMonad.Layout.LayoutBuilder

Methods

readsPrec :: Int -> ReadS (LayoutB l1 l2 p a) #

readList :: ReadS [LayoutB l1 l2 p a] #

readPrec :: ReadPrec (LayoutB l1 l2 p a) #

readListPrec :: ReadPrec [LayoutB l1 l2 p a] #

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

Defined in XMonad.Layout.LayoutBuilder

Methods

showsPrec :: Int -> LayoutB l1 l2 p a -> ShowS #

show :: LayoutB l1 l2 p a -> String #

showList :: [LayoutB l1 l2 p a] -> ShowS #

type LayoutN l1 l2 a = LayoutB l1 l2 () a Source #

A variant of LayoutB that can't use layoutP. For backwards compatibility with previous versions of LayoutBuilder.