aboutsummaryrefslogtreecommitdiffstats
path: root/Tabbed.hs
diff options
context:
space:
mode:
authorJason Creighton <jcreigh@gmail.com>2007-06-27 05:39:10 +0200
committerJason Creighton <jcreigh@gmail.com>2007-06-27 05:39:10 +0200
commit1b5e7b626dd6d15c38aaa6555ab72740be58a8bf (patch)
tree7e1d605fec5bc8fa4137eaeef3ea7715eec4a006 /Tabbed.hs
parentbbab7221c7d02d0f7b974f99c2bf5379cbfb4d3c (diff)
downloadXMonadContrib-1b5e7b626dd6d15c38aaa6555ab72740be58a8bf.tar.gz
XMonadContrib-1b5e7b626dd6d15c38aaa6555ab72740be58a8bf.tar.xz
XMonadContrib-1b5e7b626dd6d15c38aaa6555ab72740be58a8bf.zip
Tabbed: Make use of the Stack to get focused window
darcs-hash:20070627033910-b9aa7-0c9dd49af1c853ac608f8b7b368febe687d7343d.gz
Diffstat (limited to 'Tabbed.hs')
-rw-r--r--Tabbed.hs7
1 files changed, 3 insertions, 4 deletions
diff --git a/Tabbed.hs b/Tabbed.hs
index efb91d8..48205d9 100644
--- a/Tabbed.hs
+++ b/Tabbed.hs
@@ -20,8 +20,7 @@ module XMonadContrib.Tabbed (
, TConf (..), defaultTConf
) where
-import Control.Monad ( forM, liftM )
-import Control.Monad.State ( gets )
+import Control.Monad ( forM )
import Graphics.X11.Xlib
import XMonad
@@ -86,7 +85,7 @@ dolay shr conf sc@(Rectangle x y wid _) s = withDisplay $ \dpy ->
maketab (t,ow) = newDecoration ow t 1 bgcolor activecolor (fontName conf) (drawtab t ow) (focus ow)
drawtab r@(Rectangle _ _ wt ht) ow d w' gc fn =
do nw <- getName ow
- tabcolor <- (maybe inactivecolor (\focusw -> if focusw == ow then activecolor else inactivecolor) . W.peek) `liftM` gets windowset
+ let tabcolor = if W.focus s == ow then activecolor else inactivecolor
io $ setForeground d gc tabcolor
io $ fillRectangles d w' gc [Rectangle 0 0 wt ht]
io $ setForeground d gc textcolor
@@ -100,7 +99,7 @@ dolay shr conf sc@(Rectangle x y wid _) s = withDisplay $ \dpy ->
(fromIntegral (wt `div` 2) - fromIntegral (width `div` 2))
((fromIntegral ht + fromIntegral asc) `div` 2) name'
forM tws maketab
- return $ map (\w -> (w,shrink conf sc)) ws
+ return [(W.focus s, shrink conf sc)]
type Shrinker = String -> [String]