aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--Combo.hs8
1 files changed, 5 insertions, 3 deletions
diff --git a/Combo.hs b/Combo.hs
index 4a9598d..fa9c6c6 100644
--- a/Combo.hs
+++ b/Combo.hs
@@ -6,19 +6,21 @@
module XMonadContrib.Combo where
import XMonad
+import StackSet ( integrate, differentiate )
combo :: [(Layout, Int)] -> Layout -> Layout
-combo origls super = Layout { doLayout = arrange, modifyLayout = message }
+combo origls super = Layout { doLayout = \r s -> arrange r (integrate s), modifyLayout = message }
where arrange _ [] = return []
arrange r [w] = return [(w,r)]
arrange rinput origws =
- do rs <- map snd `fmap` doLayout super rinput (take (length origls) origws)
+ do rs <- map snd `fmap` doLayout super rinput (differentiate $ take (length origls) origws)
let wss [] _ = []
wss [_] ws = [ws]
wss (n:ns) ws = take len1 ws : wss ns (drop len1 ws)
where len1 = min n (length ws - length ns)
out <- sequence $ zipWith3 doLayout (map fst origls) rs
- (wss (take (length rs) $ map snd origls) origws)
+ (map differentiate $
+ wss (take (length rs) $ map snd origls) origws)
return $ concat out
message m = do msuper' <- modifyLayout super m
case msuper' of