Copyright | (c) Lukas Mai |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | <l.mai@web.de> |
Stability | unstable |
Portability | unportable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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 -> (l' a -> l a) -> b) -> b
- data Toggle a = forall t.Transformer t a => Toggle t
- (??) :: a -> b -> HCons a b
- data EOT = EOT
- single :: a -> HCons a EOT
- mkToggle :: LayoutClass l a => ts -> l a -> MultiToggle ts l a
- mkToggle1 :: LayoutClass l a => t -> l a -> MultiToggle (HCons t EOT) l a
- isToggleActive :: Transformer t Window => t -> WindowSpace -> X (Maybe Bool)
- class HList c a
- data HCons a b
- data 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.
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 MultiToggle
s. 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).
transform :: LayoutClass l a => t -> l a -> (forall l'. LayoutClass l' a => l' a -> (l' a -> l a) -> b) -> b Source #
Instances
Transformer StdTransformers Window Source # | |
Defined in XMonad.Layout.MultiToggle.Instances transform :: LayoutClass l Window => StdTransformers -> l Window -> (forall (l' :: TYPE LiftedRep -> Type). LayoutClass l' Window => l' Window -> (l' Window -> l Window) -> b) -> b Source # | |
Transformer SimpleTabBar Window Source # | |
Defined in XMonad.Layout.MultiToggle.TabBarDecoration transform :: LayoutClass l Window => SimpleTabBar -> l Window -> (forall (l' :: TYPE LiftedRep -> Type). LayoutClass l' Window => l' Window -> (l' Window -> l Window) -> b) -> b Source # | |
Transformer REFLECTX Window Source # | |
Transformer REFLECTY Window Source # | |
Toggle the specified layout transformer.
forall t.Transformer t a => Toggle t |
(??) :: a -> b -> HCons a b infixr 0 Source #
Prepend an element to a heterogeneous list. Used to build transformer
tables for mkToggle
.
Marks the end of a transformer list.
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)
find, resolve
Instances
HList EOT w Source # | |
Defined in XMonad.Layout.MultiToggle 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 # | |
Defined in XMonad.Layout.MultiToggle find :: Transformer t w => HCons a b -> t -> Maybe Int resolve :: HCons a b -> Int -> b0 -> (forall t. Transformer t w => t -> b0) -> b0 |
Instances
(Read a, Read b) => Read (HCons a b) Source # | |
(Show a, Show b) => Show (HCons a b) Source # | |
(Transformer a w, HList b w) => HList (HCons a b) w Source # | |
Defined in XMonad.Layout.MultiToggle 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 #