aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout
diff options
context:
space:
mode:
authorAdam Vogt <vogt.adam@gmail.com>2009-10-15 03:01:23 +0200
committerAdam Vogt <vogt.adam@gmail.com>2009-10-15 03:01:23 +0200
commite1295ab77d0dfc6f77321031db90222419805b2c (patch)
tree683f06f6a2a6b7019eb8a2b623292a00d19838d9 /XMonad/Layout
parentbcf6914fe0bd5386c207139df1ee39186573b5a8 (diff)
downloadXMonadContrib-e1295ab77d0dfc6f77321031db90222419805b2c.tar.gz
XMonadContrib-e1295ab77d0dfc6f77321031db90222419805b2c.tar.xz
XMonadContrib-e1295ab77d0dfc6f77321031db90222419805b2c.zip
Remove NamedFieldPuns from L.LimitWindows
Ignore-this: 228ca5b5ac067876c3b2809fc03b6016 This is more ugly, but otherwise we have lots of trouble for ghc-6.8 compatibility (due to the recomended flag having changed) darcs-hash:20091015010123-1499c-82099ae2f0598dfbb86c389aa5d3ad4a6151f465.gz
Diffstat (limited to 'XMonad/Layout')
-rw-r--r--XMonad/Layout/LimitWindows.hs28
1 files changed, 14 insertions, 14 deletions
diff --git a/XMonad/Layout/LimitWindows.hs b/XMonad/Layout/LimitWindows.hs
index bfd1906..1b66c93 100644
--- a/XMonad/Layout/LimitWindows.hs
+++ b/XMonad/Layout/LimitWindows.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable, NamedFieldPuns, PatternGuards #-}
+{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable, PatternGuards #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonad.Layout.LimitWindows
@@ -128,27 +128,27 @@ instance LayoutModifier Selection a where
Nothing
select :: Selection l -> W.Stack a -> W.Stack a
-select (Sel { nMaster, start, nRest }) stk
- | lups < nMaster
- = stk { W.down=take (nMaster - lups - 1) downs ++
- (take nRest . drop (start - lups - 1) $ downs) }
+select s stk
+ | lups < nMaster s
+ = stk { W.down=take (nMaster s - lups - 1) downs ++
+ (take (nRest s) . drop (start s - lups - 1) $ downs) }
| otherwise
- = stk { W.up=reverse (take nMaster ups ++ drop start ups),
- W.down=take (nRest - (lups - start) - 1) downs }
+ = stk { W.up=reverse (take (nMaster s) ups ++ drop (start s) ups),
+ W.down=take ((nRest s) - (lups - start s) - 1) downs }
where
downs = W.down stk
ups = reverse $ W.up stk
lups = length ups
updateStart :: Selection l -> W.Stack a -> Int
-updateStart (Sel { nMaster, start, nRest }) stk
- | lups < nMaster -- the focussed window is in the master pane
- = start `min` (lups + ldown - nRest + 1) `max` nMaster
+updateStart s stk
+ | lups < nMaster s -- the focussed window is in the master pane
+ = start s `min` (lups + ldown - (nRest s) + 1) `max` nMaster s
| otherwise
- = start `min` lups
- `max` (lups - nRest + 1)
- `min` (lups + ldown - nRest + 1)
- `max` nMaster
+ = start s `min` lups
+ `max` (lups - (nRest s) + 1)
+ `min` (lups + ldown - (nRest s) + 1)
+ `max` nMaster s
where
lups = length $ W.up stk
ldown = length $ W.down stk