xmonad-contrib-0.17.1: Community-maintained extensions for xmonad
Copyright(c) 2009 Anders Engstrom <ankaan@gmail.com> 2011 Ilya Portnov <portnov84@rambler.ru>
LicenseBSD3-style (see LICENSE)
MaintainerIlya Portnov <portnov84@rambler.ru>
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Layout.LayoutBuilderP

Description

Deprecated: Use XMonad.Layout.LayoutBuilder instead

DEPRECATED. Use LayoutBuilder instead.

Synopsis

Documentation

data LayoutP p l1 l2 a Source #

Data type for our layout.

Constructors

LayoutP (Maybe a) (Maybe a) p SubBox (Maybe SubBox) (l1 a) (Maybe (l2 a)) 

Instances

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

Defined in XMonad.Layout.LayoutBuilderP

Methods

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

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

pureLayout :: LayoutP p l1 l2 w -> Rectangle -> Stack w -> [(w, Rectangle)] #

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

handleMessage :: LayoutP p l1 l2 w -> SomeMessage -> X (Maybe (LayoutP p l1 l2 w)) #

pureMessage :: LayoutP p l1 l2 w -> SomeMessage -> Maybe (LayoutP p l1 l2 w) #

description :: LayoutP p l1 l2 w -> String #

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

Defined in XMonad.Layout.LayoutBuilderP

Methods

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

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

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

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

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

Defined in XMonad.Layout.LayoutBuilderP

Methods

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

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

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

layoutP Source #

Arguments

:: (Read a, Eq a, LayoutClass l1 a, LayoutClass l2 a, LayoutClass l3 a, Predicate p a) 
=> p 
-> 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

-> LayoutP p l2 l3 a

Where to send the remaining windows

-> LayoutP p l1 (LayoutP p l2 l3) 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

:: forall l1 p a. (Read a, Eq a, LayoutClass l1 a, Predicate p a) 
=> SubBox

The box to place the windows in

-> l1 a

The layout to use in the specified area

-> LayoutP p l1 Full a

The resulting layout

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

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.

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.

Overloading ways to select 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

Instances details
Predicate Property Window Source # 
Instance details

Defined in XMonad.Layout.LayoutBuilderP

data Proxy a Source #

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

Constructors

Proxy