add SimpleStacking module to make Combo and Tabbed work together.

WARNING! This change will break existing Tabbed configurations.  The
problem is that there is no way within a Layout's "doLayout" to safely
modify the layout itself.  This makes LayoutHooks fragile, and more to the
point, makes SimpleStacking fragile, so we can't safely define a

tabbed' = simpleStacking . tabbed

A workaround would have been to duplicate the tabbed code, but I'd rather
leave the ugliness and get this fixed.
This commit is contained in:
David Roundy
2007-06-21 15:15:24 +00:00
parent 3f08632b37
commit 10f20c432e
4 changed files with 57 additions and 5 deletions

View File

@@ -27,10 +27,11 @@ import Operations ( UnDoLayout(UnDoLayout) )
-- To use this layout write, in your Config.hs: -- To use this layout write, in your Config.hs:
-- --
-- > import XMonadContrib.Combo -- > import XMonadContrib.Combo
-- > import XMonadContrib.SimpleStacking
-- --
-- and add something like -- and add something like
-- --
-- > combo [(full,1),(tabbed shrinkText,1)] (twoPane 0.03 0.5) -- > simpleStacking $ combo [(full,1),(tabbed shrinkText,1)] (twoPane 0.03 0.5)
-- --
-- to your defaultLayouts. -- to your defaultLayouts.

View File

@@ -42,6 +42,7 @@ import XMonadContrib.NamedWindows ()
import XMonadContrib.NoBorders () import XMonadContrib.NoBorders ()
import XMonadContrib.RotView () import XMonadContrib.RotView ()
import XMonadContrib.SimpleDate () import XMonadContrib.SimpleDate ()
import XMonadContrib.SimpleStacking ()
import XMonadContrib.Spiral () import XMonadContrib.Spiral ()
import XMonadContrib.Square () import XMonadContrib.Square ()
import XMonadContrib.Submap () import XMonadContrib.Submap ()

50
SimpleStacking.hs Normal file
View File

@@ -0,0 +1,50 @@
{-# OPTIONS -fglasgow-exts #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonadContrib.SimpleStacking
-- Copyright : (c) David Roundy <droundy@darcs.net>
-- License : BSD-style (see LICENSE)
--
-- Maintainer : David Roundy <droundy@darcs.net>
-- Stability : unstable
-- Portability : unportable
--
-- A module to be used to obtain a simple "memory" of stacking order.
--
-----------------------------------------------------------------------------
module XMonadContrib.SimpleStacking (
-- * Usage
-- $usage
simpleStacking
) where
import Control.Monad.State ( modify )
import qualified Data.Map as M
import Data.Maybe ( catMaybes )
import Data.List ( nub, lookup )
import StackSet ( focus, tag, workspace, current, integrate )
import Graphics.X11.Xlib ( Window )
import XMonad
-- $usage
-- You can use this module for
-- See, for instance, "XMonadContrib.Tabbed"
simpleStacking :: Layout Window -> Layout Window
simpleStacking = simpleStacking' []
simpleStacking' :: [Window] -> Layout Window -> Layout Window
simpleStacking' st l = l { doLayout = dl
, modifyLayout = \m -> fmap (simpleStacking' st) `fmap` modifyLayout l m }
where dl r s = do modify $ \ state ->
state { layouts = M.adjust
(\(_,ss)->(simpleStacking'
(focus s:filter (`elem` integrate s) st) l,ss))
(tag.workspace.current.windowset $ state)
(layouts state) }
lo <- doLayout l r s
let m = map (\ (w,rr) -> (w,(w,rr))) lo
return $ catMaybes $ map ((flip lookup) m) $ nub (focus s : st ++ map fst lo)

View File

@@ -34,18 +34,18 @@ import XMonadContrib.NamedWindows
-- You can use this module with the following in your configuration file: -- You can use this module with the following in your configuration file:
-- --
-- > import XMonadContrib.Tabbed -- > import XMonadContrib.Tabbed
-- > import XMonadContrib.SimpleStacking
-- --
-- > defaultLayouts :: [Layout] -- > defaultLayouts :: [Layout]
-- > defaultLayouts = [ tabbed shrinkText -- > defaultLayouts = [ simpleStacking $ tabbed shrinkText
-- > , ... ] -- > , ... ]
tabbed :: Shrinker -> Layout Window tabbed :: Shrinker -> Layout Window
tabbed shrinkT = Layout { doLayout = dolay shrinkT, modifyLayout = const (return Nothing) } tabbed shrinkT = Layout { doLayout = dolay shrinkT, modifyLayout = const (return Nothing) }
dolay :: Shrinker -> Rectangle -> W.Stack Window -> X [(Window, Rectangle)] dolay :: Shrinker -> Rectangle -> W.Stack Window -> X [(Window, Rectangle)]
dolay _ sc (W.Stack w [] []) = return [(w,sc)] dolay _ sc (W.Stack w [] []) = return [(w,sc)]
dolay shr sc@(Rectangle x y wid _) s@(W.Stack w _ _) = withDisplay $ \dpy -> dolay shr sc@(Rectangle x y wid _) s = withDisplay $ \dpy ->
do activecolor <- io $ initColor dpy "#BBBBBB" do activecolor <- io $ initColor dpy "#BBBBBB"
inactivecolor <- io $ initColor dpy "#888888" inactivecolor <- io $ initColor dpy "#888888"
textcolor <- io $ initColor dpy "#000000" textcolor <- io $ initColor dpy "#000000"
@@ -72,7 +72,7 @@ dolay shr sc@(Rectangle x y wid _) s@(W.Stack w _ _) = withDisplay $ \dpy ->
(fromIntegral (wt `div` 2) - fromIntegral (width `div` 2)) (fromIntegral (wt `div` 2) - fromIntegral (width `div` 2))
(fromIntegral ht - fromIntegral (asc `div` 2)) name' (fromIntegral ht - fromIntegral (asc `div` 2)) name'
forM tws maketab forM tws maketab
return [ (w,shrink sc) ] return $ map (\w -> (w,shrink sc)) ws
type Shrinker = String -> [String] type Shrinker = String -> [String]