aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/TabBarDecoration.hs
blob: 00cfd03fcd945623dedd823bb1d43abd73b8f84e (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
65
66
67
68
69
70
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  XMonad.Layout.TabBarDecoration
-- Copyright   :  (c) 2007 Andrea Rossato
-- License     :  BSD-style (see xmonad/LICENSE)
--
-- Maintainer  :  andrea.rossato@unibz.it
-- Stability   :  unstable
-- Portability :  unportable
--
-- A layout modifier to add a bar of tabs to your layouts.
-----------------------------------------------------------------------------

module XMonad.Layout.TabBarDecoration
    ( -- * Usage
      -- $usage
      simpleTabBar, tabBar
    , defaultTheme, shrinkText
    , TabBarDecoration (..), XPPosition (..)
    ) where

import Data.List
import XMonad
import qualified XMonad.StackSet as S
import XMonad.Layout.Decoration
import XMonad.Prompt ( XPPosition (..) )
-- $usage
-- You can use this module with the following in your
-- @~\/.xmonad\/xmonad.hs@:
--
-- > import XMonad.Layout.TabBarDecoration
--
-- Then edit your @layoutHook@ by adding the layout you want:
--
-- > main = xmonad defaultConfig { layoutHook = simpleTabBar $ layoutHook defaultConfig}
--
-- For more detailed instructions on editing the layoutHook see:
--
-- "XMonad.Doc.Extending#Editing_the_layout_hook"
--
-- 'tabBar' will give you the possibility of setting a custom shrinker
-- and a custom theme.
--
-- The deafult theme can be dynamically change with the xmonad theme
-- selector. See "XMonad.Prompt.Theme". For more themse, look at
-- "XMonad.Util.Themes"

simpleTabBar :: Eq a => l a -> ModifiedLayout (Decoration TabBarDecoration DefaultShrinker) l a
simpleTabBar = decoration shrinkText defaultTheme (TabBar Top)

tabBar :: (Eq a, Shrinker s) => s -> Theme -> XPPosition -> l a -> ModifiedLayout (Decoration TabBarDecoration s) l a
tabBar s t p = decoration s t (TabBar p)

data TabBarDecoration a = TabBar XPPosition deriving (Read, Show)

instance Eq a => DecorationStyle TabBarDecoration a where
    describeDeco  _ = "TabBar"
    decorateFirst _ = True
    shrink    _ _ r = r
    decorationMouseDragHook _ _ _ = return ()
    pureDecoration (TabBar p) _ dht (Rectangle x y wh ht) s _ (w,_) =
        if isInStack s w then Just $ Rectangle nx ny nwh (fi dht) else Nothing
        where nwh = wh `div` max 1 (fi $ length $ S.integrate s)
              ny = case p of
                     Top    -> y
                     Bottom -> y + fi ht - fi dht
              nx  = case w `elemIndex` (S.integrate s) of
                      Just i  -> x + (fi nwh * fi i)
                      Nothing -> x