xmonad-contrib-0.12: Third party extensions for xmonad

CopyrightQuentin Moser <moserq@gmail.com>
LicenseBSD-style (see LICENSE)
Maintainerorphaned
Stabilityunstable
Portabilityunportable
Safe HaskellNone
LanguageHaskell98

XMonad.Layout.ZoomRow

Contents

Description

Row layout with individually resizable elements.

Synopsis

Usage

This module provides a layout which places all windows in a single row; the size occupied by each individual window can be increased and decreased, and a window can be set to use the whole available space whenever it has focus.

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

import XMonad.Layout.ZoomRow

and using zoomRow somewhere in your layoutHook, for example:

myLayout = zoomRow ||| Mirror zoomRow

To be able to resize windows, you can create keybindings to send the relevant ZoomMessages:

  -- Increase the size occupied by the focused window
, ((modMask .|. shifMask, xK_minus), sendMessage zoomIn)
  -- Decrease the size occupied by the focused window
, ((modMayk             , xK_minus), sendMessage zoomOut)
  -- Reset the size occupied by the focused window
, ((modMask             , xK_equal), sendMessage zoomReset)
  -- (Un)Maximize the focused window
, ((modMask             , xK_f    ), sendMessage ToggleZoomFull)

For more information on editing your layout hook and key bindings, see XMonad.Doc.Extending.

data ZoomRow f a Source

A layout that arranges its windows in a horizontal row, and allows to change the relative size of each element independently.

Instances

(EQF f a, Show a, Read a, Show (f a), Read (f a)) => LayoutClass (ZoomRow f) a Source 
(Eq a, Eq (f a)) => Eq (ZoomRow f a) Source 
(Read a, Read (f a)) => Read (ZoomRow f a) Source 
(Show a, Show (f a)) => Show (ZoomRow f a) Source 

Creation

zoomRow :: (Eq a, Show a, Read a) => ZoomRow ClassEQ a Source

ZoomRow layout for laying out elements which are instances of Eq. Perfect for Windows.

Messages

data ZoomMessage Source

The type of messages accepted by a ZoomRow layout

Constructors

Zoom Rational

Multiply the focused window's size factor by the given number.

ZoomTo Rational

Set the focused window's size factor to the given number.

ZoomFull Bool

Set whether the focused window should occupy all available space when it has focus

ZoomFullToggle

Toggle whether the focused window should occupy all available space when it has focus

zoomIn :: ZoomMessage Source

Increase the size of the focused window. Defined as Zoom 1.5

zoomOut :: ZoomMessage Source

Decrease the size of the focused window. Defined as Zoom (2/3)

zoomReset :: ZoomMessage Source

Reset the size of the focused window. Defined as ZoomTo 1

Use with non-Eq elements

Haskell's Eq class is usually concerned with structural equality, whereas what this layout really wants is for its elements to have a unique identity, even across changes. There are cases (such as, importantly, Windows) where the Eq instance for a type actually does that, but if you want to lay out something more exotic than windows and your Eq means something else, you can use the following.

zoomRowWith :: (EQF f a, Show (f a), Read (f a), Show a, Read a) => f a -> ZoomRow f a Source

ZoomRow layout with a custom equality predicate. It should of course satisfy the laws for Eq, and you should also make sure that the layout never has to handle two "equal" elements at the same time (it won't do any huge damage, but might behave a bit strangely).

class EQF f a where Source

Class for equivalence relations. Must be transitive, reflexive.

Methods

eq :: f a -> a -> a -> Bool Source

Instances

Eq a => EQF ClassEQ a Source 
Eq a => EQF GroupEQ (Group l a) Source 

data ClassEQ a Source

To use the usual ==:

Constructors

ClassEQ 

Instances