aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Decoration.hs
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2008-02-12 17:53:06 +0100
committerAndrea Rossato <andrea.rossato@unibz.it>2008-02-12 17:53:06 +0100
commit4a59b66f3cde6cda9b89e7fa22a6ec74e3c1ec75 (patch)
tree16977579154be3a9c2c98fceb397403be2920a9d /XMonad/Layout/Decoration.hs
parentb1120e6eb7c6133d2d10ce516d4f503f80bd7b91 (diff)
downloadXMonadContrib-4a59b66f3cde6cda9b89e7fa22a6ec74e3c1ec75.tar.gz
XMonadContrib-4a59b66f3cde6cda9b89e7fa22a6ec74e3c1ec75.tar.xz
XMonadContrib-4a59b66f3cde6cda9b89e7fa22a6ec74e3c1ec75.zip
Decoration: remove mouse resize and more
- since mouse resize is not related to decoration, I removed the code from here. Mouse resize will be handled by a separated layout modifier (in a separated module) - now also stacked decoration will be removed (I separated insert_dwr from remove_stacked) darcs-hash:20080212165306-32816-1272c6e2d3aaaecb389a6e655f22d35c21a40168.gz
Diffstat (limited to 'XMonad/Layout/Decoration.hs')
-rw-r--r--XMonad/Layout/Decoration.hs32
1 files changed, 15 insertions, 17 deletions
diff --git a/XMonad/Layout/Decoration.hs b/XMonad/Layout/Decoration.hs
index 48fe6d4..c5b78ae 100644
--- a/XMonad/Layout/Decoration.hs
+++ b/XMonad/Layout/Decoration.hs
@@ -110,7 +110,6 @@ class (Read (ds a), Show (ds a)) => DecorationStyle ds a where
decorationEventHook :: ds a -> DecorationState -> Event -> X ()
decorationEventHook ds s e = do decorationMouseFocusHook ds s e
decorationMouseDragHook ds s e
- decorationMouseResizeHook ds s e
decorationMouseFocusHook :: ds a -> DecorationState -> Event -> X ()
decorationMouseFocusHook _ s e = handleMouseFocusDrag False s e
@@ -118,9 +117,6 @@ class (Read (ds a), Show (ds a)) => DecorationStyle ds a where
decorationMouseDragHook :: ds a -> DecorationState -> Event -> X ()
decorationMouseDragHook _ s e = handleMouseFocusDrag True s e
- decorationMouseResizeHook :: ds a -> DecorationState -> Event -> X ()
- decorationMouseResizeHook _ s e = handleMouseResize s e
-
pureDecoration :: ds a -> Dimension -> Dimension -> Rectangle
-> W.Stack a -> [(a,Rectangle)] -> (a,Rectangle) -> Maybe Rectangle
pureDecoration _ _ h _ _ _ (_,Rectangle x y w _) = Just $ Rectangle x y w h
@@ -148,20 +144,14 @@ instance (DecorationStyle ds Window, Shrinker s) => LayoutModifier (Decoration d
where
ws = map fst wrs
- del_dwrs = listFromList get_w notElem
get_w = fst . fst
get_ws = map get_w
+ del_dwrs = listFromList get_w notElem
find_dw i = fst . snd . flip (!!) i
todel d = filter (flip elem d . get_w)
toadd a = filter (flip elem a . fst )
- -- We drop any windows that are *precisely* stacked underneath
- -- another window: these must be intended to be tabbed!
- insert_dwr otherRs (((w,r),(dw,Just dr)):dwrs)
- | r `elem` otherRs = (dw,dr):insert_dwr otherRs dwrs
- | otherwise = (dw,dr):(w, shrink ds dr r):insert_dwr (r:otherRs) dwrs
- insert_dwr otherRs (((w,r),(_ ,Nothing)):dwrs) = (w,r):insert_dwr (r:otherRs) dwrs
- insert_dwr _ [] = []
+ decorate_first = length wrs == 1 && (not . decorateFirst $ ds)
resync _ [] = return []
resync d ((w,r):xs) = case w `elemIndex` get_ws d of
@@ -170,11 +160,22 @@ instance (DecorationStyle ds Window, Shrinker s) => LayoutModifier (Decoration d
return $ ((w,r),(find_dw i d, dr)) : dwrs
Nothing -> resync d xs
- decorate_first = length wrs == 1 && (not . decorateFirst $ ds)
+ -- We drop any windows that are *precisely* stacked underneath
+ -- another window: these must be intended to be tabbed!
+ remove_stacked rs ((w,r):xs)
+ | r `elem` rs = remove_stacked rs xs
+ | otherwise = (w,r) : remove_stacked (r:rs) xs
+ remove_stacked _ [] = []
+
+ insert_dwr ((w,r),(dw,Just dr)) xs = (dw,dr):(w, shrink ds dr r):xs
+ insert_dwr (x ,(_ ,Nothing)) xs = x:xs
+
+ dwrs_to_wrs = remove_stacked [] . foldr insert_dwr []
+
processState s = do ndwrs <- resync (decos s) wrs
showWindows (getDWs ndwrs)
updateDecos sh t (font s) ndwrs
- return (insert_dwr [] ndwrs, Just (Decoration (I (Just (s {decos = ndwrs}))) sh t ds))
+ return (dwrs_to_wrs ndwrs, Just (Decoration (I (Just (s {decos = ndwrs}))) sh t ds))
handleMess (Decoration (I (Just s@(DS {decos = dwrs}))) sh t ds) m
| Just e <- fromMessage m :: Maybe Event = do decorationEventHook ds s e
@@ -218,9 +219,6 @@ handleMouseFocusDrag b (DS dwrs _) ButtonEvent { ev_window = ew
sendMessage (SetGeometry rect)) (return ())
handleMouseFocusDrag _ _ _ = return ()
-handleMouseResize :: DecorationState -> Event -> X ()
-handleMouseResize _ _ = return ()
-
lookFor :: Window -> [(OrigWin,DecoWin)] -> Maybe (OrigWin,DecoWin)
lookFor w ((wr,(dw,dr)):dwrs) | w == dw = Just (wr,(dw,dr))
| otherwise = lookFor w dwrs