aboutsummaryrefslogtreecommitdiffstats
path: root/XMonad/Layout/Decoration.hs
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2008-02-08 08:35:14 +0100
committerAndrea Rossato <andrea.rossato@unibz.it>2008-02-08 08:35:14 +0100
commit08684f11ebcc50a30a6bd1d9cf5358cf8430d642 (patch)
tree36b6a53c2508c7569bf0d3d67ed401cf97b67558 /XMonad/Layout/Decoration.hs
parentb86f9938798858bbba6305fc68e2e27a946e4da0 (diff)
downloadXMonadContrib-08684f11ebcc50a30a6bd1d9cf5358cf8430d642.tar.gz
XMonadContrib-08684f11ebcc50a30a6bd1d9cf5358cf8430d642.tar.xz
XMonadContrib-08684f11ebcc50a30a6bd1d9cf5358cf8430d642.zip
Decoration: add a mouseEventHook methohd and move mouse button event there
darcs-hash:20080208073514-32816-9f8c9812e142c55a37a04ed9919b9eb76f0fedf5.gz
Diffstat (limited to 'XMonad/Layout/Decoration.hs')
-rw-r--r--XMonad/Layout/Decoration.hs17
1 files changed, 12 insertions, 5 deletions
diff --git a/XMonad/Layout/Decoration.hs b/XMonad/Layout/Decoration.hs
index 8ffcdc6..3323e37 100644
--- a/XMonad/Layout/Decoration.hs
+++ b/XMonad/Layout/Decoration.hs
@@ -105,6 +105,13 @@ class (Read (ds a), Show (ds a)) => DecorationStyle ds a where
shrink :: ds a -> Rectangle -> Rectangle -> Rectangle
shrink _ (Rectangle _ _ _ dh) (Rectangle x y w h) = Rectangle x (y + fi dh) w (h - dh)
+ mouseEventHook :: ds a -> DecorationState -> Event -> X ()
+ mouseEventHook _ (DS dwrs _) e
+ | ButtonEvent {ev_window = w,ev_event_type = ty} <- e,
+ ty == buttonPress,
+ Just ((mainw,_),_) <- lookFor w dwrs = focus mainw
+ mouseEventHook _ _ _ = return ()
+
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
@@ -158,8 +165,11 @@ instance (DecorationStyle ds Window, Shrinker s) => LayoutModifier (Decoration d
return (insert_dwr [] 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 = handleEvent sh t s e >> return Nothing
- | Just Hide <- fromMessage m = hideWindows (getDWs dwrs) >> return Nothing
+ | Just e <- fromMessage m :: Maybe Event = do mouseEventHook ds s e
+ handleEvent sh t s e
+ return Nothing
+ | Just Hide <- fromMessage m = do hideWindows (getDWs dwrs)
+ return Nothing
| Just (SetTheme nt) <- fromMessage m = do releaseResources s
return $ Just $ Decoration (I Nothing) sh nt ds
| Just ReleaseResources <- fromMessage m = do releaseResources s
@@ -178,9 +188,6 @@ handleEvent :: Shrinker s => s -> Theme -> DecorationState -> Event -> X ()
handleEvent sh t (DS dwrs fs) e
| PropertyEvent {ev_window = w} <- e, w `elem` (map (fst . fst) dwrs) = updateDecos sh t fs dwrs
| ExposeEvent {ev_window = w} <- e, w `elem` (map (fst . snd) dwrs) = updateDecos sh t fs dwrs
- | ButtonEvent {ev_window = w,ev_event_type = ty} <- e,
- ty == buttonPress,
- Just ((mainw,_),_) <- lookFor w dwrs = focus mainw
handleEvent _ _ _ _ = return ()
lookFor :: Window -> [(OrigWin,DecoWin)] -> Maybe (OrigWin,DecoWin)