aboutsummaryrefslogtreecommitdiffstats
path: root/NewTabbed.hs
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2007-09-26 13:40:56 +0200
committerAndrea Rossato <andrea.rossato@unibz.it>2007-09-26 13:40:56 +0200
commit97d3915692401b74d4aefc8e0e70a362251edc3f (patch)
treeb8332788829b9fd76c4b71374296f814fabf2c74 /NewTabbed.hs
parent80297df41556adc546f56a5e10e8871fcb73f410 (diff)
downloadXMonadContrib-97d3915692401b74d4aefc8e0e70a362251edc3f.tar.gz
XMonadContrib-97d3915692401b74d4aefc8e0e70a362251edc3f.tar.xz
XMonadContrib-97d3915692401b74d4aefc8e0e70a362251edc3f.zip
NewTabbed: we must check if the sceen rectangle changed
- Check if rectangle changed - removed orphan instances warnings - some code formatting darcs-hash:20070926114056-32816-82fecbb401a9b189de27199a5e528ec9849e19ea.gz
Diffstat (limited to 'NewTabbed.hs')
-rw-r--r--NewTabbed.hs9
1 files changed, 5 insertions, 4 deletions
diff --git a/NewTabbed.hs b/NewTabbed.hs
index 73d5a1b..05f296b 100644
--- a/NewTabbed.hs
+++ b/NewTabbed.hs
@@ -1,3 +1,4 @@
+{-# OPTIONS -fno-warn-orphans -fglasgow-exts #-}
-----------------------------------------------------------------------------
-- |
-- Module : XMonadContrib.Tabbed
@@ -95,7 +96,7 @@ data Tabbed a =
instance Layout Tabbed Window where
doLayout (Tabbed mst conf) = doLay mst conf
- handleMessage l m = modLay l m
+ handleMessage l m = modLay l m
instance Read FontStruct where
readsPrec _ _ = []
@@ -110,11 +111,11 @@ doLay mst conf sc@(Rectangle _ _ wid _) s@(W.Stack w _ _) = do
-- initialize state
st <- case mst of
Nothing -> initState conf sc ws
- Just ts -> if map snd (tabsWindows ts) == ws
+ Just ts -> if map snd (tabsWindows ts) == ws && scr ts == sc
then return ts
else do destroyTabs (map fst $ tabsWindows ts)
tws <- createTabs conf sc ws
- return (ts {tabsWindows = zip tws ws})
+ return (ts {scr = sc, tabsWindows = zip tws ws})
showTabs $ map fst $ tabsWindows st
mapM_ (updateTab conf (fontS st) width) $ tabsWindows st
return ([(w,shrink conf sc)], Just (Tabbed (Just st) conf))
@@ -150,7 +151,7 @@ handleEvent conf (TabState {tabsWindows = tws, scr = screen, fontS =
updateTab conf fs width (thisw, fromJust $ lookup thisw tws)
-- propertyNotify
| thisw `elem` (map snd tws) && t == propertyNotify = do
- let tabwin = (fst $ fromJust $ find (\x -> snd x == thisw) tws, thisw)
+ let tabwin = (fst $ fromJust $ find ((== thisw) . snd) tws, thisw)
updateTab conf fs width tabwin
where
width = rect_width screen`div` fromIntegral (length tws)