From 387cac87e5f32735e2ff8dbb2fb620dbf46edccf Mon Sep 17 00:00:00 2001 From: David Roundy Date: Tue, 5 Feb 2008 21:23:43 +0100 Subject: make tabbed work nicely with LayoutCombinators and WindowNavigation. The problem is that WindowNavigation assumes all windows are navigable, and it was getting confused by decorations. With a bit of work, we can decorate windows *after* combining layouts just fine. darcs-hash:20080205202343-72aca-38ec52df06997059edaac4085a6f1d86d5a756ae.gz --- XMonad/Config/Droundy.hs | 19 ++++++++++--------- XMonad/Layout/Tabbed.hs | 18 +++++++++++++----- 2 files changed, 23 insertions(+), 14 deletions(-) diff --git a/XMonad/Config/Droundy.hs b/XMonad/Config/Droundy.hs index 2b07cd0..9293bdd 100644 --- a/XMonad/Config/Droundy.hs +++ b/XMonad/Config/Droundy.hs @@ -6,7 +6,7 @@ -- ------------------------------------------------------------------------ -module XMonad.Config.Droundy ( config, mytab ) where +module XMonad.Config.Droundy ( config ) where --import Control.Monad.State ( modify ) @@ -21,6 +21,7 @@ import System.Exit -- % Extension-provided imports +import XMonad.Layout.Simplest import XMonad.Layout.Tabbed import XMonad.Layout.Combo import XMonad.Layout.Mosaic @@ -32,6 +33,7 @@ import XMonad.Layout.WindowNavigation import XMonad.Layout.NoBorders import XMonad.Layout.WorkspaceDir import XMonad.Layout.ToggleLayouts +import XMonad.Layout.ShowWName ( showWName ) import XMonad.Prompt import XMonad.Prompt.Layout @@ -132,13 +134,14 @@ config = -- withUrgencyHook FocusUrgencyHook $ defaultConfig { borderWidth = 1 -- Width of the window border in pixels. , XMonad.workspaces = ["1:mutt","2:iceweasel"] - , layoutHook = workspaceDir "~" $ windowNavigation $ + , layoutHook = addTabs CustomShrink defaultTheme $ showWName $ workspaceDir "~" $ + windowNavigation $ toggleLayouts (noBorders Full) $ avoidStruts $ - named "tabbed" (noBorders mytab) ||| - named "xclock" (mytab ****//* combineTwo Square mytab mytab) ||| - named "three" (mytab **//* mytab *//* combineTwo Square mytab mytab) ||| - named "widescreen" ((mytab *||* mytab) - ****//* combineTwo Square mytab mytab) -- ||| + named "tabbed" (noBorders Simplest) ||| + named "xclock" (Simplest ****//* combineTwo Square Simplest Simplest) ||| + named "three" (Simplest **//* Simplest *//* combineTwo Square Simplest Simplest) ||| + named "widescreen" ((Simplest *||* Simplest) + ****//* combineTwo Square Simplest Simplest) -- ||| --mosaic 0.25 0.5 , manageHook = manageHook defaultConfig <+> manageDocks -- add panel-handling , logHook = ewmhDesktopsLogHook -- actually, no logging here, just other stuff @@ -149,8 +152,6 @@ config = -- withUrgencyHook FocusUrgencyHook $ , XMonad.keys = keys } -mytab = tabbed CustomShrink defaultTheme - instance Shrinker CustomShrink where shrinkIt shr s | Just s' <- dropFromHead " " s = shrinkIt shr s' shrinkIt shr s | Just s' <- dropFromTail " " s = shrinkIt shr s' diff --git a/XMonad/Layout/Tabbed.hs b/XMonad/Layout/Tabbed.hs index 33596ac..db4ba3e 100644 --- a/XMonad/Layout/Tabbed.hs +++ b/XMonad/Layout/Tabbed.hs @@ -17,7 +17,7 @@ module XMonad.Layout.Tabbed ( -- * Usage: -- $usage - tabbed + tabbed, addTabs , Theme (..) , defaultTheme , TabbedDecoration (..) @@ -61,13 +61,21 @@ tabbed :: (Eq a, Shrinker s) => s -> Theme -> ModifiedLayout (Decoration TabbedDecoration s) Simplest a tabbed s c = decoration s c Tabbed Simplest +addTabs :: (Eq a, LayoutClass l a, Shrinker s) => s -> Theme -> l a + -> ModifiedLayout (Decoration TabbedDecoration s) l a +addTabs s c l = decoration s c Tabbed l + data TabbedDecoration a = Tabbed deriving (Read, Show) instance Eq a => DecorationStyle TabbedDecoration a where describeDeco _ = "Tabbed" - decorateFirst _ = False - pureDecoration _ _ ht (Rectangle x y wh _) s wrs (w,_) = Just $ Rectangle nx y nwh (fi ht) - where nwh = wh `div` max 1 (fi $ length wrs) - nx = case w `elemIndex` (S.integrate s) of + decorateFirst _ = True + pureDecoration _ _ ht _ s wrs (w,r@(Rectangle x y wh _)) = + if length wrs' <= 1 then Nothing + else Just $ Rectangle nx y nwh (fi ht) + where wrs' = filter ((==r) . snd) wrs + ws = map fst wrs' + nwh = wh `div` max 1 (fi $ length wrs') + nx = case elemIndex w $ filter (`elem` ws) (S.integrate s) of Just i -> x + (fi nwh * fi i) Nothing -> x -- cgit v1.2.3