xmonad-contrib-0.6: Third party extensions for xmonadSource codeContentsIndex
XMonad.Layout.MultiToggle
Portabilityunportable
Stabilityunstable
Maintainer<l.mai@web.de>
Contents
Usage
Description
Dynamically apply and unapply transformers to your window layout. This can be used to rotate your window layout by 90 degrees, or to make the currently focused window occupy the whole screen ("zoom in") then undo the transformation ("zoom out").
Synopsis
class (Eq t, Typeable t) => Transformer t a | t -> a where
transform :: LayoutClass l a => t -> l a -> (forall l'. LayoutClass l' a => l' a -> b) -> b
data Toggle a = forall t . Transformer t a => Toggle t
(??) :: HList b w => a -> b -> HCons a b
data EOT = EOT
single :: a -> HCons a EOT
mkToggle :: LayoutClass l a => ts -> l a -> MultiToggle ts l a
Usage

The basic idea is to have a base layout and a set of layout transformers, of which at most one is active at any time. Enabling another transformer first disables any currently active transformer; i.e. it works like a group of radio buttons.

A side effect of this meta-layout is that layout transformers no longer receive any messages; any message not handled by MultiToggle itself will undo the current layout transformer, pass the message on to the base layout, then reapply the transformer.

To use this module, you first have to define the transformers that you want to be handled by MultiToggle. For example, if the transformer is XMonad.Layout.Mirror:

 data MIRROR = MIRROR deriving (Read, Show, Eq, Typeable)
 instance Transformer MIRROR Window where
     transform _ x k = k (Mirror x)

MIRROR can be any identifier (it has to start with an uppercase letter, of course); I've chosen an all-uppercase version of the transforming function's name here. You need to put {-# OPTIONS_GHC -fglasgow-exts #-} at the beginning of your file to be able to derive Data.Typeable.

Somewhere else in your file you probably have a definition of layout; the default looks like this:

 layout = tiled ||| Mirror tiled ||| Full

After changing this to

 layout = mkToggle (single MIRROR) (tiled ||| Full)

you can now dynamically apply the XMonad.Layout.Mirror transformation:

 ...
   , ((modMask,               xK_x     ), sendMessage $ Toggle MIRROR)
 ...

(That should be part of your key bindings.) When you press mod-x, the active layout is mirrored. Another mod-x and it's back to normal.

It's also possible to stack MultiToggles. Let's define a few more transformers (XMonad.Layout.NoBorders.noBorders is in XMonad.Layout.NoBorders):

 data NOBORDERS = NOBORDERS deriving (Read, Show, Eq, Typeable)
 instance Transformer NOBORDERS Window where
     transform _ x k = k (noBorders x)

 data FULL = FULL deriving (Read, Show, Eq, Typeable)
 instance Transformer FULL Window where
     transform _ x k = k Full
 layout = id
     . XMonad.Layout.NoBorders.smartBorders
     . mkToggle (NOBORDERS ?? FULL ?? EOT)
     . mkToggle (single MIRROR)
     $ tiled ||| XMonad.Layout.Grid.Grid ||| XMonad.Layout.Circle.Circle

By binding a key to (sendMessage $ Toggle FULL) you can temporarily maximize windows, in addition to being able to rotate layouts and remove window borders.

class (Eq t, Typeable t) => Transformer t a | t -> a whereSource
A class to identify custom transformers (and look up transforming functions by type).
Methods
transform :: LayoutClass l a => t -> l a -> (forall l'. LayoutClass l' a => l' a -> b) -> bSource
show/hide Instances
data Toggle a Source
Toggle the specified layout transformer.
Constructors
forall t . Transformer t a => Toggle t
show/hide Instances
(??) :: HList b w => a -> b -> HCons a bSource
Prepend an element to a heterogeneous list. Used to build transformer tables for mkToggle.
data EOT Source
Marks the end of a transformer list.
Constructors
EOT
show/hide Instances
single :: a -> HCons a EOTSource
Construct a singleton transformer table.
mkToggle :: LayoutClass l a => ts -> l a -> MultiToggle ts l aSource
Construct a MultiToggle layout from a transformer table and a base layout.
Produced by Haddock version 2.3.0