diff options
author | Max Rabkin <max.rabkin@gmail.com> | 2009-09-29 19:33:46 +0200 |
---|---|---|
committer | Max Rabkin <max.rabkin@gmail.com> | 2009-09-29 19:33:46 +0200 |
commit | 03276f70fa625e7ba594682bf5621430dc0f3c68 (patch) | |
tree | 26810bc028ec6956bcec25db1ae2fda826ad44ee /XMonad/Layout | |
parent | 139230cdeb304b501ff31781f2b8653fd75248fa (diff) | |
download | XMonadContrib-03276f70fa625e7ba594682bf5621430dc0f3c68.tar.gz XMonadContrib-03276f70fa625e7ba594682bf5621430dc0f3c68.tar.xz XMonadContrib-03276f70fa625e7ba594682bf5621430dc0f3c68.zip |
Support IncMasterN in Selective
Ignore-this: 3fd288d0062905177c06006ea4066f6d
darcs-hash:20090929173346-a5338-2d3965e3bade676e302db3015b9a8147e45fdd92.gz
Diffstat (limited to 'XMonad/Layout')
-rw-r--r-- | XMonad/Layout/Selective.hs | 9 |
1 files changed, 9 insertions, 0 deletions
diff --git a/XMonad/Layout/Selective.hs b/XMonad/Layout/Selective.hs index f1a001d..8b78c45 100644 --- a/XMonad/Layout/Selective.hs +++ b/XMonad/Layout/Selective.hs @@ -22,6 +22,7 @@ module XMonad.Layout.Selective where import XMonad.Core import XMonad.StackSet +import XMonad.Layout (IncMasterN (..)) import XMonad.Layout.LayoutModifier import Control.Applicative ((<$>)) @@ -70,5 +71,13 @@ instance LayoutModifier Selective a where pureModifier (Selective sel) _ stk wins = (wins, Selective . update sel <$> stk) + pureMess (Selective s) m = Selective . incmastern <$> fromMessage m + where + incmastern (IncMasterN n) = + let nm = (nMaster s + n) `max` 0 + in if nMaster s == start s + then s { nMaster = nm, start = nm } + else s { nMaster = nm } + selective :: Int -> Int -> l a -> ModifiedLayout Selective l a selective m r = ModifiedLayout . Selective $ Sel { nMaster=m, start=m, nRest=r } |