aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--Combo.hs3
-rw-r--r--MetaModule.hs1
-rw-r--r--SimpleStacking.hs50
-rw-r--r--Tabbed.hs8
4 files changed, 57 insertions, 5 deletions
diff --git a/Combo.hs b/Combo.hs
index cdf4092..1b0d04a 100644
--- a/Combo.hs
+++ b/Combo.hs
@@ -27,10 +27,11 @@ import Operations ( UnDoLayout(UnDoLayout) )
-- To use this layout write, in your Config.hs:
--
-- > import XMonadContrib.Combo
+-- > import XMonadContrib.SimpleStacking
--
-- 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.
diff --git a/MetaModule.hs b/MetaModule.hs
index 77fb9bc..c8f4d37 100644
--- a/MetaModule.hs
+++ b/MetaModule.hs
@@ -42,6 +42,7 @@ import XMonadContrib.NamedWindows ()
import XMonadContrib.NoBorders ()
import XMonadContrib.RotView ()
import XMonadContrib.SimpleDate ()
+import XMonadContrib.SimpleStacking ()
import XMonadContrib.Spiral ()
import XMonadContrib.Square ()
import XMonadContrib.Submap ()
diff --git a/SimpleStacking.hs b/SimpleStacking.hs
new file mode 100644
index 0000000..ed1e3ef
--- /dev/null
+++ b/SimpleStacking.hs
@@ -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)
diff --git a/Tabbed.hs b/Tabbed.hs
index 031f9c5..a4490d2 100644
--- a/Tabbed.hs
+++ b/Tabbed.hs
@@ -34,18 +34,18 @@ import XMonadContrib.NamedWindows
-- You can use this module with the following in your configuration file:
--
-- > import XMonadContrib.Tabbed
+-- > import XMonadContrib.SimpleStacking
--
-- > defaultLayouts :: [Layout]
--- > defaultLayouts = [ tabbed shrinkText
+-- > defaultLayouts = [ simpleStacking $ tabbed shrinkText
-- > , ... ]
-
tabbed :: Shrinker -> Layout Window
tabbed shrinkT = Layout { doLayout = dolay shrinkT, modifyLayout = const (return Nothing) }
dolay :: Shrinker -> Rectangle -> W.Stack Window -> X [(Window, Rectangle)]
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"
inactivecolor <- io $ initColor dpy "#888888"
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 ht - fromIntegral (asc `div` 2)) name'
forM tws maketab
- return [ (w,shrink sc) ]
+ return $ map (\w -> (w,shrink sc)) ws
type Shrinker = String -> [String]