xmonad-contrib-0.17.1: Community-maintained extensions for xmonad
Copyright(c) Brent Yorgey
LicenseBSD-style (see LICENSE)
Maintainer<byorgey@gmail.com>
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Layout.Reflect

Contents

Description

Reflect a layout horizontally or vertically.

Synopsis

Usage

You can use this module by importing it into your ~/.xmonad/xmonad.hs file:

import XMonad.Layout.Reflect

and modifying your layoutHook as follows (for example):

layoutHook = reflectHoriz $ Tall 1 (3/100) (1/2)  -- put master pane on the right

reflectHoriz and reflectVert can be applied to any sort of layout (including Mirrored layouts) and will simply flip the physical layout of the windows vertically or horizontally.

XMonad.Layout.MultiToggle transformers are also provided for toggling layouts between reflected/non-reflected with a keybinding. To use this feature, you will also need to import the MultiToggle module:

import XMonad.Layout.MultiToggle

Next, add one or more toggles to your layout. For example, to allow separate toggling of both vertical and horizontal reflection:

layoutHook = mkToggle (single REFLECTX) $
             mkToggle (single REFLECTY) $
               (tiled ||| Mirror tiled ||| ...) -- whatever layouts you use

Finally, add some keybindings to do the toggling, for example:

, ((modm .|. controlMask, xK_x), sendMessage $ Toggle REFLECTX)
, ((modm .|. controlMask, xK_y), sendMessage $ Toggle REFLECTY)

reflectHoriz :: l a -> ModifiedLayout Reflect l a Source #

Apply a horizontal reflection (left <--> right) to a layout.

reflectVert :: l a -> ModifiedLayout Reflect l a Source #

Apply a vertical reflection (top <--> bottom) to a layout.

data REFLECTX Source #

Constructors

REFLECTX 

Instances

Instances details
Read REFLECTX Source # 
Instance details

Defined in XMonad.Layout.Reflect

Show REFLECTX Source # 
Instance details

Defined in XMonad.Layout.Reflect

Eq REFLECTX Source # 
Instance details

Defined in XMonad.Layout.Reflect

Transformer REFLECTX Window Source # 
Instance details

Defined in XMonad.Layout.Reflect

Methods

transform :: LayoutClass l Window => REFLECTX -> l Window -> (forall (l' :: Type -> Type). LayoutClass l' Window => l' Window -> (l' Window -> l Window) -> b) -> b Source #

data REFLECTY Source #

Constructors

REFLECTY 

Instances

Instances details
Read REFLECTY Source # 
Instance details

Defined in XMonad.Layout.Reflect

Show REFLECTY Source # 
Instance details

Defined in XMonad.Layout.Reflect

Eq REFLECTY Source # 
Instance details

Defined in XMonad.Layout.Reflect

Transformer REFLECTY Window Source # 
Instance details

Defined in XMonad.Layout.Reflect

Methods

transform :: LayoutClass l Window => REFLECTY -> l Window -> (forall (l' :: Type -> Type). LayoutClass l' Window => l' Window -> (l' Window -> l Window) -> b) -> b Source #

data Reflect a Source #

Instances

Instances details
LayoutModifier Reflect a Source # 
Instance details

Defined in XMonad.Layout.Reflect

Read (Reflect a) Source # 
Instance details

Defined in XMonad.Layout.Reflect

Show (Reflect a) Source # 
Instance details

Defined in XMonad.Layout.Reflect

Methods

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

show :: Reflect a -> String #

showList :: [Reflect a] -> ShowS #