xmonad-contrib-0.17.1: Community-maintained extensions for xmonad
Copyright(c) Lukas Mai
LicenseBSD-style (see LICENSE)
Maintainer<l.mai@web.de>
Stabilityunstable
Portabilityunportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

XMonad.Layout.MultiToggle

Contents

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

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.

To use this module, you need some data types which represent transformers; for some commonly used transformers (including MIRROR, NOBORDERS, and FULL used in the examples below) you can simply import XMonad.Layout.MultiToggle.Instances.

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 Mirror transformation:

...
  , ((modm,               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. For example:

layout = id
    . smartBorders
    . mkToggle (NOBORDERS ?? FULL ?? EOT)
    . mkToggle (single MIRROR)
    $ tiled ||| Grid ||| 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.

You can also define your own transformers by creating a data type which is an instance of the Transformer class. For example, here is the definition of MIRROR:

data MIRROR = MIRROR deriving (Read, Show, Eq)
instance Transformer MIRROR Window where
    transform _ x k = k (Mirror x) (\(Mirror x') -> x')

Note, you need to put {-# LANGUAGE TypeSynonymInstances, MultiParamTypeClasses #-} at the beginning of your file.

class (Eq t, Typeable t) => Transformer t a | t -> a where Source #

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 -> (l' a -> l a) -> b) -> b Source #

Instances

Instances details
Transformer StdTransformers Window Source # 
Instance details

Defined in XMonad.Layout.MultiToggle.Instances

Methods

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

Transformer SimpleTabBar Window Source # 
Instance details

Defined in XMonad.Layout.MultiToggle.TabBarDecoration

Methods

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

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 #

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 Toggle a Source #

Toggle the specified layout transformer.

Constructors

forall t.Transformer t a => Toggle t 

Instances

Instances details
Typeable a => Message (Toggle a) Source # 
Instance details

Defined in XMonad.Layout.MultiToggle

(??) :: a -> b -> HCons a b infixr 0 Source #

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 

Instances

Instances details
Read EOT Source # 
Instance details

Defined in XMonad.Layout.MultiToggle

Show EOT Source # 
Instance details

Defined in XMonad.Layout.MultiToggle

Methods

showsPrec :: Int -> EOT -> ShowS #

show :: EOT -> String #

showList :: [EOT] -> ShowS #

HList EOT w Source # 
Instance details

Defined in XMonad.Layout.MultiToggle

Methods

find :: Transformer t w => EOT -> t -> Maybe Int

resolve :: EOT -> Int -> b -> (forall t. Transformer t w => t -> b) -> b

single :: a -> HCons a EOT Source #

Construct a singleton transformer table.

mkToggle :: LayoutClass l a => ts -> l a -> MultiToggle ts l a Source #

Construct a MultiToggle layout from a transformer table and a base layout.

mkToggle1 :: LayoutClass l a => t -> l a -> MultiToggle (HCons t EOT) l a Source #

Construct a MultiToggle layout from a single transformer and a base layout.

isToggleActive :: Transformer t Window => t -> WindowSpace -> X (Maybe Bool) Source #

Query the state of a Transformer on a given workspace.

To query the current workspace, use something like this:

withWindowSet (isToggleActive t . W.workspace . W.current)

class HList c a Source #

Minimal complete definition

find, resolve

Instances

Instances details
HList EOT w Source # 
Instance details

Defined in XMonad.Layout.MultiToggle

Methods

find :: Transformer t w => EOT -> t -> Maybe Int

resolve :: EOT -> Int -> b -> (forall t. Transformer t w => t -> b) -> b

(Transformer a w, HList b w) => HList (HCons a b) w Source # 
Instance details

Defined in XMonad.Layout.MultiToggle

Methods

find :: Transformer t w => HCons a b -> t -> Maybe Int

resolve :: HCons a b -> Int -> b0 -> (forall t. Transformer t w => t -> b0) -> b0

data HCons a b Source #

Instances

Instances details
(Read a, Read b) => Read (HCons a b) Source # 
Instance details

Defined in XMonad.Layout.MultiToggle

(Show a, Show b) => Show (HCons a b) Source # 
Instance details

Defined in XMonad.Layout.MultiToggle

Methods

showsPrec :: Int -> HCons a b -> ShowS #

show :: HCons a b -> String #

showList :: [HCons a b] -> ShowS #

(Transformer a w, HList b w) => HList (HCons a b) w Source # 
Instance details

Defined in XMonad.Layout.MultiToggle

Methods

find :: Transformer t w => HCons a b -> t -> Maybe Int

resolve :: HCons a b -> Int -> b0 -> (forall t. Transformer t w => t -> b0) -> b0

data MultiToggle ts l a Source #

Instances

Instances details
(Typeable a, Show ts, Typeable ts, HList ts a, LayoutClass l a) => LayoutClass (MultiToggle ts l) a Source # 
Instance details

Defined in XMonad.Layout.MultiToggle

Methods

runLayout :: Workspace WorkspaceId (MultiToggle ts l a) a -> Rectangle -> X ([(a, Rectangle)], Maybe (MultiToggle ts l a)) #

doLayout :: MultiToggle ts l a -> Rectangle -> Stack a -> X ([(a, Rectangle)], Maybe (MultiToggle ts l a)) #

pureLayout :: MultiToggle ts l a -> Rectangle -> Stack a -> [(a, Rectangle)] #

emptyLayout :: MultiToggle ts l a -> Rectangle -> X ([(a, Rectangle)], Maybe (MultiToggle ts l a)) #

handleMessage :: MultiToggle ts l a -> SomeMessage -> X (Maybe (MultiToggle ts l a)) #

pureMessage :: MultiToggle ts l a -> SomeMessage -> Maybe (MultiToggle ts l a) #

description :: MultiToggle ts l a -> String #

(LayoutClass l a, Read (l a), HList ts a, Read ts) => Read (MultiToggle ts l a) Source # 
Instance details

Defined in XMonad.Layout.MultiToggle

(Show ts, Show (l a), LayoutClass l a) => Show (MultiToggle ts l a) Source # 
Instance details

Defined in XMonad.Layout.MultiToggle

Methods

showsPrec :: Int -> MultiToggle ts l a -> ShowS #

show :: MultiToggle ts l a -> String #

showList :: [MultiToggle ts l a] -> ShowS #