diff options
author | David Roundy <droundy@darcs.net> | 2007-06-12 00:49:22 +0200 |
---|---|---|
committer | David Roundy <droundy@darcs.net> | 2007-06-12 00:49:22 +0200 |
commit | 6a07f2897dfbdc799f6ef441b73ab6242721e911 (patch) | |
tree | f6afab775ba578f5504480cf97f0a86e5635f583 | |
parent | 3d93d359bae57d3981f23f8f515268dc8567d122 (diff) | |
download | XMonadContrib-6a07f2897dfbdc799f6ef441b73ab6242721e911.tar.gz XMonadContrib-6a07f2897dfbdc799f6ef441b73ab6242721e911.tar.xz XMonadContrib-6a07f2897dfbdc799f6ef441b73ab6242721e911.zip |
add new combo layout combiner.
darcs-hash:20070611224922-72aca-0881579ddddc2e12c9f9cb4cba9031a725a70913.gz
-rw-r--r-- | Combo.hs | 26 |
1 files changed, 26 insertions, 0 deletions
diff --git a/Combo.hs b/Combo.hs new file mode 100644 index 0000000..4a9598d --- /dev/null +++ b/Combo.hs @@ -0,0 +1,26 @@ +-- A layout that combines multiple layouts. + +-- To use this layout, 'import XMonadContrib.Combo' and add something like +-- 'combo [(full,1),(tabbed,1)] (twoPane 0.03 0.5)' to your defaultLayouts. + +module XMonadContrib.Combo where + +import XMonad + +combo :: [(Layout, Int)] -> Layout -> Layout +combo origls super = Layout { doLayout = arrange, 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) + 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) + return $ concat out + message m = do msuper' <- modifyLayout super m + case msuper' of + Nothing -> return Nothing + Just super' -> return $ Just $ combo origls super' |