aboutsummaryrefslogtreecommitdiffstats
path: root/DragPane.hs
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2007-10-08 16:38:01 +0200
committerAndrea Rossato <andrea.rossato@unibz.it>2007-10-08 16:38:01 +0200
commitebb82ecd692b72785f37f40dec415b07bdbb9c2f (patch)
treec9566d017ed1dccfdd8f8b4e4d5698f36a8216d6 /DragPane.hs
parent0303a3797e66fa31b4759a951ffb6f29dbb9cc57 (diff)
downloadXMonadContrib-ebb82ecd692b72785f37f40dec415b07bdbb9c2f.tar.gz
XMonadContrib-ebb82ecd692b72785f37f40dec415b07bdbb9c2f.tar.xz
XMonadContrib-ebb82ecd692b72785f37f40dec415b07bdbb9c2f.zip
DragPane: no need to deal with expose events in this simplified version
darcs-hash:20071008143801-32816-f0d4610216852a38a12b5fd01d0c45be54011de6.gz
Diffstat (limited to 'DragPane.hs')
-rw-r--r--DragPane.hs24
1 files changed, 8 insertions, 16 deletions
diff --git a/DragPane.hs b/DragPane.hs
index dc345fc..793f80c 100644
--- a/DragPane.hs
+++ b/DragPane.hs
@@ -59,7 +59,7 @@ dragPane :: DragType -> Double -> Double -> DragPane a
dragPane t x y = DragPane (I Nothing) t x y
data DragPane a =
- DragPane (Invisible Maybe (Window,Rectangle,Rectangle,Int)) DragType Double Double
+ DragPane (Invisible Maybe (Window,Rectangle,Int)) DragType Double Double
deriving ( Show, Read )
data DragType = Horizontal | Vertical deriving ( Show, Read )
@@ -73,7 +73,7 @@ data SetFrac = SetFrac Int Double deriving ( Show, Read, Eq, Typeable )
instance Message SetFrac
handleMess :: DragPane Window -> SomeMessage -> X (Maybe (DragPane Window))
-handleMess d@(DragPane mb@(I (Just (win,_,_,ident))) ty delta split) x
+handleMess d@(DragPane mb@(I (Just (win,_,ident))) ty delta split) x
| Just e <- fromMessage x :: Maybe Event = do handleEvent d e
return Nothing
| Just Hide <- fromMessage x = do hideWindow win
@@ -88,7 +88,7 @@ handleMess d@(DragPane mb@(I (Just (win,_,_,ident))) ty delta split) x
handleMess _ _ = return Nothing
handleEvent :: DragPane Window -> Event -> X ()
-handleEvent (DragPane (I (Just (win,_,r,ident))) ty _ _)
+handleEvent (DragPane (I (Just (win,r,ident))) ty _ _)
(ButtonEvent {ev_window = thisw, ev_subwindow = thisbw, ev_event_type = t })
| t == buttonPress && thisw == win || thisbw == win = do
mouseDrag (\ex ey -> do
@@ -97,12 +97,7 @@ handleEvent (DragPane (I (Just (win,_,r,ident))) ty _ _)
Horizontal -> (fromIntegral ey - (fromIntegral $ rect_y r))/(fromIntegral $ rect_height r)
sendMessage (SetFrac ident frac))
(return ())
-handleEvent (DragPane (I (Just (win,oret,_,_))) _ _ _)
- (ExposeEvent {ev_window = thisw })
- | thisw == win = do
- updateDragWin win oret
- return ()
-handleEvent _ _ = return ()
+handleEvent _ _ = return ()
doLay :: (Rectangle -> Rectangle) -> DragPane Window -> Rectangle -> W.Stack a -> X ([(a, Rectangle)], Maybe (DragPane a))
doLay mirror (DragPane mw ty delta split) r s = do
@@ -123,22 +118,19 @@ doLay mirror (DragPane mw ty delta split) r s = do
[] -> [(W.focus s, r)]
if length wrs > 1
then case mw of
- I (Just (w,_,_,ident)) -> do
+ I (Just (w,_,ident)) -> do
w' <- deleteWindow w >> newDragWin handr
- return (wrs, Just $ DragPane (I $ Just (w',r,r',ident)) ty delta split)
+ return (wrs, Just $ DragPane (I $ Just (w',r',ident)) ty delta split)
I Nothing -> do
w <- newDragWin handr
i <- io $ newUnique
- return (wrs, Just $ DragPane (I $ Just (w,r,r',hashUnique i)) ty delta split)
+ return (wrs, Just $ DragPane (I $ Just (w,r',hashUnique i)) ty delta split)
else return (wrs, Nothing)
newDragWin :: Rectangle -> X Window
-newDragWin r@(Rectangle _ _ wh ht) = do
+newDragWin r = do
let mask = Just $ exposureMask .|. buttonPressMask
w <- createNewWindow r mask handleColor
showWindow w
return w
-
-updateDragWin :: Window -> Rectangle -> X ()
-updateDragWin w (Rectangle _ _ wh ht) = return ()