aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Groups/Wmii.hs
diff options
context:
space:
mode:
authormoserq <moserq@gmail.com>2010-10-01 12:41:42 +0200
committermoserq <moserq@gmail.com>2010-10-01 12:41:42 +0200
commit86244fae66ff444a318895680764d29517295fa5 (patch)
tree80d125c7e78572671357766f7625a836716f8a9a /XMonad/Layout/Groups/Wmii.hs
parent881fc77dae6108579761e4fa8281b418cde089cc (diff)
downloadXMonadContrib-86244fae66ff444a318895680764d29517295fa5.tar.gz
XMonadContrib-86244fae66ff444a318895680764d29517295fa5.tar.xz
XMonadContrib-86244fae66ff444a318895680764d29517295fa5.zip
Split X.L.Groups.Examples
Ignore-this: 4d3bc3c44b1c0233d59c6ce5eefcc587 X.L.G.Examples : rowOfColumns and tiled tabs layouts X.L.G.Helpers : helper actions X.L.G.Wmii : wmii layout darcs-hash:20101001104142-88fd0-6ac471ab66a886497aba7d6c0b4803c3b8aaa884.gz
Diffstat (limited to 'XMonad/Layout/Groups/Wmii.hs')
-rw-r--r--XMonad/Layout/Groups/Wmii.hs133
1 files changed, 133 insertions, 0 deletions
diff --git a/XMonad/Layout/Groups/Wmii.hs b/XMonad/Layout/Groups/Wmii.hs
new file mode 100644
index 0000000..92297fe
--- /dev/null
+++ b/XMonad/Layout/Groups/Wmii.hs
@@ -0,0 +1,133 @@
+{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
+{-# LANGUAGE MultiParamTypeClasses, Rank2Types #-}
+
+-----------------------------------------------------------------------------
+-- |
+-- Module : XMonad.Layout.Groups.Wmii
+-- Copyright : Quentin Moser <moserq@gmail.com>
+-- License : BSD-style (see LICENSE)
+--
+-- Maintainer : orphaned
+-- Stability : stable
+-- Portability : unportable
+--
+-- A wmii-like layout algorithm.
+--
+-----------------------------------------------------------------------------
+
+module XMonad.Layout.Groups.Wmii ( -- * Usage
+ -- $usage
+
+ wmii
+ , zoomGroupIn
+ , zoomGroupOut
+ , zoomGroupReset
+ , toggleGroupFull
+ , groupToNextLayout
+ , groupToFullLayout
+ , groupToTabbedLayout
+ , groupToVerticalLayout
+
+ -- * Useful re-exports
+ , shrinkText
+ , defaultTheme
+ , module XMonad.Layout.Groups.Helpers ) where
+
+import XMonad hiding ((|||))
+
+import qualified XMonad.Layout.Groups as G
+import XMonad.Layout.Groups.Examples
+import XMonad.Layout.Groups.Helpers
+
+import XMonad.Layout.Tabbed
+import XMonad.Layout.Named
+import XMonad.Layout.Renamed
+import XMonad.Layout.LayoutCombinators
+import XMonad.Layout.MessageControl
+import XMonad.Layout.Simplest
+
+
+-- $usage
+-- This module provides a layout inspired by the one used by the wmii
+-- (<http://wmii.suckless.org>) window manager.
+-- Windows are arranged into groups in a horizontal row, and each group can lay out
+-- its windows
+--
+-- * by maximizing the focused one
+--
+-- * by tabbing them (wmii uses a stacked layout, but I'm too lazy to write it)
+--
+-- * by arranging them in a column.
+--
+-- As the groups are arranged in a 'ZoomRow', the relative width of each group can be
+-- increased or decreased at will. Groups can also be set to use the whole screen
+-- whenever they have focus.
+--
+-- You can use the contents of this module by adding
+--
+-- > import XMonad.Layout.Groups.Wmii
+--
+-- to the top of your @.\/.xmonad\/xmonad.hs@, and adding 'wmii'
+-- (with a 'Shrinker' and decoration 'Theme' as
+-- parameters) to your layout hook, for example:
+--
+-- > myLayout = wmii shrinkText defaultTheme
+--
+-- To be able to zoom in and out of groups, change their inner layout, etc.,
+-- create key bindings for the relevant actions:
+--
+-- > ((modMask, xK_f), toggleGroupFull)
+--
+-- and so on.
+--
+-- For more information on how to extend your layout hook and key bindings, see
+-- "XMonad.Doc.Extending".
+--
+-- Finally, you will probably want to be able to move focus and windows
+-- between groups in a consistent fashion. For this, you should take a look
+-- at the "XMonad.Layout.Groups.Helpers" module, whose contents are re-exported
+-- by this module.
+
+-- | A layout inspired by wmii
+wmii s t = G.group innerLayout zoomRowG
+ where column = named "Column" $ Tall 0 (3/100) (1/2)
+ tabs = named "Tabs" $ Simplest
+ innerLayout = renamed [CutWordsLeft 3]
+ $ addTabs s t
+ $ ignore NextLayout
+ $ ignore (JumpToLayout "") $ unEscape
+ $ column ||| tabs ||| Full
+
+-- | Increase the width of the focused group
+zoomGroupIn :: X ()
+zoomGroupIn = zoomColumnIn
+
+-- | Decrease the size of the focused group
+zoomGroupOut :: X ()
+zoomGroupOut = zoomColumnOut
+
+-- | Reset the size of the focused group to the default
+zoomGroupReset :: X ()
+zoomGroupReset = zoomColumnReset
+
+-- | Toggle whether the currently focused group should be maximized
+-- whenever it has focus.
+toggleGroupFull :: X ()
+toggleGroupFull = toggleGroupFull
+
+-- | Rotate the layouts in the focused group.
+groupToNextLayout :: X ()
+groupToNextLayout = sendMessage $ escape NextLayout
+
+-- | Switch the focused group to the \"maximized\" layout.
+groupToFullLayout :: X ()
+groupToFullLayout = sendMessage $ escape $ JumpToLayout "Full"
+
+-- | Switch the focused group to the \"tabbed\" layout.
+groupToTabbedLayout :: X ()
+groupToTabbedLayout = sendMessage $ escape $ JumpToLayout "Tabs"
+
+-- | Switch the focused group to the \"column\" layout.
+groupToVerticalLayout :: X ()
+groupToVerticalLayout = sendMessage $ escape $ JumpToLayout "Column"
+