aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/HintedGrid.hs
diff options
context:
space:
mode:
authorLukas Mai <l.mai@web.de>2008-04-02 06:28:46 +0200
committerLukas Mai <l.mai@web.de>2008-04-02 06:28:46 +0200
commitbc99bc2c41fba3f3e8e35b9ee512adeedea31d6a (patch)
tree7672a32bc71df739d3f308f94f383f5c9eb167ea /XMonad/Layout/HintedGrid.hs
parent4126825a61896aa836ebc3b89a5a568e91172720 (diff)
downloadXMonadContrib-bc99bc2c41fba3f3e8e35b9ee512adeedea31d6a.tar.gz
XMonadContrib-bc99bc2c41fba3f3e8e35b9ee512adeedea31d6a.tar.xz
XMonadContrib-bc99bc2c41fba3f3e8e35b9ee512adeedea31d6a.zip
HintedGrid: guesstimate window flexibility and layout rigid windows first
darcs-hash:20080402042846-462cf-02aa424c4357675351146f9bdeffe8ba82d9fb9b.gz
Diffstat (limited to 'XMonad/Layout/HintedGrid.hs')
-rw-r--r--XMonad/Layout/HintedGrid.hs8
1 files changed, 5 insertions, 3 deletions
diff --git a/XMonad/Layout/HintedGrid.hs b/XMonad/Layout/HintedGrid.hs
index 0e2b726..731af89 100644
--- a/XMonad/Layout/HintedGrid.hs
+++ b/XMonad/Layout/HintedGrid.hs
@@ -27,6 +27,8 @@ import XMonad hiding (windows)
import XMonad.StackSet
import Control.Monad.State
+import Data.List
+import Data.Ord
infixr 9 .
(.) :: (Functor f) => (a -> b) -> f a -> f b
@@ -62,10 +64,10 @@ replicateS n = runState . replicateM n . State
doColumn :: Dimension -> Dimension -> Dimension -> [(D -> D)] -> [D]
doColumn width height k adjs =
let
- (h1, d1) = doC height k adjs
- (h2, d2) = doC height k (reverse adjs)
+ (ind, fs) = unzip . sortBy (comparing $ snd . ($ (width, height)) . snd) . zip [0 :: Int ..] $ adjs
+ (_, ds) = doC height k fs
in
- if h2 < h1 then reverse d2 else d1
+ map snd . sortBy (comparing fst) . zip ind $ ds
where
doC h _ [] = (h, [])
doC h n (f : fs) = (adj :) . doC (h - h') (n - 1) fs