@@ -77,10 +77,9 @@ data MultiCol a = MultiCol
7777 } deriving (Show ,Read ,Eq )
7878
7979instance LayoutClass MultiCol a where
80- doLayout l r s = return (zip w rlist, resl)
80+ doLayout l r s = return (combine s rlist, resl)
8181 where rlist = doL (multiColNWin l') (multiColSize l') r wlen
82- w = W. integrate s
83- wlen = length w
82+ wlen = length $ W. integrate s
8483 -- Make sure the list of columns is big enough and update active column
8584 nw = multiColNWin l ++ repeat (multiColDefWin l)
8685 l' = l { multiColNWin = take (max (length $ multiColNWin l) $ getCol (wlen- 1 ) nw + 1 ) nw
@@ -90,6 +89,7 @@ instance LayoutClass MultiCol a where
9089 resl = if l'== l
9190 then Nothing
9291 else Just l'
92+ combine (W. Stack foc left right) rs = zip (foc : reverse left ++ right) $ raiseFocused (length left) rs
9393 handleMessage l m =
9494 return $ msum [fmap resize (fromMessage m)
9595 ,fmap incmastern (fromMessage m)]
@@ -104,6 +104,10 @@ instance LayoutClass MultiCol a where
104104 a = multiColActive l
105105 description _ = " MultiCol"
106106
107+ raiseFocused :: Int -> [a ] -> [a ]
108+ raiseFocused n xs = actual ++ before ++ after
109+ where (before,rest) = splitAt n xs
110+ (actual,after) = splitAt 1 rest
107111
108112-- | Get which column a window is in, starting at 0.
109113getCol :: Int -> [Int ] -> Int
0 commit comments