aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/LimitWindows.hs
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2009-06-22 02:43:09 +0200
committerAdam Vogt <vogt.adam@gmail.com>2009-06-22 02:43:09 +0200
commitf2eaf0f2690093d1e105a779a746cdc7b36047f5 (patch)
tree5f5bbd7984456e6cd72afd182abdce7836511d8d /XMonad/Layout/LimitWindows.hs
parentdad19f299b837f3d5a37b7126daa96ec6fefc760 (diff)
downloadXMonadContrib-f2eaf0f2690093d1e105a779a746cdc7b36047f5.tar.gz
XMonadContrib-f2eaf0f2690093d1e105a779a746cdc7b36047f5.tar.xz
XMonadContrib-f2eaf0f2690093d1e105a779a746cdc7b36047f5.zip
Fix window ordering bug in L.LimitWindows
Ignore-this: 7bcfffe335b765c081c18b103d9d450a darcs-hash:20090622004309-1499c-ac234ddda7c9c03403a135bab10fe6f6391906ee.gz
Diffstat (limited to 'XMonad/Layout/LimitWindows.hs')
-rw-r--r--XMonad/Layout/LimitWindows.hs11
1 files changed, 7 insertions, 4 deletions
diff --git a/XMonad/Layout/LimitWindows.hs b/XMonad/Layout/LimitWindows.hs
index 7007c18..61b6164 100644
--- a/XMonad/Layout/LimitWindows.hs
+++ b/XMonad/Layout/LimitWindows.hs
@@ -28,6 +28,7 @@ import XMonad.Layout.LayoutModifier
import XMonad
import qualified XMonad.StackSet as W
import Control.Monad((<=<),guard)
+import Data.Maybe(fromJust)
-- $usage
-- To use this module, add the following import to @~\/.xmonad\/xmonad.hs@:
@@ -43,6 +44,9 @@ import Control.Monad((<=<),guard)
--
-- 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.
increaseLimit :: X ()
increaseLimit = sendMessage $ LimitChange succ
@@ -73,7 +77,7 @@ instance Message LimitChange
instance LayoutModifier LimitWindows a where
pureMess (LimitWindows s n) =
fmap (LimitWindows s) . pos <=< (`app` n) . unLC <=< fromMessage
- where pos x = guard (x>=0) >> return x
+ where pos x = guard (x>=1) >> return x
app f x = guard (f x /= x) >> return (f x)
modifyLayout (LimitWindows style n) ws r =
@@ -83,9 +87,8 @@ instance LayoutModifier LimitWindows a where
Slice -> slice
firstN :: Int -> W.Stack a -> W.Stack a
-firstN n st = W.Stack f (reverse u) d
- where (u,f:d) = splitAt (min (n-1) $ length $ W.up st)
- $ take n $ W.integrate st
+firstN n st = upfocus $ fromJust $ W.differentiate $ take (max 1 n) $ W.integrate st
+ where upfocus = foldr (.) id $ replicate (length (W.up st)) W.focusDown'
-- | A non-wrapping, fixed-size slice of a stack around the focused element
slice :: Int -> W.Stack t -> W.Stack t