aboutsummaryrefslogtreecommitdiffstats
path: root/Tabbed.hs
blob: 106afa878bc601ec9e8ee8153353c2cad48e2016 (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
module XMonadContrib.Tabbed ( tabbed ) where

-- This module defines a tabbed layout.

-- You can use this module with the following in your config file:

-- import XMonadContrib.Tabbed

-- defaultLayouts :: [Layout]
-- defaultLayouts = [ tabbed
--                  , ... ]

import Control.Monad ( forM, liftM )
import Control.Monad.State ( gets )

import Graphics.X11.Xlib
import XMonad
import XMonadContrib.Decoration
import Operations ( focus )
import qualified StackSet as W

import XMonadContrib.NamedWindows

tabbed :: Layout
tabbed =  Layout { doLayout = dolay, modifyLayout = const (return Nothing) }

dolay :: Rectangle -> W.Stack Window -> X [(Window, Rectangle)]
dolay sc (W.Node w [] []) = return [(w,sc)]
dolay sc@(Rectangle x y wid _) s@(W.Node w _ _) =
    do let ws = W.integrate s
           ts = gentabs x y wid (length ws)
           tws = zip ts ws
           maketab (t,w) = newDecoration w t 1 0x000000 0x777777 (drawtab t w) (focus w)
           drawtab r@(Rectangle _ _ wt ht) w d w' gc =
               do nw <- getName w
                  tabcolor <- (maybe 0x888888 (\focusw -> if focusw == w then 0xBBBBBB else 0x888888) . W.peek) `liftM` gets windowset
                  io $ setForeground d gc tabcolor
                  io $ fillRectangles d w' gc [Rectangle 0 0 wt ht]
                  io $ setForeground d gc 0x000000
                  centerText d w' gc r (show nw)
           centerText d w' gc (Rectangle _ _ wt ht) name =
               do font <- io (fontFromGC d gc >>= queryFont d)
                  -- let (_,namew,nameh,_) = textExtents font name -- textExtents causes a crash!
                  -- let nameh = ht `div` 2
                  --     namew = textWidth font name -- textWidth also causes a crash!
                  let nameh = ht - 6
                      namew = wt - 10
                  io $ drawString d w' gc
                         (fromIntegral (wt `div` 2) - fromIntegral (namew `div` 2))
                         (fromIntegral (ht `div` 2) + fromIntegral (nameh `div` 2)) name
       forM tws maketab
       return [ (w,shrink sc) ]

shrink :: Rectangle -> Rectangle
shrink (Rectangle x y w h) = Rectangle x (y+tabsize) w (h-tabsize)

gentabs :: Position -> Position -> Dimension -> Int -> [Rectangle]
gentabs _ _ _ 0 = []
gentabs x y w num = Rectangle x y (wid - 2) (tabsize - 2)
                   : gentabs (x + fromIntegral wid) y (w - wid) (num - 1)
                              where wid = w `div` (fromIntegral num)

tabsize :: Integral a => a
tabsize = 20