xmonad-0.18.0: A tiling window manager
Copyright(c) Spencer Janssen 2007
LicenseBSD3-style (see LICENSE)
Maintainerspencerjanssen@gmail.com
Stabilityunstable
Portabilitynot portable, mtl, posix
Safe HaskellNone
LanguageHaskell2010

XMonad.Layout

Description

The collection of core layouts.

Synopsis

Documentation

data Full a Source #

Simple fullscreen mode. Renders the focused window fullscreen.

Constructors

Full 

Instances

Instances details
LayoutClass Full a Source # 
Instance details

Defined in XMonad.Layout

Read (Full a) Source # 
Instance details

Defined in XMonad.Layout

Show (Full a) Source # 
Instance details

Defined in XMonad.Layout

Methods

showsPrec :: Int -> Full a -> ShowS #

show :: Full a -> String #

showList :: [Full a] -> ShowS #

data Tall a Source #

The builtin tiling mode of xmonad. Supports Shrink, Expand and IncMasterN.

Constructors

Tall 

Fields

Instances

Instances details
LayoutClass Tall a Source # 
Instance details

Defined in XMonad.Layout

Read (Tall a) Source # 
Instance details

Defined in XMonad.Layout

Show (Tall a) Source # 
Instance details

Defined in XMonad.Layout

Methods

showsPrec :: Int -> Tall a -> ShowS #

show :: Tall a -> String #

showList :: [Tall a] -> ShowS #

newtype Mirror (l :: Type -> Type) a Source #

Mirror a layout, compute its 90 degree rotated form.

Constructors

Mirror (l a) 

Instances

Instances details
LayoutClass l a => LayoutClass (Mirror l) a Source # 
Instance details

Defined in XMonad.Layout

Read (l a) => Read (Mirror l a) Source # 
Instance details

Defined in XMonad.Layout

Show (l a) => Show (Mirror l a) Source # 
Instance details

Defined in XMonad.Layout

Methods

showsPrec :: Int -> Mirror l a -> ShowS #

show :: Mirror l a -> String #

showList :: [Mirror l a] -> ShowS #

data Resize Source #

Change the size of the master pane.

Constructors

Shrink 
Expand 

Instances

Instances details
Message Resize Source # 
Instance details

Defined in XMonad.Layout

newtype IncMasterN Source #

Increase the number of clients in the master pane.

Constructors

IncMasterN Int 

Instances

Instances details
Message IncMasterN Source # 
Instance details

Defined in XMonad.Layout

data Choose (l :: Type -> Type) (r :: Type -> Type) a Source #

A layout that allows users to switch between various layout options.

Constructors

Choose CLR (l a) (r a) 

Instances

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

Defined in XMonad.Layout

Methods

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

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

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

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

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

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

description :: Choose l r a -> String Source #

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

Defined in XMonad.Layout

Methods

readsPrec :: Int -> ReadS (Choose l r a) #

readList :: ReadS [Choose l r a] #

readPrec :: ReadPrec (Choose l r a) #

readListPrec :: ReadPrec [Choose l r a] #

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

Defined in XMonad.Layout

Methods

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

show :: Choose l r a -> String #

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

(|||) :: l a -> r a -> Choose l r a infixr 5 Source #

The layout choice combinator

data CLR Source #

Choose the current sub-layout (left or right) in Choose.

Constructors

CL 
CR 

Instances

Instances details
Read CLR Source # 
Instance details

Defined in XMonad.Layout

Show CLR Source # 
Instance details

Defined in XMonad.Layout

Methods

showsPrec :: Int -> CLR -> ShowS #

show :: CLR -> String #

showList :: [CLR] -> ShowS #

Eq CLR Source # 
Instance details

Defined in XMonad.Layout

Methods

(==) :: CLR -> CLR -> Bool #

(/=) :: CLR -> CLR -> Bool #

data ChangeLayout Source #

Messages to change the current layout. Also see JumpToLayout.

Constructors

FirstLayout 
NextLayout 

Instances

Instances details
Show ChangeLayout Source # 
Instance details

Defined in XMonad.Layout

Eq ChangeLayout Source # 
Instance details

Defined in XMonad.Layout

Message ChangeLayout Source # 
Instance details

Defined in XMonad.Layout

newtype JumpToLayout Source #

A message to jump to a particular layout, specified by its description string.

The argument given to a JumpToLayout message should be the description of the layout to be selected. If you use XMonad.Hooks.DynamicLog from xmonad-contrib, this is the name of the layout displayed in your status bar. Alternatively, you can use GHCi to determine the proper name to use. For example:

$ ghci
GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
:set prompt "> "    -- don't show loaded module names
> :m +XMonad.Core   -- load the xmonad core
> :m +XMonad.Layout.Grid  -- load whatever module you want to use
> description Grid  -- find out what it's called
"Grid"

As yet another (possibly easier) alternative, you can use the XMonad.Layout.Renamed module (also in xmonad-contrib) to give custom names to your layouts, and use those.

For example, if you want to jump directly to the Full layout you can do

, ((modm .|. controlMask, xK_f), sendMessage $ JumpToLayout "Full")

Constructors

JumpToLayout String 

Instances

Instances details
Message JumpToLayout Source # 
Instance details

Defined in XMonad.Layout

mirrorRect :: Rectangle -> Rectangle Source #

Mirror a rectangle.

tile Source #

Arguments

:: Rational

frac, what proportion of the screen to devote to the master area

-> Rectangle

r, the rectangle representing the screen

-> Int

nmaster, the number of windows in the master pane

-> Int

n, the total number of windows to tile

-> [Rectangle] 

Compute the positions for windows using the default two-pane tiling algorithm.

The screen is divided into two panes. All clients are then partitioned between these two panes. One pane, the master, by convention has the least number of windows in it.