From 6cd7adf93fa8da770d9faa894e75694dd877a50a Mon Sep 17 00:00:00 2001 From: Andrea Rossato Date: Mon, 18 Feb 2008 17:11:21 +0100 Subject: Add TabBarDecoration, a layout modifier to add a bar of tabs to any layout ... and port DecorationMadness to the new system. darcs-hash:20080218161121-32816-5c834c6f6c2c8b156a20f140ee15049c87f623b8.gz --- XMonad/Layout/TabBarDecoration.hs | 70 +++++++++++++++++++++++++++++++++++++++ 1 file changed, 70 insertions(+) create mode 100644 XMonad/Layout/TabBarDecoration.hs (limited to 'XMonad/Layout/TabBarDecoration.hs') diff --git a/XMonad/Layout/TabBarDecoration.hs b/XMonad/Layout/TabBarDecoration.hs new file mode 100644 index 0000000..00cfd03 --- /dev/null +++ b/XMonad/Layout/TabBarDecoration.hs @@ -0,0 +1,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 -- cgit v1.2.3