aboutsummaryrefslogtreecommitdiffstats
path: root/SimpleStacking.hs
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2007-06-21 17:15:24 +0200
committerDavid Roundy <droundy@darcs.net>2007-06-21 17:15:24 +0200
commitae3fa53317da8447dcc005ea57a48ca4be4d3c0a (patch)
treea4685e4cf141bca293bbc43510e8062c2a2cf819 /SimpleStacking.hs
parent5acd4ad8b1edd9cf0953d8347bb64bafd88f743c (diff)
downloadXMonadContrib-ae3fa53317da8447dcc005ea57a48ca4be4d3c0a.tar.gz
XMonadContrib-ae3fa53317da8447dcc005ea57a48ca4be4d3c0a.tar.xz
XMonadContrib-ae3fa53317da8447dcc005ea57a48ca4be4d3c0a.zip
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' darcs-hash:20070621151524-72aca-2466fff5a37ce1388879367c419cf52161f8f838.gz
Diffstat (limited to 'SimpleStacking.hs')
-rw-r--r--SimpleStacking.hs50
1 files changed, 50 insertions, 0 deletions
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)