aboutsummaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorDavid Roundy <droundy@darcs.net>2007-06-10 18:36:51 +0200
committerDavid Roundy <droundy@darcs.net>2007-06-10 18:36:51 +0200
commit278468da3cd9e1952bc7c20a34601f2e824f80c7 (patch)
tree9e15a1932c8d064ed0afef61c1c992b2f2453143
parent35938e439ad3dc86b0e6a32437bbdea25371ee1f (diff)
downloadXMonadContrib-278468da3cd9e1952bc7c20a34601f2e824f80c7.tar.gz
XMonadContrib-278468da3cd9e1952bc7c20a34601f2e824f80c7.tar.xz
XMonadContrib-278468da3cd9e1952bc7c20a34601f2e824f80c7.zip
make Decoration draw the window initially.
We still don't respond to expose events. :( darcs-hash:20070610163651-72aca-9bbc33663ef50926bd60d0dcbe1974b9eddc058b.gz
-rw-r--r--Decoration.hs20
1 files changed, 13 insertions, 7 deletions
diff --git a/Decoration.hs b/Decoration.hs
index 0b399ad..1b3eea9 100644
--- a/Decoration.hs
+++ b/Decoration.hs
@@ -1,19 +1,17 @@
module XMonadContrib.Decoration ( newDecoration ) where
import qualified Data.Map as M
-
import Control.Monad.Reader ( asks )
import Control.Monad.State ( modify, gets )
-import Graphics.X11.Xlib ( Window, Rectangle(Rectangle), Pixel
- , createSimpleWindow, mapWindow, destroyWindow
- , buttonPress )
+import Graphics.X11.Xlib
import Graphics.X11.Xlib.Extras ( Event(AnyEvent,ButtonEvent), ev_subwindow, ev_event_type, ev_window )
import XMonad
import Operations ( ModifyWindows(ModifyWindows) )
import qualified StackSet as W
-newDecoration :: Rectangle -> Int -> Pixel -> Pixel -> X () -> X () -> X Window
+newDecoration :: Rectangle -> Int -> Pixel -> Pixel
+ -> (Display -> Window -> GC -> X ()) -> X () -> X Window
newDecoration (Rectangle x y w h) th fg bg draw click =
do d <- asks display
rt <- asks theRoot
@@ -21,7 +19,8 @@ newDecoration (Rectangle x y w h) th fg bg draw click =
Just (l,ls) <- M.lookup n `fmap` gets layouts
win <- io $ createSimpleWindow d rt x y w h (fromIntegral th) fg bg
io $ mapWindow d win
- let modml :: (SomeMessage -> X (Maybe Layout)) -> SomeMessage -> X (Maybe Layout)
+ let draw' = withGC win draw
+ modml :: (SomeMessage -> X (Maybe Layout)) -> SomeMessage -> X (Maybe Layout)
modml oldml m | Just ModifyWindows == fromMessage m = io (destroyWindow d win) >> oldml m
| Just e <- fromMessage m = handle_event e >> oldml m
| otherwise = fmap modl `fmap` oldml m
@@ -31,7 +30,14 @@ newDecoration (Rectangle x y w h) th fg bg draw click =
| t == buttonPress && thisw == win = click
handle_event (ButtonEvent {ev_window = thisw,ev_event_type = t})
| t == buttonPress && thisw == win = click
- handle_event (AnyEvent {ev_window = thisw}) | thisw == win = draw
+ handle_event (AnyEvent {ev_window = thisw}) | thisw == win = draw'
handle_event _ = return ()
+ draw'
modify $ \s -> s { layouts = M.insert n (modl l,ls) (layouts s) }
return win
+
+-- FIXME: withGC should use bracket (but can't, unless draw is an IO thing)
+withGC :: Drawable -> (Display -> Drawable -> GC -> X ()) -> X ()
+withGC w f = withDisplay $ \d -> do gc <- io $ createGC d w
+ f d w gc
+ io $ freeGC d gc