aboutsummaryrefslogtreecommitdiffstats
path: root/DragPane.hs
diff options
context:
space:
mode:
authorAndrea Rossato <andrea.rossato@unibz.it>2007-09-28 20:58:32 +0200
committerAndrea Rossato <andrea.rossato@unibz.it>2007-09-28 20:58:32 +0200
commit1ff0e1dd1f5550d3eaca04e1e5785d70ab29b64a (patch)
treee8ca6d3fe5f928c8c7d8a5d20193ed2512c004f7 /DragPane.hs
parentac0bb57a2d29624ad8abfefc2175621b313c6d87 (diff)
downloadXMonadContrib-1ff0e1dd1f5550d3eaca04e1e5785d70ab29b64a.tar.gz
XMonadContrib-1ff0e1dd1f5550d3eaca04e1e5785d70ab29b64a.tar.xz
XMonadContrib-1ff0e1dd1f5550d3eaca04e1e5785d70ab29b64a.zip
DragPane now uses Invisible
darcs-hash:20070928185832-32816-1912a8d1ad0b2d90b6be1ffe0afd0e3be591b207.gz
Diffstat (limited to 'DragPane.hs')
-rw-r--r--DragPane.hs19
1 files changed, 10 insertions, 9 deletions
diff --git a/DragPane.hs b/DragPane.hs
index 329a60c..2d5a68f 100644
--- a/DragPane.hs
+++ b/DragPane.hs
@@ -36,6 +36,7 @@ import Data.Unique
import Operations
import qualified StackSet as W
+import XMonadContrib.Invisible
-- $usage
--
@@ -54,10 +55,10 @@ handleColor :: String
handleColor = "#000000"
dragPane :: DragType -> Double -> Double -> DragPane a
-dragPane t x y = DragPane Nothing t x y
+dragPane t x y = DragPane (I Nothing) t x y
data DragPane a =
- DragPane (Maybe (Window,Rectangle,Int)) DragType Double Double
+ DragPane (Invisible Maybe (Window,Rectangle,Int)) DragType Double Double
deriving ( Show, Read )
data DragType = Horizontal | Vertical deriving ( Show, Read )
@@ -71,13 +72,13 @@ 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@(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 hideDragWin win
return $ Just (DragPane mb ty delta split)
| Just ReleaseResources <- fromMessage x = do destroyDragWin win
- return $ Just (DragPane Nothing ty delta split)
+ return $ Just (DragPane (I Nothing) ty delta split)
-- layout specific messages
| Just Shrink <- fromMessage x = return $ Just (DragPane mb ty delta (split - delta))
| Just Expand <- fromMessage x = return $ Just (DragPane mb ty delta (split + delta))
@@ -86,7 +87,7 @@ handleMess d@(DragPane mb@(Just (win,_,ident)) ty delta split) x
handleMess _ _ = return Nothing
handleEvent :: DragPane Window -> Event -> X ()
-handleEvent (DragPane (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
@@ -117,13 +118,13 @@ doLay mirror (DragPane mw ty delta split) r s = do
[] -> [(W.focus s, r)]
if length wrs > 1
then case mw of
- Just (w,_,ident) -> do
+ I (Just (w,_,ident)) -> do
w' <- updateDragWin w handlec handr
- return (wrs, Just $ DragPane (Just (w',r',ident)) ty delta split)
- Nothing -> do
+ return (wrs, Just $ DragPane (I $ Just (w',r',ident)) ty delta split)
+ I Nothing -> do
w <- newDragWin handlec handr
i <- io $ newUnique
- return (wrs, Just $ DragPane (Just (w,r',hashUnique i)) ty delta split)
+ return (wrs, Just $ DragPane (I $ Just (w,r',hashUnique i)) ty delta split)
else return (wrs, Nothing)