darcs patch: add decorations infrastructure

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.
David
Sat Jun 9 12:23:49 PDT 2007 David Roundy

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

On Sat, Jun 09, 2007 at 12:40:21PM -0700, Stefan O'Rear wrote:
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.
Actually this isn't needed. It can be handled just fine using a *real* toolkit out-of-process. Stefan

On Sat, Jun 09, 2007 at 12:46:59PM -0700, Stefan O'Rear wrote:
On Sat, Jun 09, 2007 at 12:40:21PM -0700, Stefan O'Rear wrote:
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.
Actually this isn't needed. It can be handled just fine using a *real* toolkit out-of-process.
On second thought, having toolkit functionality in the Xmonad core would be a Good Thing, since it would allow the core to remain agnostic of extension functionality such as external command sources. Stefan

On Sat, 09 Jun 2007 12:27:00 -0700
David Roundy
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.
David
Sat Jun 9 12:23:49 PDT 2007 David Roundy
* add decorations infrastructure
I think we should leverage the existing layout/message system as much as possible here. Proposed modifications: - instance Message XEvent - dispatch unhandled XEvents to layouts - add another message type: data ViewMsg = View | Hide -- send this message to layouts on workspace change - put modifyLayout in the X monad This should give us enough flexibility to do decorations inside layouts without polluting the core with decoration handling. Cheers, Spencer Janssen

On Sat, Jun 09, 2007 at 05:54:58PM -0500, Spencer Janssen wrote:
On Sat, 09 Jun 2007 12:27:00 -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.
David
Sat Jun 9 12:23:49 PDT 2007 David Roundy
* add decorations infrastructure I think we should leverage the existing layout/message system as much as possible here. Proposed modifications: - instance Message XEvent - dispatch unhandled XEvents to layouts - add another message type: data ViewMsg = View | Hide -- send this message to layouts on workspace change - put modifyLayout in the X monad
This does sound like a better approach.
This should give us enough flexibility to do decorations inside layouts without polluting the core with decoration handling.
That still doesn't give us any way to delete decorations when they are no longer needed. At a minimum we'd also need to send an event/message when we want to switch layouts. The user could always do this in his/her config file, but it'd be nicer for layout writers to not put this burden on their users, and to be able to rely on *always* getting notified when they are no longer in control of the screen (and thus need to clean up anything they've stuck on it). -- David Roundy http://www.darcs.net

sjanssen:
On Sat, 09 Jun 2007 12:27:00 -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.
David
Sat Jun 9 12:23:49 PDT 2007 David Roundy
* add decorations infrastructure I think we should leverage the existing layout/message system as much as possible here. Proposed modifications: - instance Message XEvent
Good.
- dispatch unhandled XEvents to layouts
Good.
- add another message type: data ViewMsg = View | Hide -- send this message to layouts on workspace change
Ok, what's the case here? that a layout has drawn something on the screen depending on the workspace, and won't know that its moved to a new workspace? Perhaps doLayout should take (Stack a, WorkspaceId) ?
- put modifyLayout in the X monad
Seems reasonable.
This should give us enough flexibility to do decorations inside layouts without polluting the core with decoration handling.
Souds good. -- Don

On Sun, Jun 10, 2007 at 01:31:17PM +1000, Donald Bruce Stewart wrote:
- add another message type: data ViewMsg = View | Hide -- send this message to layouts on workspace change
Ok, what's the case here? that a layout has drawn something on the screen depending on the workspace, and won't know that its moved to a new workspace?
The trouble is that when you switch layouts the old layout needs to know to clean its decorations up, or they just sit there on the screen for the new layout, which is pretty ugly.
Perhaps doLayout should take (Stack a, WorkspaceId) ?
Possibly, but I believe this is orthogonal. You need to give the "old" layout a chance to clean up, and a Hide message (I think I called it something else like ModifyWindows--sort of a stupid name) seems the simplest way to do this. -- David Roundy http://www.darcs.net
participants (4)
-
David Roundy
-
dons@cse.unsw.edu.au
-
Spencer Janssen
-
Stefan O'Rear