
9 Jun
2007
9 Jun
'07
3:40 p.m.
On Sat, Jun 09, 2007 at 12:27:00PM -0700, David Roundy wrote: > Hi all, > > Here's some infrastructure to allow layouts to define window decorations > such as tabs or title bars. I'm mostly sending it in to get comments. > I soon hope to have a crude tabbed layout using this. Cool! In the spirit of comments, I think I see a simpler and more general way to accomplish this. Expect a counterpatch shortly! Why restrict the core to *decorations*? This can be generalized: 1. Have a transientRestore :: [X ()] hook in the state, which is used by the decoration manager (a XMonadContrib module) to remove decorations. 2. Have a eventHandlers :: M.Map WindowId (Event -> X ()) which specifies what to do when other windows get events. This gives Xmonad the toolkit-like facilities to implement drawing, clicking, etc decorations. With this your decoration manager could be implemented in XMonadContrib. > Sat Jun 9 12:23:49 PDT 2007 David Roundy> * add decorations infrastructure > Content-Description: A darcs patch for your repository! > > New patches: > > [add decorations infrastructure > David Roundy **20070609192349] > < > > { > hunk ./Main.hs 66 > st = XState > { windowset = winset > , layouts = M.fromList [(w, safeLayouts) | w <- [0 .. W workspaces - 1]] > + , decorations = [] > , statusGaps = take (length xinesc) $ defaultGaps ++ repeat (0,0,0,0) > , xineScreens = xinesc > , mapped = S.empty > hunk ./Main.hs 186 > | t == buttonPress = do > isr <- isRoot w > if isr then whenJust (M.lookup (cleanMask (ev_state e), b) mouseBindings) ($ ev_subwindow e) > - else focus w > + else do withDecoration w clickDecoration > + focus w > -- If it's the root window, then it's something we > -- grabbed in grabButtons. Otherwise, it's click-to-focus. > > hunk ./Main.hs 228 > -- the root may have configured > handle (ConfigureEvent {ev_window = w}) = whenX (isRoot w) rescreen > > +handle (AnyEvent {ev_event_type = t, ev_window = w}) > + | t == expose = withDecoration w drawDecoration > + > handle _ = return () -- trace (eventName e) -- ignoring > hunk ./Operations.hs 127 > -- | windows. Modify the current window list with a pure function, and refresh > windows :: (WindowSet -> WindowSet) -> X () > windows f = do > + destroyDecorations > XState { windowset = old, layouts = fls, xineScreens = xinesc, statusGaps = gaps } <- get > let ws = f old > modify (\s -> s { windowset = ws }) > hunk ./Operations.hs 551 > applyMaxSizeHint (mw,mh) x@(w,h) = > if mw > 0 && mh > 0 then (min w mw,min h mh) else x > > +destroyDecorations :: X () > +destroyDecorations = do decs <- gets decorations > + modify $ \x -> x { decorations = [] } > + withDisplay $ \d -> forM_ decs (io . destroyWindow d . decorationWindow) > + > +addDecoration :: Decoration -> X () > +addDecoration dec = do modify $ \x -> x { decorations = dec : decorations x } > + withDisplay $ \d -> io $ mapWindow d (decorationWindow dec) > + > +withDecoration :: Window -> (Decoration -> X ()) -> X () > +withDecoration w f = do decs <- filter ((==w) . decorationWindow) `fmap` gets decorations > + case decs of > + (x:_) -> f x > + _ -> return () > + > hunk ./XMonad.hs 20 > > module XMonad ( > X, WindowSet, WorkspaceId(..), ScreenId(..), XState(..), XConf(..), Layout(..), > + Decoration, decorationWindow, drawDecoration, clickDecoration, newDecoration, > Typeable, Message, SomeMessage(..), fromMessage, atom_WM_PROTOCOLS, atom_WM_DELETE_WINDOW, > runX, io, withDisplay, withWindowSet, isRoot, spawn, restart, trace, whenJust, whenX, > atom_WM_STATE > hunk ./XMonad.hs 48 > , statusGaps :: ![(Int,Int,Int,Int)] -- ^ width of status bar on each screen > , mapped :: !(S.Set Window) -- ^ the Set of mapped windows > , waitingUnmap :: !(M.Map Window Int) -- ^ the number of expected UnmapEvents > + , decorations :: ![Decoration] -- ^ currently visible decorations > , layouts :: !(M.Map WorkspaceId (Layout, [Layout])) } > -- ^ mapping of workspaces to descriptions of their layouts > data XConf = XConf > hunk ./XMonad.hs 107 > atom_WM_DELETE_WINDOW = getAtom "WM_DELETE_WINDOW" > atom_WM_STATE = getAtom "WM_STATE" > > +------------------------------------------------------------------------ > +-- Decorations > + > +data Decoration = Decoration { decorationWindow :: Window > + , drawDecoration :: X () > + , clickDecoration :: X () } > + > +newDecoration :: Rectangle -> Int -> Pixel -> Pixel -> X Decoration > +newDecoration (Rectangle x y w h) th fg bg = > + withDisplay $ \d -> do rt <- asks theRoot > + win <- io $ createSimpleWindow d rt x y w h (fromIntegral th) fg bg > + return $ Decoration win (return ()) (return ()) > + > ------------------------------------------------------------------------ > -- Layout handling