aboutsummaryrefslogtreecommitdiffstats
path: root/Tabbed.hs
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2007-06-23 23:09:52 +0200
committerDavid Roundy <droundy@darcs.net>2007-06-23 23:09:52 +0200
commit5f1312128d87961231d5431af0885711a01cd120 (patch)
tree5b785ff7779d1d842bc17ac554ccbe759ea4c35d /Tabbed.hs
parentb40d0f8237f4140decbf4edc7366b900cf82428b (diff)
downloadXMonadContrib-5f1312128d87961231d5431af0885711a01cd120.tar.gz
XMonadContrib-5f1312128d87961231d5431af0885711a01cd120.tar.xz
XMonadContrib-5f1312128d87961231d5431af0885711a01cd120.zip
make everything work with new doLayout.
This modifies all the contrib modules to work (so far as I know) with the new contrib layout. The exception is the LayoutHooks module, which isn't used. It exports an API that is inherently unsafe, so far as I can tell (and always has been). darcs-hash:20070623210952-72aca-1993ca13dc6996b59fedacc271c03fbaf87eabaa.gz
Diffstat (limited to 'Tabbed.hs')
-rw-r--r--Tabbed.hs49
1 files changed, 16 insertions, 33 deletions
diff --git a/Tabbed.hs b/Tabbed.hs
index 48205d9..9948681 100644
--- a/Tabbed.hs
+++ b/Tabbed.hs
@@ -20,7 +20,8 @@ module XMonadContrib.Tabbed (
, TConf (..), defaultTConf
) where
-import Control.Monad ( forM )
+import Control.Monad ( forM, liftM )
+import Control.Monad.State ( gets )
import Graphics.X11.Xlib
import XMonad
@@ -29,6 +30,7 @@ import Operations ( focus, initColor )
import qualified StackSet as W
import XMonadContrib.NamedWindows
+import XMonadContrib.LayoutHelpers ( idModify )
-- $usage
-- You can use this module with the following in your configuration file:
@@ -50,42 +52,23 @@ import XMonadContrib.NamedWindows
-- > defaultLayouts = [ simpleStacking $ tabbed shrinkText myconfig
-- > , ... ]
-data TConf =
- TConf { activeColor :: String
- , inactiveColor :: String
- , bgColor :: String
- , textColor :: String
- , fontName :: String
- , tabSize :: Int
- } deriving (Show, Read)
-
-defaultTConf :: TConf
-defaultTConf =
- TConf { activeColor ="#BBBBBB"
- , inactiveColor = "#888888"
- , bgColor = "#000000"
- , textColor = "#000000"
- , fontName = "-misc-fixed-*-*-*-*-10-*-*-*-*-*-*-*"
- , tabSize = 20
- }
+tabbed :: Shrinker -> Layout Window
+tabbed shrinkT = Layout { doLayout = dolay shrinkT, modifyLayout = const (return Nothing) }
-tabbed :: Shrinker -> TConf -> Layout Window
-tabbed shrinkT config = Layout { doLayout = dolay shrinkT config, modifyLayout = const (return Nothing) }
-
-dolay :: Shrinker -> TConf -> Rectangle -> W.Stack Window -> X [(Window, Rectangle)]
-dolay _ _ sc (W.Stack w [] []) = return [(w,sc)]
-dolay shr conf sc@(Rectangle x y wid _) s = withDisplay $ \dpy ->
- do activecolor <- io $ initColor dpy $ activeColor conf
- inactivecolor <- io $ initColor dpy $ inactiveColor conf
- textcolor <- io $ initColor dpy $ textColor conf
- bgcolor <- io $ initColor dpy $ bgColor conf
+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 = withDisplay $ \dpy ->
+ do activecolor <- io $ initColor dpy "#BBBBBB"
+ inactivecolor <- io $ initColor dpy "#888888"
+ textcolor <- io $ initColor dpy "#000000"
+ bgcolor <- io $ initColor dpy "#000000"
let ws = W.integrate s
ts = gentabs conf x y wid (length ws)
tws = zip ts ws
- 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 =
+ maketab (t,ow) = newDecoration ow t 1 bgcolor activecolor (drawtab t ow) (focus ow)
+ drawtab r@(Rectangle _ _ wt ht) ow d w' gc =
do nw <- getName ow
- let tabcolor = if W.focus s == ow then activecolor else inactivecolor
+ tabcolor <- (maybe inactivecolor (\focusw -> if focusw == ow then activecolor else inactivecolor) . W.peek) `liftM` gets windowset
io $ setForeground d gc tabcolor
io $ fillRectangles d w' gc [Rectangle 0 0 wt ht]
io $ setForeground d gc textcolor
@@ -99,7 +82,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 [(W.focus s, shrink conf sc)]
+ return $ map (\w -> (w,shrink sc)) ws
type Shrinker = String -> [String]