aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad
diff options
context:
space:
mode:
authorMax Rabkin <max.rabkin@gmail.com>2009-10-02 13:27:20 +0200
committerMax Rabkin <max.rabkin@gmail.com>2009-10-02 13:27:20 +0200
commit6afa8de084f735296c8b9020d84aa05c4b184257 (patch)
tree5451a8ced9a8b3ff43cfcb571a716d4e4bd04310 /XMonad
parent03276f70fa625e7ba594682bf5621430dc0f3c68 (diff)
downloadXMonadContrib-6afa8de084f735296c8b9020d84aa05c4b184257.tar.gz
XMonadContrib-6afa8de084f735296c8b9020d84aa05c4b184257.tar.xz
XMonadContrib-6afa8de084f735296c8b9020d84aa05c4b184257.zip
added haddocks for L.Selective
Ignore-this: d29016f1261d0176634bb040fcc1836a darcs-hash:20091002112720-a5338-4d23800e34986d1ee473ac299e794b6e4e0093d4.gz
Diffstat (limited to 'XMonad')
-rw-r--r--XMonad/Layout/Selective.hs37
1 files changed, 36 insertions, 1 deletions
diff --git a/XMonad/Layout/Selective.hs b/XMonad/Layout/Selective.hs
index 8b78c45..2999d34 100644
--- a/XMonad/Layout/Selective.hs
+++ b/XMonad/Layout/Selective.hs
@@ -18,7 +18,15 @@
NoMonomorphismRestriction,
NamedFieldPuns #-}
-module XMonad.Layout.Selective where
+module XMonad.Layout.Selective (
+ -- * Description
+ -- $description
+ -- * Usage
+ -- $usage
+
+ -- The Layout Modifier
+ selective
+ ) where
import XMonad.Core
import XMonad.StackSet
@@ -26,6 +34,30 @@ import XMonad.Layout (IncMasterN (..))
import XMonad.Layout.LayoutModifier
import Control.Applicative ((<$>))
+-- $description
+-- Selective is a layout modifier which limits the number of windows on screen.
+-- The first @n@ windows ("the master pane", which may correspond to the
+-- master pane of the underlying layout) plus several others are shown, such
+-- that the focussed window is always visible. Windows are not moved until a
+-- hidden window gains focus.
+
+-- $usage
+-- To use this module, add the following import to @~\/.xmonad\/xmonad.hs@:
+--
+-- > import XMonad.Layout.Selective
+--
+-- > myLayout = (selective 1 3 $ Tall 1 0.03 0.5) ||| Full ||| RandomOtherLayout...
+-- > main = xmonad defaultConfig { layoutHook = myLayout }
+--
+-- The layout modifier accepts the IncMasterN message to change the number of
+-- windows in the "master pane".
+--
+-- For detailed instructions on editing your key bindings, see
+-- "XMonad.Doc.Extending#Editing_key_bindings".
+--
+-- See also 'XMonad.Layout.BoringWindows.boringAuto' for keybindings that skip
+-- the hidden windows.
+
-- invariant: 0 <= nMaster <= start; 1 <= nRest
data Selection = Sel { nMaster :: Int, start :: Int, nRest :: Int }
deriving (Read, Show, Eq)
@@ -79,5 +111,8 @@ instance LayoutModifier Selective a where
then s { nMaster = nm, start = nm }
else s { nMaster = nm }
+-- | Only display the first @m@ windows and @r@ others.
+-- The @IncMasterN@ message will change @m@, as well as passing it onto the
+-- underlying layout.
selective :: Int -> Int -> l a -> ModifiedLayout Selective l a
selective m r = ModifiedLayout . Selective $ Sel { nMaster=m, start=m, nRest=r }