aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Groups/Wmii.hs
blob: fc0b59f390600c0184ee8c0fb93c6eb08bf5aada (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
{-# 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
                                 , def
                                 , 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 def
--
-- 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"