1 /*  Part of XPCE --- The SWI-Prolog GUI toolkit
2 
3     Author:        Jan Wielemaker and Anjo Anjewierden
4     E-mail:        jan@swi.psy.uva.nl
5     WWW:           http://www.swi.psy.uva.nl/projects/xpce/
6     Copyright (c)  1985-2002, University of Amsterdam
7     All rights reserved.
8 
9     Redistribution and use in source and binary forms, with or without
10     modification, are permitted provided that the following conditions
11     are met:
12 
13     1. Redistributions of source code must retain the above copyright
14        notice, this list of conditions and the following disclaimer.
15 
16     2. Redistributions in binary form must reproduce the above copyright
17        notice, this list of conditions and the following disclaimer in
18        the documentation and/or other materials provided with the
19        distribution.
20 
21     THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
22     "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
23     LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
24     FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
25     COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
26     INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
27     BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
28     LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
29     CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
30     LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
31     ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
32     POSSIBILITY OF SUCH DAMAGE.
33 */
34 
35 #include <h/kernel.h>
36 #include <h/dialog.h>
37 
38 static status	uncreateWindow(PceWindow sw);
39 static status   tileWindow(PceWindow sw, TileObj t);
40 static status   updateScrollbarValuesWindow(PceWindow sw);
41 static status   UpdateScrollbarValuesWindow(PceWindow sw);
42 static status	visible_window(PceWindow sw, IArea a);
43 extern void	unlink_changes_data_window(PceWindow sw);
44 
45 
46 status
initialiseWindow(PceWindow sw,Name label,Size size,DisplayObj display)47 initialiseWindow(PceWindow sw, Name label, Size size, DisplayObj display)
48 { initialiseDevice((Device) sw);
49 
50   assign(sw, scroll_offset,	   newObject(ClassPoint, EAV));
51   assign(sw, input_focus,	   OFF);
52   assign(sw, has_pointer,	   OFF);
53   assign(sw, sensitive,		   ON);
54   assign(sw, bounding_box,	   newObject(ClassArea, EAV));
55   assign(sw, buffered_update,	   ON);
56   obtainClassVariablesObject(sw);
57 
58   if ( isDefault(size) )
59     TRY( size = getClassVariableValueObject(sw, NAME_size) );
60   setArea(sw->area, ZERO, ZERO, size->w, size->h);
61 
62   sw->changes_data = NULL;
63   sw->ws_ref = NULL;
64 
65   if ( notDefault(label) || notDefault(display) )
66     frameWindow(sw, newObject(ClassFrame, label, DEFAULT, display, EAV));
67 
68   succeed;
69 }
70 
71 
72 static PceWindow
getConvertWindow(Class class,Graphical gr)73 getConvertWindow(Class class, Graphical gr)
74 { answer(getWindowGraphical(gr));
75 }
76 
77 		 /*******************************
78 		 *	     SAVE-LOAD		*
79 		 *******************************/
80 
81 static status
storeWindow(PceWindow sw,FileObj file)82 storeWindow(PceWindow sw, FileObj file)
83 { return storeSlotsObject(sw, file);
84 }
85 
86 
87 static status
loadWindow(PceWindow sw,IOSTREAM * fd,ClassDef def)88 loadWindow(PceWindow sw, IOSTREAM *fd, ClassDef def)
89 { TRY(loadSlotsObject(sw, fd, def));
90 
91   sw->ws_ref = NULL;
92   if ( isNil(sw->has_pointer) )
93     assign(sw, has_pointer, OFF);
94 
95   succeed;
96 }
97 
98 		/********************************
99 		*    WINDOW-SYSTEM INTERFACE	*
100 		********************************/
101 
102 status
createdWindow(PceWindow sw)103 createdWindow(PceWindow sw)
104 { return ws_created_window(sw);
105 }
106 
107 
108 static status
uncreateWindow(PceWindow sw)109 uncreateWindow(PceWindow sw)
110 { DEBUG(NAME_window, Cprintf("uncreateWindow(%s)\n", pp(sw)));
111 
112   deleteChain(ChangedWindows, sw);
113   ws_uncreate_window(sw);
114 
115   succeed;
116 }
117 
118 
119 status
grabPointerWindow(PceWindow sw,BoolObj val)120 grabPointerWindow(PceWindow sw, BoolObj val)
121 { DEBUG(NAME_focus,
122 	Cprintf("FOCUS: grabPointerWindow(%s, %s)\n", pp(sw), pp(val)));
123 
124   ws_grab_pointer_window(sw, val);
125 
126   succeed;
127 }
128 
129 
130 status
grabKeyboardWindow(PceWindow sw,BoolObj val)131 grabKeyboardWindow(PceWindow sw, BoolObj val)
132 { ws_grab_keyboard_window(sw, val);
133 
134   succeed;
135 }
136 
137 
138 		/********************************
139 		*          DESTRUCTION		*
140 		********************************/
141 
142 static status
freeWindow(PceWindow sw)143 freeWindow(PceWindow sw)
144 { if ( notNil(sw->frame) )
145     return send(sw->frame, NAME_free, EAV);
146   else if ( notNil(sw->decoration) )
147     return send(sw->decoration, NAME_free, EAV);
148   else
149     return freeObject(sw);
150 }
151 
152 
153 static status
destroyWindow(PceWindow sw)154 destroyWindow(PceWindow sw)
155 { if ( notNil(sw->frame) )
156     return destroyVisual((VisualObj) sw->frame);
157   else if ( notNil(sw->decoration) )
158     return destroyVisual((VisualObj) sw->decoration);
159   else
160     return destroyVisual((VisualObj) sw);
161 }
162 
163 
164 status
unlinkWindow(PceWindow sw)165 unlinkWindow(PceWindow sw)
166 { assign(sw, displayed, OFF);		/* avoid updates */
167   unlinkedWindowEvent(sw);
168   uncreateWindow(sw);
169   unlink_changes_data_window(sw);
170   unlinkDevice((Device) sw);
171 
172   if ( notNil(sw->frame) )
173   { deleteChain(sw->frame->members, sw);
174     assign(sw, frame, NIL);
175   }
176 
177   succeed;
178 }
179 
180 		/********************************
181 		*           OPEN/CREATE		*
182 		********************************/
183 
184 static status
openWindow(PceWindow sw,Point pos,BoolObj normalise)185 openWindow(PceWindow sw, Point pos, BoolObj normalise)
186 { if ( send(sw, NAME_create, EAV) &&
187        send(getFrameWindow(sw, DEFAULT), NAME_open,
188 	    pos, DEFAULT, normalise, EAV) )
189   succeed;
190 
191   fail;
192 }
193 
194 
195 static status
openCenteredWindow(PceWindow sw,Point pos,BoolObj grab,Monitor mon)196 openCenteredWindow(PceWindow sw, Point pos, BoolObj grab, Monitor mon)
197 { if ( send(sw, NAME_create, EAV) &&
198        send(getFrameWindow(sw, DEFAULT), NAME_openCentered,
199 	    pos, grab, mon, EAV) )
200     succeed;
201 
202   fail;
203 }
204 
205 
206 static Any
getConfirmWindow(PceWindow sw,Point pos,BoolObj grab,BoolObj normalise)207 getConfirmWindow(PceWindow sw, Point pos, BoolObj grab, BoolObj normalise)
208 { TRY( send(sw, NAME_create, EAV) );
209 
210   answer(getConfirmFrame(getFrameWindow(sw, DEFAULT), pos, grab, normalise));
211 }
212 
213 
214 static Any
getConfirmCenteredWindow(PceWindow sw,Point pos,BoolObj grab,Monitor mon)215 getConfirmCenteredWindow(PceWindow sw, Point pos, BoolObj grab, Monitor mon)
216 { TRY( send(sw, NAME_create, EAV) );
217 
218   answer(getConfirmCenteredFrame(getFrameWindow(sw, DEFAULT),
219 				 pos, grab, mon));
220 }
221 
222 
223 static status
createWindow(PceWindow sw,PceWindow parent)224 createWindow(PceWindow sw, PceWindow parent)
225 { if ( createdWindow(sw) )		/* already done */
226     succeed;
227 
228   DEBUG(NAME_window, Cprintf("createWindow(%s, %s)\n", pp(sw), pp(parent)));
229 
230   if ( isDefault(parent) )		/* do my manager first */
231   { if ( notNil(sw->decoration) )
232     { if ( !createdWindow(sw->decoration) )
233 	return send(sw->decoration, NAME_create, EAV);
234       succeed;
235     } else
236     { if ( isNil(sw->frame) )
237 	frameWindow(sw, DEFAULT);
238       if ( !createdFrame(sw->frame) )
239 	return send(sw->frame, NAME_create, EAV);
240     }
241   } else
242   { if ( !createdWindow(parent) )
243       send(parent, NAME_create, EAV);
244   }
245 
246 					/* fix the default colours */
247   if ( notDefault(parent) )
248   { if ( isDefault(sw->colour) )
249       assign(sw, colour, parent->colour);
250     if ( isDefault(sw->background) )
251       assign(sw, background, parent->background);
252   } else
253   { DisplayObj d;
254 
255     if ( notNil(sw->frame) )
256       d = sw->frame->display;
257     else
258       d = CurrentDisplay(sw);
259 
260     if ( isDefault(sw->colour) )
261       assign(sw, colour, d->foreground);
262     if ( isDefault(sw->background) )
263       assign(sw, background, d->background);
264   }
265 
266   ws_create_window(sw, parent);
267   qadSendv(sw, NAME_resize, 0, NULL);
268 
269   addChain(ChangedWindows, sw);		/* force initial update */
270 
271   succeed;
272 }
273 
274 
275 static status
ComputeDesiredSizeWindow(PceWindow sw)276 ComputeDesiredSizeWindow(PceWindow sw)
277 { succeed;
278 }
279 
280 
281 		 /*******************************
282 		 *	   DECORATIONS		*
283 		 *******************************/
284 
285 static status
decorateWindow(PceWindow sw,Name how,Int lb,Int tb,Int rb,Int bb,PceWindow dw)286 decorateWindow(PceWindow sw, Name how, Int lb, Int tb, Int rb, Int bb,
287 	       PceWindow dw)
288 { if ( isDefault(how)) how= NAME_grow;
289   if ( isDefault(lb) ) lb = ZERO;
290   if ( isDefault(rb) ) rb = ZERO;
291   if ( isDefault(tb) ) tb = ZERO;
292   if ( isDefault(bb) ) bb = ZERO;
293   if ( isDefault(dw) ) dw = newObject(ClassWindow, EAV);
294 
295   if ( isDefault(dw->colour) )     assign(dw, colour, sw->colour);
296   if ( isDefault(dw->background) ) assign(dw, background, sw->background);
297 
298   ws_reassociate_ws_window(sw, dw);
299 
300   assign(dw, tile, sw->tile);
301   if ( instanceOfObject(dw->tile, ClassTile) )
302     assign(dw->tile, object, dw);
303   assign(sw, tile, NIL);
304 
305   if ( notNil(sw->frame) )
306   { replaceChain(sw->frame->members, sw, dw);
307     assign(dw, frame, sw->frame);
308     assign(sw, frame, NIL);
309   } else if ( notNil(sw->device) )
310   { replaceChain(sw->device->graphicals, sw, dw);
311     assign(dw, device, sw->device);
312     assign(sw, device, NIL);
313   }
314   assign(dw, displayed, sw->displayed);
315 
316   if ( how == NAME_grow )
317   { send(dw, NAME_set,
318 	 sub(sw->area->x, lb),
319 	 sub(sw->area->y, tb),
320 	 add(sw->area->w, add(lb, rb)),
321 	 add(sw->area->h, add(tb, bb)), EAV);
322     send(sw, NAME_set, lb, tb, EAV);
323   } else
324   { send(sw, NAME_set,
325 	 lb, tb,
326 	 sub(sw->area->w, add(lb, rb)),
327 	 sub(sw->area->h, add(tb, bb)), EAV);
328   }
329 
330   DeviceGraphical(sw, (Device) dw);
331   assign(sw, decoration, dw);
332 
333   succeed;
334 }
335 
336 
337 PceWindow				/* used in MSW binding */
userWindow(PceWindow sw)338 userWindow(PceWindow sw)
339 { if ( instanceOfObject(sw, ClassWindowDecorator) )
340   { WindowDecorator dw = (WindowDecorator)sw;
341 
342     answer(dw->window);
343   }
344 
345   answer(sw);
346 }
347 
348 
349 		/********************************
350 		*        GRAPHICAL ROLE		*
351 		********************************/
352 
353 status
updatePositionWindow(PceWindow sw)354 updatePositionWindow(PceWindow sw)
355 { PceWindow parent = getWindowGraphical((Graphical) sw->device);
356 
357   if ( parent && createdWindow(parent) &&
358        parent->displayed == ON &&
359        getIsDisplayedGraphical((Graphical)sw, (Device)parent) == ON )
360   { int ox, oy, x, y, w, h;
361     int pen = valInt(sw->pen);
362 
363     offsetDeviceGraphical(sw, &x, &y);
364     DEBUG(NAME_offset, Cprintf("x = %d, y = %d\n", x, y));
365     offset_window(parent, &ox, &oy);
366     DEBUG(NAME_offset, Cprintf("ox = %d, oy = %d\n", ox, oy));
367     x += valInt(sw->area->x) + ox;
368     y += valInt(sw->area->y) + oy;
369     w  = valInt(sw->area->w);
370     h  = valInt(sw->area->h);
371 
372     if ( !createdWindow(sw) )
373       TRY(send(sw, NAME_create, parent, EAV));
374 
375     ws_geometry_window(sw, x, y, w, h, pen);
376     UpdateScrollbarValuesWindow(sw);
377   } else
378   { uncreateWindow(sw);
379     assign(sw, displayed, ON);
380   }
381 
382   succeed;
383 }
384 
385 
386 static void
updatePositionSubWindowsDevice(Device dev)387 updatePositionSubWindowsDevice(Device dev)
388 { Cell cell;
389 
390   for_cell(cell, dev->graphicals)
391   { if ( instanceOfObject(cell->value, ClassWindow) )
392       updatePositionWindow(cell->value);
393     else if ( instanceOfObject(cell->value, ClassDevice) )
394       updatePositionSubWindowsDevice(cell->value);
395   }
396 }
397 
398 
399 
400 
401 static status
reparentWindow(PceWindow sw)402 reparentWindow(PceWindow sw)
403 { if ( !getWindowGraphical((Graphical) sw->device) )
404     uncreateWindow(sw);
405 
406   succeed;
407 }
408 
409 
410 static status
deviceWindow(PceWindow sw,Device dev)411 deviceWindow(PceWindow sw, Device dev)
412 { if ( notNil(dev) )
413   { if ( notNil(sw->frame) )
414       send(sw->frame, NAME_delete, sw, EAV);
415 
416     if ( notNil(sw->decoration) && dev != (Device) sw->decoration )
417       return DeviceGraphical(sw->decoration, dev);
418   }
419 
420   return deviceGraphical(sw, dev);
421 }
422 
423 
424 static status
displayedWindow(PceWindow sw,BoolObj val)425 displayedWindow(PceWindow sw, BoolObj val)
426 { displayedGraphical(sw, val);
427 
428   if ( notNil(sw->decoration) )
429     displayedWindow(sw->decoration, val);
430 
431   if ( val == ON )
432     addChain(ChangedWindows, sw);
433 
434   succeed;
435 }
436 
437 
438 status
resizeWindow(PceWindow sw)439 resizeWindow(PceWindow sw)
440 { if ( notNil(sw->resize_message) )
441     forwardReceiverCode(sw->resize_message, sw, sw, getSizeArea(sw->area), EAV);
442 
443   succeed;
444 }
445 
446 
447 static status
resizeMessageWindow(PceWindow sw,Code msg)448 resizeMessageWindow(PceWindow sw, Code msg)
449 { assign(sw, resize_message, msg);
450 
451   if ( createdWindow(sw) )
452     qadSendv(sw, NAME_resize, 0, NULL);
453 
454   succeed;
455 }
456 
457 
458 static Monitor
getMonitorWindow(PceWindow sw)459 getMonitorWindow(PceWindow sw)
460 { if ( isNil(sw->device) )
461   { DisplayObj d = getDisplayGraphical((Graphical)sw);
462 
463     if ( d )
464     { FrameObj fr;
465       int dx, dy;
466       struct area a;
467 
468       frame_offset_window(sw, &fr, &dx, &dy);
469       a = *fr->area;
470       a.x = toInt(valInt(a.x)+dx);
471       a.y = toInt(valInt(a.y)+dy);
472 
473       answer(getMonitorDisplay(d, &a));
474     }
475 
476     fail;
477   }
478 
479   return getMonitorGraphical((Graphical)sw);
480 }
481 
482 
483 		/********************************
484 		*           COMPUTING		*
485 		********************************/
486 
487 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
488 offset_window(sw,  x, y) computes the offset  of the coordinate system
489 of the  window  as a device,  relative   to the X-window's  coordinate
490 system.
491 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
492 
493 void
offset_window(PceWindow sw,int * x,int * y)494 offset_window(PceWindow sw, int *x, int *y)
495 { *x  = valInt(sw->scroll_offset->x);
496   *y  = valInt(sw->scroll_offset->y);
497 }
498 
499 
500 void
compute_window(PceWindow sw,int * x,int * y,int * w,int * h)501 compute_window(PceWindow sw, int *x, int *y, int *w, int *h)
502 { *x  = 0;
503   *y  = 0;
504   *w  = valInt(sw->area->w);
505   *h  = valInt(sw->area->h);
506 }
507 
508 
509 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
510 frame_offset_window(window|frame, frame *, int *x, int *y)
511     Determine the frame of the object and the relative position in this
512     frame.  Used for computing event-offsets.
513 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
514 
515 status
frame_offset_window(Any obj,FrameObj * fr,int * X,int * Y)516 frame_offset_window(Any obj, FrameObj *fr, int *X, int *Y)
517 { if ( instanceOfObject(obj, ClassFrame) )
518   { *fr = obj;
519     *X = 0; *Y = 0;
520     succeed;
521   } else
522   { int x = 0, y = 0;
523     PceWindow w = obj;
524 
525     while(isNil(w->frame))
526     { if ( notNil(w->device) )
527       { PceWindow w2 = DEFAULT;
528 	Int ox, oy;
529 
530 	get_absolute_xy_graphical((Graphical)w, (Device *)&w2, &ox, &oy);
531 	if ( instanceOfObject(w2, ClassWindow) )
532 	{ int ox2, oy2;
533 
534 	  offset_window(w2, &ox2, &oy2);
535 	  x += valInt(ox) + ox2;
536 	  y += valInt(oy) + oy2;
537 
538 	  w = w2;
539 	  continue;
540 	}
541       }
542 
543       fail;
544     }
545 
546     x += valInt(w->area->x);
547     y += valInt(w->area->y);
548 
549     *fr = w->frame, *X = x, *Y = y;
550     DEBUG(NAME_position,
551 	  Cprintf("frame_offset_window(%s) --> fr = %s, offset = %d,%d\n",
552 		  pp(obj), pp(*fr), x, y));
553 
554     succeed;
555   }
556 }
557 
558 
559 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
560 Determine the offset between a window and an arbitrary other window or
561 frame.  Used for event-position computations.
562 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
563 
564 void
offset_windows(PceWindow w1,Any w2,int * X,int * Y)565 offset_windows(PceWindow w1, Any w2, int *X, int *Y)
566 { FrameObj fr1, fr2;
567   int ox1, oy1, ox2, oy2;
568 
569   if ( w1 == w2 || nonObject(w1) || nonObject(w2) )
570   { *X = *Y = 0;
571   } else if ( frame_offset_window(w1, &fr1, &ox1, &oy1) &&
572 	      frame_offset_window(w2, &fr2, &ox2, &oy2) )
573   { if ( fr1 == fr2 )
574     { *X = ox1 - ox2;
575       *Y = oy1 - oy2;
576     } else
577     { Area a1 = fr1->area;
578       Area a2 = fr2->area;
579 
580       *X = (ox1 + valInt(a1->x)) - (ox2 + valInt(a2->x));
581       *Y = (oy1 + valInt(a1->y)) - (oy2 + valInt(a2->y));
582     }
583   } else				/* subwindows */
584   { Cprintf("offset_windows(%s, %s) ???\n", pp(w1), pp(w2));
585     *X = *Y = 0;
586   }
587 }
588 
589 
590 		/********************************
591 		*        EVENT HANDLING		*
592 		********************************/
593 
594 int
is_service_window(PceWindow sw)595 is_service_window(PceWindow sw)
596 { Application app = getApplicationGraphical((Graphical)sw);
597 
598   DEBUG(NAME_service, Cprintf("Event on %s app=%s\n", pp(sw), pp(app)));
599 
600   return (app && app->kind == NAME_service ? PCE_EXEC_SERVICE
601 					   : PCE_EXEC_USER);
602 }
603 
604 
605 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
606 Support for `display->inspect_handler'.  The naming of this is a bit old
607 fashioned.  Checks whether there is a handler   in the chain that may be
608 capable of handling the event before doing anything.
609 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
610 
611 static status
inspectWindow(PceWindow sw,EventObj ev)612 inspectWindow(PceWindow sw, EventObj ev)
613 { DisplayObj d = getDisplayGraphical((Graphical)sw);
614 
615   if ( d )
616   { Cell cell;
617 
618     for_cell(cell, d->inspect_handlers)
619     { Handler h = cell->value;
620 
621       if ( isAEvent(ev, h->event) )
622 	return inspectDevice((Device) sw, ev);
623     }
624   }
625 
626   DEBUG(NAME_inspect, Cprintf("inspectWindow(%s, %s) failed\n",
627 			      pp(sw), pp(ev->id)));
628 
629   fail;
630 }
631 
632 
633 status
postEventWindow(PceWindow sw,EventObj ev)634 postEventWindow(PceWindow sw, EventObj ev)
635 { int rval = FAIL;
636   EventObj old_event;
637 
638   if ( sw->current_event == ev )
639     fail;				/* I don't want loops */
640 
641   old_event = sw->current_event;
642   addCodeReference(old_event);
643   assign(sw, current_event, ev);
644 
645   if ( isAEvent(ev, NAME_areaEnter) )
646   { FrameObj fr = getFrameWindow(sw, DEFAULT);
647 
648     if ( fr && notNil(fr) &&
649 	 !getHyperedObject(fr, NAME_keyboardFocus, DEFAULT) )
650       send(fr, NAME_inputWindow, sw, EAV);
651     send(sw, NAME_hasPointer, ON, EAV);
652   } else if ( isAEvent(ev, NAME_areaExit) )
653     send(sw, NAME_hasPointer, OFF, EAV);
654 
655   if ( inspectWindow(sw, ev) )
656     goto out;
657 
658   if ( isDownEvent(ev) && sw->input_focus == OFF )
659     send(getFrameWindow(sw, DEFAULT), NAME_keyboardFocus, sw, EAV);
660 
661   if ( isAEvent(ev, NAME_keyboard) )
662   { PceWindow iw;
663     FrameObj fr = getFrameWindow(sw, DEFAULT);
664 
665     if ( notNil(fr) &&
666 	 (iw = getKeyboardFocusFrame(fr)) &&
667 	 iw != sw )
668     { rval = eventFrame(fr, ev);
669       goto out;
670     }
671 
672     if ( notNil(sw->keyboard_focus) )
673     { rval = postEvent(ev, sw->keyboard_focus, DEFAULT);
674       goto out;
675     }
676   }
677 
678   if ( notNil(sw->focus) )
679   { if ( sw->focus == (Graphical) sw && isNil(sw->focus_recogniser) )
680       rval = send(sw, NAME_event, ev, EAV);
681     else
682     { DEBUG(NAME_focus,
683 	    Cprintf("FOCUS: Directing focussed %s event to %s\n",
684 		    pp(ev->id),
685 		    isNil(sw->focus_recogniser) ? pp(sw->focus)
686 						: pp(sw->focus_recogniser)));
687 
688       rval = postEvent(ev, sw->focus,
689 		       isNil(sw->focus_recogniser) ? DEFAULT
690 						   : sw->focus_recogniser);
691     }
692 
693     if ( isFreedObj(sw) )
694       return rval;
695 
696     if ( isUpEvent(ev) &&
697 	(isDefault(sw->focus_button) ||
698 	 getButtonEvent(ev) == sw->focus_button) )
699       focusWindow(sw, NIL, NIL, NIL, NIL);
700 
701     goto out;
702   }
703 
704   if ( sw->focus != (Graphical) sw || notNil(sw->focus_recogniser) )
705   { rval = send(sw, NAME_event, ev, EAV);
706   }
707 
708   if ( !rval )
709   { ScrollBar sb;
710     Any obj;
711 
712     if ( hasGetMethodObject(sw, NAME_verticalScrollbar) &&
713 	 (sb = get(sw, NAME_verticalScrollbar, EAV)) )
714       obj = sb->object;
715     else
716       obj = sw;
717 
718     rval = mapWheelMouseEvent(ev, obj);
719   }
720 
721   if ( !rval && isDownEvent(ev) )
722     rval = postEvent(ev, (Graphical) sw, popupGesture());
723 
724 out:
725   if ( isFreedObj(sw) )
726     goto destroyed;
727   if ( rval == FAIL && isAEvent(ev, NAME_keyboard) )
728   { if ( (rval = send(sw, NAME_typed, ev, ON, EAV)) )
729       goto out;
730   }
731 
732   updateCursorWindow(sw);
733 
734   assign(sw, current_event, old_event);
735 destroyed:
736   delCodeReference(old_event);
737 
738   return rval;
739 }
740 
741 
742 status
typedWindow(PceWindow sw,EventId id,BoolObj delegate)743 typedWindow(PceWindow sw, EventId id, BoolObj delegate)
744 { Name key = characterName(id);
745   Graphical gr;
746 
747   for_chain(sw->graphicals, gr,
748 	    if ( send(gr, NAME_key, key, EAV) )
749 	      succeed);
750 
751   if ( delegate == ON )
752    { if ( notNil(sw->frame) )
753        return send(sw->frame, NAME_typed, id, EAV);
754      else if ( notNil(sw->device) &&
755 	       (sw = getWindowGraphical((Graphical)(sw->device))) )
756        return send(sw, NAME_typed, id, delegate, EAV);
757    }
758 
759   fail;
760 }
761 
762 		/********************************
763 		*             FOCUS		*
764 		********************************/
765 
766 status
inputFocusWindow(PceWindow sw,BoolObj val)767 inputFocusWindow(PceWindow sw, BoolObj val)
768 { DEBUG(NAME_keyboard, Cprintf("inputFocusWindow(%s, %s)\n", pp(sw), pp(val)));
769 
770   if ( sw->input_focus != val )
771   { assign(sw, input_focus, val);
772 
773     if ( notNil(sw->keyboard_focus) )
774       generateEventGraphical(sw->keyboard_focus,
775 			     val == ON ? NAME_activateKeyboardFocus
776 				       : NAME_deactivateKeyboardFocus);
777   }
778 
779   if ( instanceOfObject(sw, ClassWindowDecorator) )
780   { WindowDecorator dw = (WindowDecorator)sw;
781 
782     sw = dw->window;
783     inputFocusWindow(sw, val);
784   }
785 
786   succeed;
787 }
788 
789 
790 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
791 Should we fetch the keyboard focus  of   our  frame? For keyboard driven
792 operation, this appears necessary. Otherwise, I don't know.
793 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
794 
795 status
keyboardFocusWindow(PceWindow sw,Graphical gr)796 keyboardFocusWindow(PceWindow sw, Graphical gr)
797 { if ( !isNil(gr) && sw->input_focus == OFF )
798   { FrameObj fr = getFrameWindow(sw, OFF);
799 
800     if ( fr )
801       send(fr, NAME_keyboardFocus, sw, EAV);
802 
803   }
804 
805   if ( sw->keyboard_focus != gr )
806   { Button defb;
807 
808     if ( notNil(sw->keyboard_focus) )
809       generateEventGraphical(sw->keyboard_focus, NAME_releaseKeyboardFocus);
810 
811     if ( instanceOfObject(gr, ClassButton) !=
812 	 instanceOfObject(sw->keyboard_focus, ClassButton) &&
813 	 (defb = getDefaultButtonDevice((Device)sw)) &&
814 	 (defb->look == NAME_motif || defb->look == NAME_gtk) )
815       changedDialogItem(defb);
816 
817     assign(sw, keyboard_focus, gr);
818 
819     if ( notNil(gr) )
820       generateEventGraphical(gr,
821 			     sw->input_focus == ON ? NAME_activateKeyboardFocus
822 						   : NAME_obtainKeyboardFocus);  }
823 
824   succeed;
825 }
826 
827 
828 status
focusWindow(PceWindow sw,Graphical gr,Recogniser recogniser,CursorObj cursor,Name button)829 focusWindow(PceWindow sw, Graphical gr, Recogniser recogniser,
830 	    CursorObj cursor, Name button)
831 { DEBUG(NAME_focus,
832 	Cprintf("FOCUS: focusWindow(%s, %s, %s, %s, %s)\n",
833 		pp(sw), pp(gr), pp(recogniser), pp(cursor), pp(button)));
834 
835   if ( isNil(gr) )
836   { if ( notNil(sw->focus) )
837       generateEventGraphical(sw->focus, NAME_releaseFocus);
838 
839     assign(sw, focus, NIL);
840     assign(sw, focus_recogniser, NIL);
841     assign(sw, focus_cursor, NIL);
842     assign(sw, focus_button, NIL);
843     assign(sw, focus_event, NIL);
844   } else
845   { if ( sw->focus != gr )
846     { if ( notNil(sw->focus) )
847 	generateEventGraphical(sw->focus, NAME_releaseFocus);
848       assign(sw, focus, gr);
849       generateEventGraphical(sw->focus, NAME_obtainFocus);
850     }
851     assign(sw, focus_recogniser, isDefault(recogniser) ? NIL : recogniser);
852     if ( notDefault(cursor) )
853       assign(sw, focus_cursor, cursor);
854     if ( isDefault(button) &&
855 	 notNil(sw->current_event) && isDownEvent(sw->current_event) )
856       assign(sw, focus_button, getButtonEvent(sw->current_event));
857     else
858       assign(sw, focus_button, button);
859     assign(sw, focus_event, sw->current_event);
860   }
861 
862   succeed;
863 }
864 
865 		/********************************
866 		*           COMPUTE		*
867 		********************************/
868 
869 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
870 Hacky: the bounding box of  a  device   is  <-area,  while a window uses
871 <-bounding_box (the area is the  area  in   its  role  as  a graphical).
872 Switches the two temporary to  allow  for   using  the  same  methods of
873 computation!?  Note  that   just   passing    an   extra   argument   to
874 updateBoundingBoxDevice() doesn't help as the   interface  to the public
875 method `layout_manager->compute_bounding_box' would have to change too.
876 
877 Better one dirty hack than a lot of only slightly better ones ...
878 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
879 
880 static status
computeBoundingBoxWindow(PceWindow sw)881 computeBoundingBoxWindow(PceWindow sw)
882 { if ( sw->badBoundingBox == ON )
883   { Int od[4];				/* ax, ay, aw, ah */
884     status changed;
885     Area a = sw->area;
886 
887     sw->area = sw->bounding_box;
888     changed = updateBoundingBoxDevice((Device)sw, od);
889     sw->area = a;
890     if ( changed )
891       qadSendv(sw, NAME_changedUnion, 4, od);
892 
893     assign(sw, badBoundingBox, OFF);
894   }
895 
896   succeed;
897 }
898 
899 
900 status
computeWindow(PceWindow sw)901 computeWindow(PceWindow sw)
902 { if ( notNil(sw->request_compute) )
903   { computeGraphicalsDevice((Device) sw);
904     computeLayoutDevice((Device) sw);
905     computeBoundingBoxWindow(sw);
906 
907     assign(sw, request_compute, NIL);
908   }
909 
910   succeed;
911 }
912 
913 		/********************************
914 		*            REDRAW		*
915 		********************************/
916 
917 
918 static void
union_iarea(IArea c,IArea a,IArea b)919 union_iarea(IArea c, IArea a, IArea b)
920 { int cx, cy, cw, ch;
921 
922   cx = min(a->x, b->x);
923   cy = min(a->y, b->y);
924   cw = max(a->x+a->w, b->x+b->w) - cx;
925   ch = max(a->y+a->h, b->y+b->h) - cy;
926 
927   c->x = cx; c->y = cy; c->w = cw; c->h = ch;
928 }
929 
930 
931 static status
inside_iarea(IArea a,IArea b)932 inside_iarea(IArea a, IArea b)
933 { if ( b->x >= a->x && b->x + b->w <= a->x + a->w &&
934        b->y >= a->y && b->y + b->h <= a->y + a->h )
935     succeed;
936 
937   fail;
938 }
939 
940 
941 static status
intersect_iarea(IArea a,IArea b)942 intersect_iarea(IArea a, IArea b)	/* shrink a with b; fail of empty */
943 { int x, y, w, h;
944 
945   x = (a->x > b->x ? a->x : b->x);
946   y = (a->y > b->y ? a->y : b->y);
947   w = (a->x + a->w < b->x + b->w ? a->x + a->w : b->x + b->w) - x;
948   h = (a->y + a->h < b->y + b->h ? a->y + a->h : b->y + b->h) - y;
949 
950   if ( w < 0 || h < 0 )
951     fail;
952 
953   a->x = x;
954   a->y = y;
955   a->w = w;
956   a->h = h;
957 
958   succeed;
959 }
960 
961 
962 
963 #ifdef O_CHDEBUG
964 #define CHDEBUG(s, g) DEBUG(s, g)
965 #else
966 #define CHDEBUG(s, g)
967 #endif
968 
969 void
changed_window(PceWindow sw,int x,int y,int w,int h,int clear)970 changed_window(PceWindow sw, int x, int y, int w, int h, int clear)
971 { UpdateArea a;
972   UpdateArea best = NULL;
973   iarea new;
974   int na;
975   int ok = 10;				/* max badness */
976 
977   NormaliseArea(x, y, w, h);
978   if ( w == 0 || h == 0 )
979     return;
980   CHDEBUG(NAME_changesData,
981 	Cprintf("changed_window(%s, %d, %d, %d, %d, %sclear)\n",
982 		pp(sw), x, y, w, h, clear ? "" : "no "));
983   new.x = x; new.y = y; new.w = w; new.h = h;
984   na = new.w * new.h;
985 
986   for(a=sw->changes_data; a; a = a->next)
987   { CHDEBUG(NAME_changesData,
988 	  { iarea *A = &a->area;
989 	    Cprintf("\tChecking with %d %d %d %d %sclear\n",
990 		    A->x, A->y, A->w, A->h, a->clear ? "" : "no ");
991 	  });
992 
993     if ( inside_iarea(&a->area, &new) )
994     { CHDEBUG(NAME_changesData,
995 	    Cprintf("\t\tInside changed area; discarded\n"));
996       return;				/* perfect */
997     } else if ( inside_iarea(&new, &a->area) )
998     { a->area  = new;
999       a->clear = clear;
1000       a->size  = na;
1001 
1002       CHDEBUG(NAME_changesData,
1003 	    Cprintf("\t\tOutside changed area; replaced\n"));
1004       return;
1005     } else if ( clear == a->clear )
1006     { iarea u;
1007       int ua, aa;
1008       int nok;
1009 
1010       union_iarea(&u, &a->area, &new);
1011       ua  = u.w * u.h;
1012       aa  = a->size;
1013       nok = (10 * (ua - (aa + na))) / (aa+na);
1014       if ( nok < ok )
1015       { ok = nok;
1016 	best = a;
1017       }
1018     }
1019   }
1020 
1021   if ( best )
1022   { CHDEBUG(NAME_changesData,
1023 	  { iarea *a = &best->area;
1024 	    Cprintf("\tCombined with %d %d %d %d --> ",
1025 		    a->x, a->y, a->w, a->h);
1026 	  });
1027 
1028     union_iarea(&best->area, &best->area, &new);
1029     CHDEBUG(NAME_changesData,
1030 	  { iarea *a = &best->area;
1031 	    Cprintf("%d %d %d %d\n", a->x, a->y, a->w, a->h);
1032 	  });
1033     if ( clear )
1034       best->clear = clear;
1035   } else
1036   { a =	alloc(sizeof(struct update_area));
1037 
1038     a->area    = new;
1039     a->clear   = clear;
1040     a->deleted = FALSE;
1041     a->size    = na;
1042     a->next    = sw->changes_data;
1043     sw->changes_data = a;
1044   }
1045 }
1046 
1047 
1048 void
unlink_changes_data_window(PceWindow sw)1049 unlink_changes_data_window(PceWindow sw)
1050 { UpdateArea a, b;
1051 
1052   a = sw->changes_data;
1053   sw->changes_data = NULL;
1054 
1055   for(; a; a = b)
1056   { b = a->next;
1057     unalloc(sizeof(struct update_area), a);
1058   }
1059 
1060   deleteChain(ChangedWindows, sw);
1061 }
1062 
1063 
1064 
1065 static void
combine_changes_window(PceWindow sw)1066 combine_changes_window(PceWindow sw)
1067 { UpdateArea a, b;
1068 
1069   for(a = sw->changes_data; a; a = a->next)
1070   { if ( !a->deleted )
1071     { for(b = sw->changes_data; b; b = b->next)
1072       { if ( !b->deleted && b != a &&
1073 	     inside_iarea(&a->area, &b->area) ) /* B is in A */
1074 	  b->deleted = TRUE;
1075       }
1076     }
1077   }
1078 }
1079 
1080 
1081 
1082 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1083 Redraw an area of the picture due to an exposure or resize.  The area is
1084 given in the coordinate system of the widget realizing the picture.
1085 
1086 WIN32_GRAPHICS note: this function is   called both from resize/exposure
1087 (in the X11 version) and from global  changes to the window that require
1088 it to be repainted entirely. In the  Windows version, the first bypasses
1089 this function, so we just trap the latter  to cause the entire window to
1090 be repainted.
1091 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
1092 
1093 status
redrawWindow(PceWindow sw,Area a)1094 redrawWindow(PceWindow sw, Area a)
1095 {
1096 #ifdef WIN32_GRAPHICS
1097   ws_invalidate_window(sw, DEFAULT);
1098 #else
1099   int ox, oy, dw, dh;
1100   int tmp = FALSE;
1101   iarea ia;
1102 
1103   if ( sw->displayed == OFF || !createdWindow(sw) )
1104     succeed;
1105 
1106   compute_window(sw, &ox, &oy, &dw, &dh);
1107 
1108   if ( isDefault(a) )
1109   { ia.x = 0;
1110     ia.y = 0;
1111     ia.w = valInt(sw->area->w);
1112     ia.h = valInt(sw->area->h);
1113   } else
1114   { ia.x = valInt(a->x);
1115     ia.y = valInt(a->y);
1116     ia.w = valInt(a->w);
1117     ia.h = valInt(a->h);
1118   }
1119 
1120   DEBUG(NAME_redraw, Cprintf("redrawWindow: w=%d, h=%d\n",
1121 			     valInt(sw->area->w),
1122 			     valInt(sw->area->h)));
1123 
1124   ox += valInt(sw->scroll_offset->x);
1125   oy += valInt(sw->scroll_offset->y);
1126 
1127   ia.x -= ox;
1128   ia.y -= oy;
1129 
1130   RedrawAreaWindow(sw, &ia, TRUE);	/* clear */
1131 
1132   if ( tmp )
1133     considerPreserveObject(a);
1134 #endif
1135 
1136   succeed;
1137 }
1138 
1139 
1140 status
RedrawWindow(PceWindow sw)1141 RedrawWindow(PceWindow sw)
1142 { DEBUG(NAME_window, Cprintf("Redrawing %s\n", pp(sw)));
1143 
1144   if ( sw->displayed == ON && createdWindow(sw) )
1145   { UpdateArea a, b;
1146     AnswerMark mark;
1147     iarea visible;
1148 
1149     if ( ws_delayed_redraw_window(sw) )
1150     { deleteChain(ChangedWindows, sw);
1151       DEBUG(NAME_window, Cprintf("\tForwarded to owner thread\n"));
1152       succeed;
1153     }
1154 
1155     markAnswerStack(mark);
1156 
1157     ComputeGraphical(sw);
1158     combine_changes_window(sw);
1159     visible_window(sw, &visible);
1160 
1161     a = sw->changes_data;
1162     sw->changes_data = NULL;		/* if we crash, data will be fine! */
1163 					/* (only some bytes lost) */
1164 
1165 
1166     DEBUG(NAME_changesData, Cprintf("%s:\n", pp(sw)));
1167     for(; a; a = b)
1168     { b = a->next;
1169       if ( !a->deleted && intersect_iarea(&a->area, &visible) )
1170       { DEBUG(NAME_changesData,
1171 	      Cprintf("\tUpdate %d %d %d %d (%s)\n",
1172 		      a->area.x, a->area.y, a->area.w, a->area.h,
1173 		      a->clear ? "clear" : "no clear"));
1174 #ifdef WIN32_GRAPHICS
1175         ws_redraw_window(sw, &a->area, a->clear);
1176 #else
1177 	RedrawAreaWindow(sw, &a->area, a->clear);
1178 #endif
1179       }
1180       unalloc(sizeof(struct update_area), a);
1181     }
1182 
1183     rewindAnswerStack(mark, NIL);
1184   }
1185 
1186   deleteChain(ChangedWindows, sw);
1187 
1188   succeed;
1189 }
1190 
1191 
1192 status
RedrawAreaWindow(PceWindow sw,IArea a,int clear)1193 RedrawAreaWindow(PceWindow sw, IArea a, int clear)
1194 { static Area oa = NULL;		/* Object Area */
1195 
1196   if ( sw->displayed == OFF || !createdWindow(sw) )
1197     succeed;
1198 
1199   if ( a->w != 0 && a->h != 0 )
1200   { int ox, oy, dw, dh;
1201     AnswerMark mark;
1202 
1203     markAnswerStack(mark);
1204 
1205     if ( !oa )
1206     { oa = newObject(ClassArea, EAV);
1207       protectObject(oa);
1208     }
1209 
1210     compute_window(sw, &ox, &oy, &dw, &dh);
1211     ox += valInt(sw->scroll_offset->x);
1212     oy += valInt(sw->scroll_offset->y);
1213 
1214     d_offset(ox, oy);
1215     if ( d_window(sw, a->x, a->y, a->w, a->h, clear, TRUE) )
1216     { assign(oa, x, toInt(a->x));
1217       assign(oa, y, toInt(a->y));
1218       assign(oa, w, toInt(a->w));
1219       assign(oa, h, toInt(a->h));
1220 
1221       qadSendv(sw, NAME_RedrawArea, 1, (Any *)&oa);
1222 
1223       d_done();
1224     }
1225     rewindAnswerStack(mark, NIL);
1226   }
1227 
1228   succeed;
1229 }
1230 
1231 
1232 static status
redrawAreaWindow(PceWindow sw,Area a)1233 redrawAreaWindow(PceWindow sw, Area a)
1234 { Cell cell;
1235 
1236   if ( notNil(sw->layout_manager) )
1237       qadSendv(sw->layout_manager, NAME_redrawBackground, 1, (Any*)&a);
1238 
1239   for_cell(cell, sw->graphicals)
1240     RedrawArea(cell->value, a);
1241 
1242   if ( notNil(sw->layout_manager) )
1243       qadSendv(sw->layout_manager, NAME_redrawForeground, 1, (Any*)&a);
1244 
1245   succeed;
1246 }
1247 
1248 
1249 
1250 		/********************************
1251 		*           SCROLLING		*
1252 		********************************/
1253 
1254 static status
scrollWindow(PceWindow sw,Int x,Int y,BoolObj ax,BoolObj ay)1255 scrollWindow(PceWindow sw, Int x, Int y, BoolObj ax, BoolObj ay)
1256 { int ox = valInt(sw->scroll_offset->x);
1257   int oy = valInt(sw->scroll_offset->y);
1258   int nx, ny;
1259 
1260   if ( notDefault(x) )
1261   { if ( ax == ON )
1262       nx = -valInt(x);
1263     else
1264       nx = ox - valInt(x);
1265   } else
1266     nx = ox;
1267   if ( notDefault(y) )
1268   { if ( ay == ON )
1269       ny = -valInt(y);
1270     else
1271       ny = oy - valInt(y);
1272   } else
1273     ny = oy;
1274 
1275   if ( ox != nx || ny != oy )
1276   { assign(sw->scroll_offset, x, toInt(nx));
1277     assign(sw->scroll_offset, y, toInt(ny));
1278 
1279     UpdateScrollbarValuesWindow(sw);
1280     updatePositionSubWindowsDevice((Device) sw);
1281 
1282 #ifdef WIN32_GRAPHICS
1283     ws_scroll_window(sw, nx-ox, ny-oy);
1284 #else
1285   { int x, y, w, h;
1286     int p = valInt(sw->pen);
1287 
1288     compute_window(sw, &x, &y, &w, &h);
1289     x -= valInt(sw->scroll_offset->x) + p;
1290     y -= valInt(sw->scroll_offset->y) + p;
1291 
1292 					/* should use block-move and only */
1293 					/* consider a small part changed */
1294     changed_window(sw, x, y, w, h, TRUE);
1295     addChain(ChangedWindows, sw);
1296   }
1297 #endif
1298   }
1299 
1300   succeed;
1301 }
1302 
1303 
1304 static status
scrollToWindow(PceWindow sw,Point pos)1305 scrollToWindow(PceWindow sw, Point pos)
1306 { return scrollWindow(sw, pos->x, pos->y, ON, ON);
1307 }
1308 
1309 #define DO_X 0x1
1310 #define DO_Y 0x2
1311 
1312 static status
normalise_window(PceWindow sw,Area a,int xy)1313 normalise_window(PceWindow sw, Area a, int xy)
1314 { int x, y, w, h;			/* see getVisibleWindow() */
1315   int p = valInt(sw->pen);
1316   int sx = -valInt(sw->scroll_offset->x);
1317   int sy = -valInt(sw->scroll_offset->y);
1318   int nsx = sx, nsy = sy;
1319   int ax = valInt(a->x), ay = valInt(a->y);
1320   int aw = valInt(a->w), ah = valInt(a->h);
1321   int shift;
1322 
1323   NormaliseArea(ax, ay, aw, ah);
1324   DEBUG(NAME_normalise, Cprintf("Normalise to: %d, %d %d x %d\n",
1325 				ax, ay, aw, ah));
1326 
1327   compute_window(sw, &x, &y, &w, &h);
1328   x -= valInt(sw->scroll_offset->x) + p;
1329   y -= valInt(sw->scroll_offset->y) + p;
1330   DEBUG(NAME_normalise, Cprintf("Visible: %d, %d %d x %d\n", x, y, w, h));
1331 
1332   if ( (xy&DO_X) && ax + aw > x + w )
1333   { shift = (ax + aw) - (x + w);
1334     nsx += shift; x += shift;
1335     DEBUG(NAME_normalise, Cprintf("left by %d\n", shift));
1336   }
1337   if ( (xy&DO_Y) && ay + ah > y + h )
1338   { shift = (ay + ah) - (y + h);
1339     nsy += shift; y += shift;
1340     DEBUG(NAME_normalise, Cprintf("up by %d\n", shift));
1341   }
1342   if ( (xy&DO_X) && ax < x )
1343   { nsx -= x - ax;
1344     DEBUG(NAME_normalise, Cprintf("right by %d\n", x - ax));
1345   }
1346   if ( (xy&DO_Y) && ay < y )
1347   { nsy -= y - ay;
1348     DEBUG(NAME_normalise, Cprintf("down by %d\n", y - ay));
1349   }
1350 
1351   if ( nsx != sx || nsy != sy )
1352     scrollWindow(sw,
1353 		 nsx != sx ? toInt(nsx) : (Int) DEFAULT,
1354 		 nsy != sy ? toInt(nsy) : (Int) DEFAULT,
1355 		 ON, ON);
1356 
1357   succeed;
1358 }
1359 
1360 
1361 static status
normaliseWindow(PceWindow sw,Any obj,Name mode)1362 normaliseWindow(PceWindow sw, Any obj, Name mode)
1363 { int xy;
1364 
1365   if ( mode == NAME_x )
1366     xy = DO_X;
1367   else if ( mode == NAME_y )
1368     xy = DO_Y;
1369   else
1370     xy = DO_X|DO_Y;
1371 
1372   if ( instanceOfObject(obj, ClassArea) )
1373     return normalise_window(sw, obj, xy);
1374 
1375   ComputeGraphical(sw);
1376   if ( notNil(sw->decoration) )
1377     ComputeGraphical(sw->decoration);
1378 
1379   if ( instanceOfObject(obj, ClassGraphical) )
1380   { Graphical gr = obj;
1381     Area a = getAbsoluteAreaGraphical(gr, (Device) sw);
1382 
1383     normalise_window(sw, a, xy);
1384     doneObject(a);
1385     succeed;
1386   }
1387 
1388   assert(instanceOfObject(obj, ClassChain));
1389   { Chain ch = obj;
1390     Cell cell;
1391     Area a = tempObject(ClassArea, EAV);
1392     Graphical gr;
1393 
1394     for_cell(cell, ch)
1395       if ( (gr = checkType(cell->value, TypeGraphical, NIL)) )
1396       { Area a2 = getAbsoluteAreaGraphical(gr, (Device) sw);
1397 
1398 	unionNormalisedArea(a, a2);
1399 	doneObject(a2);
1400       }
1401 
1402     if ( a->w != ZERO && a->h != ZERO )
1403       normalise_window(sw, a, xy);
1404     considerPreserveObject(a);
1405 
1406     succeed;
1407   }
1408 }
1409 
1410 
1411 static status
scrollHorizontalWindow(PceWindow sw,Name dir,Name unit,Int amount,BoolObj force)1412 scrollHorizontalWindow(PceWindow sw,
1413 		       Name dir, Name unit, Int amount, BoolObj force)
1414 { if ( force != ON &&
1415        (!instanceOfObject(sw->decoration, ClassWindowDecorator) ||
1416 	isNil(((WindowDecorator)sw->decoration)->horizontal_scrollbar)) )
1417     fail;
1418 
1419   if ( unit == NAME_file )
1420   { Area bb = sw->bounding_box;
1421 
1422     if ( dir == NAME_goto )
1423     { int h = ((valInt(bb->w)-valInt(sw->area->w)) * valInt(amount)) / 1000;
1424 
1425       scrollWindow(sw, toInt(h + valInt(bb->x)), DEFAULT, ON, ON);
1426     }
1427   } else if ( unit == NAME_page )
1428   { Area a = sw->area;
1429     int d = (valInt(a->w) * valInt(amount)) / 1000;
1430 
1431     scrollWindow(sw, toInt(dir == NAME_forwards ? d : -d), DEFAULT, OFF, ON);
1432   } else if ( unit == NAME_line )
1433   { int d = 20 * valInt(amount);
1434 
1435     scrollWindow(sw, toInt(dir == NAME_forwards ? d : -d), DEFAULT, OFF, ON);
1436   }
1437 
1438   succeed;
1439 }
1440 
1441 
1442 static status
scrollVerticalWindow(PceWindow sw,Name dir,Name unit,Int amount,BoolObj force)1443 scrollVerticalWindow(PceWindow sw,
1444 		     Name dir, Name unit, Int amount, BoolObj force)
1445 { if ( force != ON &&
1446        (!instanceOfObject(sw->decoration, ClassWindowDecorator) ||
1447 	isNil(((WindowDecorator)sw->decoration)->vertical_scrollbar)) )
1448     fail;
1449 
1450   if ( unit == NAME_file )
1451   { Area bb = sw->bounding_box;
1452 
1453     if ( dir == NAME_goto )
1454     { int h = ((valInt(bb->h)-valInt(sw->area->h)) * valInt(amount)) / 1000;
1455 
1456       scrollWindow(sw, DEFAULT, toInt(h + valInt(bb->y)), ON, ON);
1457     }
1458   } else if ( unit == NAME_page )
1459   { Area a = sw->area;
1460     int d = (valInt(a->h) * valInt(amount)) / 1000;
1461 
1462     scrollWindow(sw, DEFAULT, toInt(dir == NAME_forwards ? d : -d), ON, OFF);
1463   } else if ( unit == NAME_line )
1464   { int d = 20 * valInt(amount);
1465 
1466     scrollWindow(sw, DEFAULT, toInt(dir == NAME_forwards ? d : -d), ON, OFF);
1467   }
1468 
1469   succeed;
1470 }
1471 
1472 
1473 static status
UpdateScrollbarValuesWindow(PceWindow sw)1474 UpdateScrollbarValuesWindow(PceWindow sw)
1475 { return qadSendv(sw, NAME_updateScrollBarValues, 0, NULL);
1476 }
1477 
1478 static status
updateScrollbarValuesWindow(PceWindow sw)1479 updateScrollbarValuesWindow(PceWindow sw)
1480 { if ( notNil(sw->decoration) )
1481     requestComputeScrollbarsWindowDecorator((WindowDecorator)sw->decoration);
1482 
1483   succeed;
1484 }
1485 
1486 status
changedUnionWindow(PceWindow sw,Int ox,Int oy,Int ow,Int oh)1487 changedUnionWindow(PceWindow sw, Int ox, Int oy, Int ow, Int oh)
1488 { return UpdateScrollbarValuesWindow(sw);
1489 }
1490 
1491 
1492 static int
view_region(int x,int w,int rx,int rw)1493 view_region(int x, int w, int rx, int rw)
1494 { if ( rx > x )
1495   { w -= rx - x;
1496     x  = rx;
1497   }
1498 
1499   if ( x+w > rx+rw )
1500     w = rx+rw - x;
1501 
1502   return w < 0 ? 2 : w;
1503 }
1504 
1505 
1506 static status				/* update bubble of scroll_bar */
bubbleScrollBarWindow(PceWindow sw,ScrollBar sb)1507 bubbleScrollBarWindow(PceWindow sw, ScrollBar sb)
1508 { Area bb = sw->bounding_box;
1509   int x, y, w, h;
1510   int hor    = (sb->orientation == NAME_horizontal);
1511   int start  = valInt(hor ? bb->x : bb->y);
1512   int length = valInt(hor ? bb->w : bb->h);
1513   int view;
1514 
1515   compute_window(sw, &x, &y, &w, &h);
1516   x -= valInt(sw->scroll_offset->x);
1517   y -= valInt(sw->scroll_offset->y);
1518 					/* x, y, w, h: visible area */
1519 
1520   view = view_region(start, length,
1521 		     hor ? -valInt(sw->scroll_offset->x)
1522 			 : -valInt(sw->scroll_offset->y),
1523 		     hor ? w : h);
1524   start  = (hor ? x : y) - start;
1525   if ( start < 0 ) start = 0;
1526   if ( start > length-view ) start = length-view;
1527 
1528   return bubbleScrollBar(sb, toInt(length), toInt(start), toInt(view));
1529 }
1530 
1531 
1532 
1533 		/********************************
1534 		*        MOVE THE POINTER	*
1535 		********************************/
1536 
1537 status
pointerWindow(PceWindow sw,Point pos)1538 pointerWindow(PceWindow sw, Point pos)
1539 { if ( createdWindow(sw) )
1540   { int ox, oy;
1541 
1542     offset_window(sw, &ox, &oy);
1543     ws_move_pointer(sw, valInt(pos->x) + ox, valInt(pos->y) + oy);
1544   }
1545 
1546   succeed;
1547 }
1548 
1549 
1550 		/********************************
1551 		*             CURSOR		*
1552 		********************************/
1553 
1554 status
focusCursorWindow(PceWindow sw,CursorObj cursor)1555 focusCursorWindow(PceWindow sw, CursorObj cursor)
1556 { assign(sw, focus_cursor, cursor);
1557 
1558   return updateCursorWindow(sw);
1559 }
1560 
1561 
1562 static CursorObj
getDisplayedCursorWindow(PceWindow sw)1563 getDisplayedCursorWindow(PceWindow sw)
1564 { CursorObj rval;
1565 
1566   if ( notNil(sw->focus) )
1567   { if ( notNil(sw->focus_cursor) )
1568       answer(sw->focus_cursor);
1569     if ( notNil(sw->focus->cursor) )
1570       answer(sw->focus->cursor);
1571   }
1572 
1573   if ( (rval = getDisplayedCursorDevice((Device) sw)) &&
1574        notNil(rval) )
1575     answer(rval);
1576 
1577   answer(sw->cursor);
1578 }
1579 
1580 
1581 status
updateCursorWindow(PceWindow sw)1582 updateCursorWindow(PceWindow sw)
1583 { if ( ws_created_window(sw) )
1584   { CursorObj cursor = getDisplayedCursorWindow(sw);
1585 
1586     if ( !cursor )
1587       cursor = NIL;
1588 
1589     if ( sw->displayed_cursor != cursor )
1590     { assign(sw, displayed_cursor, cursor);
1591       ws_window_cursor(sw, cursor);
1592     }
1593   }
1594 
1595   succeed;
1596 }
1597 
1598 
1599 		/********************************
1600 		*        AREA MANAGEMENT	*
1601 		********************************/
1602 
1603 status
geometryWindow(PceWindow sw,Int X,Int Y,Int W,Int H)1604 geometryWindow(PceWindow sw, Int X, Int Y, Int W, Int H)
1605 { CHANGING_GRAPHICAL(sw,
1606 		     { setArea(sw->area, X, Y, W, H);
1607 		       if ( valInt(sw->area->w) <= 0 )
1608 			 assign(sw->area, w, ONE);
1609 		       if ( valInt(sw->area->h) <= 0 )
1610 			 assign(sw->area, h, ONE);
1611 		     });
1612 
1613   if ( notNil(sw->frame) && ws_created_window(sw) )
1614   { int x, y, w, h;
1615     int pen = valInt(sw->pen);
1616 
1617     x = valInt(sw->area->x);
1618     y = valInt(sw->area->y);
1619     w = valInt(sw->area->w);
1620     h = valInt(sw->area->h);
1621 
1622     ws_geometry_window(sw, x, y, w, h, pen);
1623   }
1624 
1625   succeed;
1626 }
1627 
1628 
1629 status
requestGeometryWindow(PceWindow sw,Int X,Int Y,Int W,Int H)1630 requestGeometryWindow(PceWindow sw, Int X, Int Y, Int W, Int H)
1631 { if ( notNil(sw->tile) )
1632   { int p = valInt(sw->pen);
1633     Int ww, wh;
1634 
1635     ww = (isDefault(W) ? (Int) DEFAULT : toInt(valInt(W) + 2*p));
1636     wh = (isDefault(H) ? (Int) DEFAULT : toInt(valInt(H) + 2*p));
1637 
1638     setTile(sw->tile, DEFAULT, DEFAULT, ww, wh);
1639 
1640     if ( notNil(sw->frame) )
1641       send(sw->frame, NAME_fit, EAV);
1642 
1643     succeed;
1644   } else if ( notNil(sw->decoration) )
1645   { return send(sw->decoration, NAME_requestGeometry, X, Y, W, H, EAV);
1646   } else
1647     return geometryWindow(sw, X, Y, W, H);
1648 }
1649 
1650 
1651 status					/* position on display */
get_display_position_window(PceWindow sw,int * X,int * Y)1652 get_display_position_window(PceWindow sw, int *X, int *Y)
1653 { int x, y;
1654   FrameObj fr;
1655 
1656   TRY(frame_offset_window(sw, &fr, &x, &y));
1657   x += valInt(fr->area->x);
1658   y += valInt(fr->area->y);
1659 
1660   *X = x; *Y = y;
1661 
1662   succeed;
1663 }
1664 
1665 
1666 static status
visible_window(PceWindow sw,IArea a)1667 visible_window(PceWindow sw, IArea a)
1668 { int p = valInt(sw->pen);
1669 
1670   compute_window(sw, &a->x, &a->y, &a->w, &a->h);
1671   a->x -= valInt(sw->scroll_offset->x);
1672   a->y -= valInt(sw->scroll_offset->y);
1673   a->w -= 2*p;
1674   a->h -= 2*p;
1675 
1676   succeed;
1677 }
1678 
1679 
1680 static Area
getVisibleWindow(PceWindow sw)1681 getVisibleWindow(PceWindow sw)
1682 { iarea a;
1683 
1684   visible_window(sw, &a);
1685 
1686   answer(answerObject(ClassArea,
1687 		      toInt(a.x), toInt(a.y), toInt(a.w), toInt(a.h),
1688 		      EAV));
1689 }
1690 
1691 
1692 static Area
getBoundingBoxWindow(PceWindow w)1693 getBoundingBoxWindow(PceWindow w)
1694 { ComputeGraphical((Graphical) w);
1695 
1696   answer(w->bounding_box);
1697 }
1698 
1699 
1700 		/********************************
1701 		*         LINK TO FRAME		*
1702 		********************************/
1703 
1704 static status
tileWindow(PceWindow sw,TileObj tile)1705 tileWindow(PceWindow sw, TileObj tile)
1706 { if ( isDefault(tile) )
1707   { if ( isNil(sw->tile) )
1708       assign(sw, tile, newObject(ClassTile, sw, EAV));
1709   } else
1710     assign(sw, tile, tile);		/* TBD: check */
1711 
1712   succeed;
1713 }
1714 
1715 
1716 PceWindow
getUserWindow(PceWindow sw)1717 getUserWindow(PceWindow sw)
1718 { PceWindow w;
1719 
1720   if ( instanceOfObject(sw, ClassWindowDecorator) &&
1721        notNil(w = ((WindowDecorator)sw)->window) )
1722     answer(w);
1723 
1724   answer(sw);
1725 }
1726 
1727 
1728 static status
for_all_tile(TileObj tile,SendFunc f,Any arg)1729 for_all_tile(TileObj tile, SendFunc f, Any arg)
1730 { if ( isNil(tile->members) )
1731     return (*f)(tile->object, arg);
1732   else
1733   { TileObj st;
1734 
1735     for_chain(tile->members, st,
1736 	      TRY(for_all_tile(st, f, arg)));
1737 
1738     succeed;
1739   }
1740 }
1741 
1742 
1743 static status
frame_window(PceWindow sw,FrameObj frame)1744 frame_window(PceWindow sw, FrameObj frame)
1745 { if ( notNil(sw->decoration) )
1746     sw = sw->decoration;
1747 
1748   if ( sw->frame != frame )
1749   { DEBUG(NAME_frame, Cprintf("Making %s part of %s\n", pp(sw), pp(frame)));
1750 
1751     addCodeReference(sw);
1752     if ( notNil(sw->frame) )
1753       DeleteFrame(sw->frame, sw);
1754     assign(sw, frame, frame);
1755     if ( notNil(sw->frame) )
1756       AppendFrame(sw->frame, sw);
1757     delCodeReference(sw);
1758   }
1759 
1760   succeed;
1761 }
1762 
1763 
1764 status
frameWindow(PceWindow sw,FrameObj frame)1765 frameWindow(PceWindow sw, FrameObj frame)
1766 { while ( notNil(sw->decoration) )
1767     sw = sw->decoration;
1768 
1769   if ( isDefault(frame) )
1770   { if ( isNil(sw->frame) )
1771       frame = newObject(ClassFrame, EAV);
1772     else
1773       succeed;
1774   }
1775 
1776   if ( isNil(frame->members) )
1777     return errorPce(frame, NAME_notInitialised);
1778 
1779   tileWindow(sw, DEFAULT);
1780   for_all_tile(getRootTile(sw->tile), frame_window, frame);
1781   if ( frame->status == NAME_open )
1782     DisplayedGraphical(sw, ON);
1783 
1784   succeed;
1785 }
1786 
1787 
1788 TileObj
getTileWindow(PceWindow sw)1789 getTileWindow(PceWindow sw)
1790 { while( notNil(sw->decoration) )
1791     sw = sw->decoration;
1792 
1793   tileWindow(sw, DEFAULT);
1794 
1795   answer(sw->tile);
1796 }
1797 
1798 
1799 FrameObj
getFrameWindow(PceWindow sw,BoolObj create)1800 getFrameWindow(PceWindow sw, BoolObj create)
1801 { PceWindow root = (PceWindow) getRootGraphical((Graphical) sw);
1802 
1803   if ( instanceOfObject(root, ClassWindow) )
1804   { if ( create != OFF )
1805       frameWindow(root, DEFAULT);
1806     if ( notNil(root->frame) )
1807       answer(root->frame);
1808   }
1809 
1810   fail;
1811 }
1812 
1813 
1814 static status
mergeFramesWindow(PceWindow w1,PceWindow w2)1815 mergeFramesWindow(PceWindow w1, PceWindow w2)
1816 { FrameObj fr1, fr2;
1817 
1818   if ( isNil(w1->frame) && isNil(w2->frame) )
1819   { /* frameWindow(w2, DEFAULT);
1820        frameWindow(w1, w2->frame);
1821     */
1822   } else if ( notNil(w1->frame) && notNil(w2->frame) )
1823   { if ( (fr1=w1->frame) != (fr2=w2->frame) )
1824     { Cell cell, c2;
1825 
1826       addCodeReference(fr1);
1827       for_cell_save(cell, c2, fr1->members)
1828 	frame_window(cell->value, fr2);
1829       delCodeReference(fr1);
1830       freeableObj(fr1);
1831     }
1832   } else if ( notNil(w1->frame) )
1833     frameWindow(w2, w1->frame);
1834   else
1835     frameWindow(w1, w2->frame);
1836 
1837   succeed;
1838 }
1839 
1840 
1841 static status
relateWindow(PceWindow sw,Name how,Any to)1842 relateWindow(PceWindow sw, Name how, Any to)
1843 { PceWindow w2 = instanceOfObject(to, ClassWindow) ? to : NIL;
1844   PceWindow wto = w2;
1845   FrameObj fr;
1846 
1847   if ( notNil(sw->decoration) )
1848     return relateWindow(sw->decoration, how, to);
1849   if ( notNil(w2) && notNil(w2->decoration) )
1850     return relateWindow(sw, how, w2->decoration);
1851 
1852   DeviceGraphical((Graphical)sw, NIL);
1853   if ( notNil(w2) )
1854   { DeviceGraphical((Graphical)w2, NIL);
1855     tileWindow(w2, DEFAULT);
1856   }
1857 
1858   if ( createdWindow(sw) && notNil(sw->frame) )
1859     send(sw->frame, NAME_delete, sw, EAV);
1860 
1861   tileWindow(sw, DEFAULT);
1862 
1863   if ( isNil(wto) )
1864     wto = ((TileObj)to)->object;
1865 
1866   if ( instanceOfObject(wto, ClassWindow) && createdWindow(wto) )
1867   { TileObj t = getRootTile(sw->tile);
1868     Any msg = newObject(ClassMessage, Arg(1), NAME_ComputeDesiredSize, EAV);
1869 
1870     send(t, NAME_forAll, msg, EAV);
1871     freeObject(msg);
1872   }
1873 
1874   if ( notNil(w2) )
1875   { TRY(send(sw->tile, how, w2->tile, EAV));
1876   } else
1877   { TileObj t2 = to;
1878 
1879     TRY(send(sw->tile, how, t2, OFF, EAV));
1880     while( isNil(t2->object) )
1881     { t2 = getHeadChain(t2->members);
1882       assert(t2);
1883     }
1884 
1885     w2 = t2->object;
1886   }
1887 
1888   mergeFramesWindow(sw, w2);
1889 
1890   if ( (fr=getFrameWindow(sw, OFF)) && createdFrame(fr) )
1891     send(fr, NAME_updateTileAdjusters, EAV);
1892 
1893   succeed;
1894 }
1895 
1896 
1897 static status
leftWindow(PceWindow w1,Any w2)1898 leftWindow(PceWindow w1, Any w2)
1899 { return relateWindow(w1, NAME_left, w2);
1900 }
1901 
1902 
1903 static status
rightWindow(PceWindow w1,Any w2)1904 rightWindow(PceWindow w1, Any w2)
1905 { return relateWindow(w1, NAME_right, w2);
1906 }
1907 
1908 
1909 static status
aboveWindow(PceWindow w1,Any w2)1910 aboveWindow(PceWindow w1, Any w2)
1911 { return relateWindow(w1, NAME_above, w2);
1912 }
1913 
1914 
1915 static status
belowWindow(PceWindow w1,Any w2)1916 belowWindow(PceWindow w1, Any w2)
1917 { return relateWindow(w1, NAME_below, w2);
1918 }
1919 
1920 
1921 		/********************************
1922 		*          ATTRIBUTES		*
1923 		********************************/
1924 
1925 
1926 static status
penWindow(PceWindow sw,Int pen)1927 penWindow(PceWindow sw, Int pen)
1928 { if ( sw->pen != pen )
1929   { assign(sw, pen, pen);
1930 
1931     if ( ws_created_window(sw) )
1932     { int x, y, w, h;
1933       int pen = valInt(sw->pen);
1934 
1935       x = valInt(sw->area->x);
1936       y = valInt(sw->area->y);
1937       w = valInt(sw->area->w);
1938       h = valInt(sw->area->h);
1939 
1940       ws_geometry_window(sw, x, y, w, h, pen);
1941     }
1942   }
1943 
1944   succeed;
1945 }
1946 
1947 
1948 static status
colourWindow(PceWindow sw,Colour colour)1949 colourWindow(PceWindow sw, Colour colour)
1950 { if ( isDefault(colour) && notNil(sw->frame) )
1951     colour = sw->frame->display->foreground;
1952 
1953   if ( sw->colour != colour )
1954   { assign(sw, colour, colour);
1955     redrawWindow(sw, DEFAULT);
1956   }
1957 
1958   succeed;
1959 }
1960 
1961 
1962 static status
backgroundWindow(PceWindow sw,Colour colour)1963 backgroundWindow(PceWindow sw, Colour colour)
1964 { if ( isDefault(colour) && notNil(sw->frame) )
1965     colour = sw->frame->display->background;
1966 
1967   if ( sw->background != colour )
1968   { assign(sw, background, colour);
1969     ws_window_background(sw, colour);
1970     redrawWindow(sw, DEFAULT);
1971   }
1972 
1973   succeed;
1974 }
1975 
1976 
1977 static status
selectionFeedbackWindow(PceWindow sw,Any feedback)1978 selectionFeedbackWindow(PceWindow sw, Any feedback)
1979 { if ( isDefault(feedback) )
1980     TRY(feedback = getClassVariableValueObject(sw, NAME_selectionFeedback));
1981 
1982   if ( feedback != sw->selection_feedback )
1983   { assign(sw, selection_feedback, feedback);
1984     redrawWindow(sw, DEFAULT);
1985   }
1986 
1987   succeed;
1988 }
1989 
1990 
1991 static Colour
getForegroundWindow(PceWindow sw)1992 getForegroundWindow(PceWindow sw)
1993 { answer(sw->colour);
1994 }
1995 
1996 
1997 static status
sensitiveWindow(PceWindow sw,BoolObj sensitive)1998 sensitiveWindow(PceWindow sw, BoolObj sensitive)
1999 { if ( sw->sensitive != sensitive )
2000   { assign(sw, sensitive, sensitive);
2001 
2002     ws_enable_window(sw, sensitive == ON ? TRUE : FALSE);
2003   }
2004 
2005   succeed;
2006 }
2007 
2008 
2009 		/********************************
2010 		*            FLUSHING		*
2011 		********************************/
2012 
2013 status
flushWindow(PceWindow sw)2014 flushWindow(PceWindow sw)
2015 { DisplayObj d = getDisplayGraphical((Graphical) sw);
2016 
2017   if ( d )
2018   { RedrawWindow(sw);
2019     ws_flush_display(d);
2020   }
2021 
2022   succeed;
2023 }
2024 
2025 
2026 		/********************************
2027 		*             ALERT		*
2028 		********************************/
2029 
2030 status
flashWindow(PceWindow sw,Area a,Int time)2031 flashWindow(PceWindow sw, Area a, Int time)
2032 { if ( sw->displayed == ON && createdWindow(sw) )
2033   { int t;
2034 
2035     if ( isDefault(time) )
2036       time = getClassVariableValueObject(sw, NAME_visualBellDuration);
2037     t = (isInteger(time) ? valInt(time) : 250);
2038 
2039     if ( isDefault(a) )
2040       ws_flash_window(sw, t);
2041     else
2042     { int x, y, w, h;
2043 
2044       x = valInt(a->x);
2045       y = valInt(a->y);
2046       w = valInt(a->w);
2047       h = valInt(a->h);
2048       NormaliseArea(x, y, w, h);
2049 
2050       ws_flash_area_window(sw, x, y, w, h, t);
2051     }
2052   }
2053 
2054   succeed;
2055 }
2056 
2057 
2058 		/********************************
2059 		*           HIDE/EXPOSE		*
2060 		********************************/
2061 
2062 static status
exposeWindow(PceWindow sw)2063 exposeWindow(PceWindow sw)
2064 { if ( notNil(sw->decoration) )
2065     return exposeWindow(sw->decoration);
2066 
2067   if ( notNil(sw->frame) )
2068     return exposeFrame(sw->frame);
2069 
2070   ws_raise_window(sw);
2071 
2072   succeed;
2073 }
2074 
2075 
2076 static status
hideWindow(PceWindow sw)2077 hideWindow(PceWindow sw)
2078 { if ( notNil(sw->decoration) )
2079     return hideWindow(sw->decoration);
2080 
2081   if ( notNil(sw->frame) )
2082     return hideFrame(sw->frame);
2083 
2084   ws_lower_window(sw);
2085 
2086   succeed;
2087 }
2088 
2089 
2090 		/********************************
2091 		*              VISUAL		*
2092 		********************************/
2093 
2094 static Any
getContainedInWindow(PceWindow sw)2095 getContainedInWindow(PceWindow sw)
2096 { if ( notNil(sw->frame) )
2097     answer(sw->frame);
2098 
2099   return getContainedInGraphical((Graphical)sw);
2100 }
2101 
2102 
2103 static status
resetWindow(PceWindow sw)2104 resetWindow(PceWindow sw)
2105 { assign(sw, current_event, NIL);
2106   focusWindow(sw, NIL, NIL, NIL, NIL);
2107   updateCursorWindow(sw);
2108 
2109   return resetVisual((VisualObj) sw);
2110 }
2111 
2112 
2113 static status
catchAllWindowv(PceWindow sw,Name selector,int argc,Any * argv)2114 catchAllWindowv(PceWindow sw, Name selector, int argc, Any *argv)
2115 { if ( getSendMethodClass(ClassWindowDecorator, selector) )
2116   { newObject(ClassWindowDecorator, sw, EAV);
2117 
2118     if ( notNil(sw->decoration) )
2119       return sendv(sw->decoration, selector, argc, argv);
2120   }
2121 
2122   if ( getSendMethodClass(ClassFrame, selector) )
2123   { FrameObj fr = getFrameWindow(sw, DEFAULT);
2124 
2125     if ( fr && notNil(fr) )
2126       return sendv(fr, selector, argc, argv);
2127     else
2128       fail;
2129   }
2130 
2131   if ( getSendMethodClass(ClassTile, selector) )
2132   { if ( notNil(sw->decoration) )
2133       return catchAllWindowv(sw->decoration, selector, argc, argv);
2134 
2135     tileWindow(sw, DEFAULT);
2136     return sendv(sw->tile, selector, argc, argv);
2137   }
2138 
2139   return errorPce(sw, NAME_noBehaviour, CtoName("->"), selector);
2140 }
2141 
2142 		 /*******************************
2143 		 *	    THREADING		*
2144 		 *******************************/
2145 
2146 static Int
getThreadWindow(PceWindow sw)2147 getThreadWindow(PceWindow sw)
2148 { return ws_window_thread(sw);
2149 }
2150 
2151 
2152 		 /*******************************
2153 		 *	 CLASS DECLARATION	*
2154 		 *******************************/
2155 
2156 /* Type declarations */
2157 
2158 static char *T_open[] =
2159         { "[point]", "normalise=[bool]" };
2160 static char *T_scrollHV[] =
2161         { "direction={forwards,backwards,goto}",
2162 	  "unit={page,file,line}",
2163 	  "amount=int",
2164 	  "force=[bool]"
2165 	};
2166 static char *T_decorate[] =
2167         { "area=[{grow,shrink}]", "left_margin=[int]", "right_margin=[int]", "top_margin=[int]", "bottom_margin=[int]", "decorator=[window]" };
2168 static char *T_confirmCentered[] =
2169         { "center=[point]", "grab=[bool]", "monitor=[monitor]" };
2170 static char *T_typed[] =
2171         { "event|event_id", "delegate=[bool]" };
2172 static char *T_focus[] =
2173         { "graphical*", "[recogniser]*", "[cursor]*", "[name]*" };
2174 static char *T_initialise[] =
2175         { "label=[name]", "size=[size]", "display=[display]" };
2176 static char *T_catchAll[] =
2177         { "name", "unchecked ..." };
2178 static char *T_changedUnion[] =
2179         { "ox=int", "oy=int", "ow=int", "oh=int" };
2180 static char *T_confirm[] =
2181         { "position=[point]", "grab=[bool]", "normalise=[bool]" };
2182 static char *T_geometry[] =
2183         { "x=[int]", "y=[int]", "width=[int]", "height=[int]" };
2184 static char *T_flash[] =
2185 	{ "area=[area]", "time=[int]" };
2186 static char *T_normalise[] =
2187 	{ "on=area|graphical|chain", "mode=[{xy,x,y}]" };
2188 
2189 /* Instance Variables */
2190 
2191 static vardecl var_window[] =
2192 { IV(NAME_frame, "frame*", IV_NONE,
2193      NAME_organisation, "Frame the window is member of"),
2194   IV(NAME_decoration, "window_decorator*", IV_GET,
2195      NAME_appearance, "Window displaying me and my decorations"),
2196   IV(NAME_boundingBox, "area", IV_NONE,
2197      NAME_area, "Union of graphicals"),
2198   IV(NAME_tile, "tile*", IV_NONE,
2199      NAME_layout, "Tile that manages my area"),
2200   SV(NAME_resizeMessage, "code*", IV_GET|IV_STORE, resizeMessageWindow,
2201      NAME_resize, "Executed after window has resized"),
2202   IV(NAME_displayedCursor, "cursor*", IV_NONE,
2203      NAME_internal, "Currently displayed cursor"),
2204   SV(NAME_inputFocus, "bool", IV_GET|IV_STORE, inputFocusWindow,
2205      NAME_focus, "Window has input focus"),
2206   SV(NAME_keyboardFocus, "graphical*", IV_GET|IV_STORE, keyboardFocusWindow,
2207      NAME_focus, "Graphical in focus of keyboard events"),
2208   IV(NAME_focus, "graphical*", IV_GET,
2209      NAME_focus, "Graphical in focus"),
2210   IV(NAME_focusRecogniser, "recogniser*", IV_GET,
2211      NAME_focus, "Recogniser in focus"),
2212   SV(NAME_focusCursor, "cursor*", IV_GET|IV_STORE, focusCursorWindow,
2213      NAME_cursor, "Cursor while there is a focus"),
2214   IV(NAME_focusButton, "[button_name]*", IV_GET,
2215      NAME_focus, "Button that should terminate focus"),
2216   IV(NAME_focusEvent, "event*", IV_GET,
2217      NAME_focus, "<-current_event when ->focus was set"),
2218   IV(NAME_scrollOffset, "point", IV_NONE,
2219      NAME_internal, "How much the window is scrolled"),
2220   IV(NAME_popup, "popup*", IV_BOTH,
2221      NAME_menu, "Popup-menu of the window"),
2222   IV(NAME_currentEvent, "event*", IV_GET,
2223      NAME_event, "Event being processed now"),
2224   SV(NAME_sensitive, "bool", IV_GET|IV_STORE, sensitiveWindow,
2225      NAME_event, "Window accepts events"),
2226   SV(NAME_background, "colour|pixmap", IV_GET|IV_STORE, backgroundWindow,
2227      NAME_appearance, "Background colour or pattern"),
2228   IV(NAME_hasPointer, "bool", IV_BOTH,
2229      NAME_event, "If @on, pointer (mouse) is in window"),
2230   SV(NAME_selectionFeedback, "{invert,handles,colour}|elevation|colour*",
2231      IV_GET|IV_STORE, selectionFeedbackWindow,
2232      NAME_appearance, "How <-selected graphicals are visualised"),
2233   IV(NAME_bufferedUpdate, "bool", IV_BOTH,
2234      NAME_redraw, "If @on (default) use buffered update"),
2235   IV(NAME_changesData, "alien:UpdateArea", IV_NONE,
2236      NAME_repaint, "Summary info for redraw"),
2237   IV(NAME_wsRef, "alien:WsRef", IV_NONE,
2238      NAME_windowSystem, "Window-System reference")
2239 };
2240 
2241 /* Send Methods */
2242 
2243 #ifdef WIN32_GRAPHICS
2244 extern status winHandleWindow(PceWindow sw, Int handle);
2245 extern Int    getWinHandleWindow(PceWindow sw);
2246 #endif
2247 
2248 static senddecl send_window[] =
2249 { SM(NAME_destroy, 0, NULL, destroyWindow,
2250      DEFAULT, "->destroy associated frame"),
2251   SM(NAME_device, 1, "device*", deviceWindow,
2252      DEFAULT, "Display window on device, take care of <-decoration"),
2253   SM(NAME_displayed, 1, "bool", displayedWindow,
2254      DEFAULT, "(Un)display window, take care of <-decoration"),
2255   SM(NAME_flush, 0, NULL, flushWindow,
2256      DEFAULT, "Update graphicals in this window immediately"),
2257   SM(NAME_free, 0, NULL, freeWindow,
2258      DEFAULT, "->free associated frame"),
2259   SM(NAME_geometry, 4, T_geometry, geometryWindow,
2260      DEFAULT, "Resize window inside its frame"),
2261   SM(NAME_initialise, 3, T_initialise, initialiseWindow,
2262      DEFAULT, "Create from label, size and display"),
2263   SM(NAME_move, 1, "point", positionGraphical,
2264      DEFAULT, "Move origin to argument"),
2265   SM(NAME_reparent, 0, NULL, reparentWindow,
2266      DEFAULT, "If no longer related to the window, ->uncreate"),
2267   SM(NAME_requestGeometry, 4, T_geometry, requestGeometryWindow,
2268      DEFAULT, "Resize window inside its frame"),
2269   SM(NAME_reset, 0, NULL, resetWindow,
2270      DEFAULT, "Reset window after an abort"),
2271   SM(NAME_unlink, 0, NULL, unlinkWindow,
2272      DEFAULT, "Destroy related window-system resources"),
2273   SM(NAME_x, 1, "int", xGraphical,
2274      DEFAULT, "Move graphical horizontally"),
2275   SM(NAME_y, 1, "int", yGraphical,
2276      DEFAULT, "Move graphical vertically"),
2277   SM(NAME_colour, 1, "[colour|pixmap]", colourWindow,
2278      DEFAULT, "Default colour of graphicals"),
2279   SM(NAME_pen, 1, "0..", penWindow,
2280      DEFAULT, "Thickness of line around window"),
2281   SM(NAME_position, 1, "point", positionGraphical,
2282      DEFAULT, "Position in <-frame"),
2283   SM(NAME_typed, 2, T_typed, typedWindow,
2284      NAME_accelerator, "Handle accelerator (delegate to <-frame)"),
2285   SM(NAME_decorate, 6, T_decorate, decorateWindow,
2286      NAME_appearance, "Embed window for scrollbars, etc."),
2287   SM(NAME_foreground, 1, "colour", colourWindow,
2288      NAME_appearance, "Set foreground colour"),
2289   SM(NAME_resize, 0, NULL, resizeWindow,
2290      NAME_area, "Execute <-resize_message"),
2291   SM(NAME_catchAll, 2, T_catchAll, catchAllWindowv,
2292      NAME_delegate, "Handle frame methods when no frame is present"),
2293   SM(NAME_postEvent, 1, "event", postEventWindow,
2294      NAME_event, "Handle event"),
2295   SM(NAME_grabKeyboard, 1, "bool", grabKeyboardWindow,
2296      NAME_event, "Grab keyboard events"),
2297   SM(NAME_grabPointer, 1, "bool", grabPointerWindow,
2298      NAME_event, "Grab pointer (mouse) events"),
2299   SM(NAME_focus, 4, T_focus, focusWindow,
2300      NAME_focus, "Forward events to graphical"),
2301   SM(NAME_ComputeDesiredSize, 0, NULL, ComputeDesiredSizeWindow,
2302      NAME_layout, "Compute the desired size (no-op)"),
2303   SM(NAME_above, 1, "window|tile", aboveWindow,
2304      NAME_layout, "Put me above argument"),
2305   SM(NAME_below, 1, "window|tile", belowWindow,
2306      NAME_layout, "Put me below argument"),
2307   SM(NAME_left, 1, "window|tile", leftWindow,
2308      NAME_layout, "Put me left of argument"),
2309   SM(NAME_right, 1, "window|tile", rightWindow,
2310      NAME_layout, "Put me right of argument"),
2311   SM(NAME_create, 1, "[window]", createWindow,
2312      NAME_open, "Create associated X-window structure"),
2313   SM(NAME_Create, 1, "[window]", createWindow,
2314      NAME_open, "Create associated X-window structure (internal)"),
2315   SM(NAME_open, 2, T_open, openWindow,
2316      NAME_open, "Open associated frame on the display"),
2317   SM(NAME_openCentered, 3, T_confirmCentered, openCenteredWindow,
2318      NAME_open, "Open frame centered around point"),
2319   SM(NAME_uncreate, 0, NULL, uncreateWindow,
2320      NAME_open, "Destroy associated X-window structure"),
2321   SM(NAME_pointer, 1, "point", pointerWindow,
2322      NAME_pointer, "Move the pointer relative to window"),
2323   SM(NAME_redraw, 1, "[area]", redrawWindow,
2324      NAME_repaint, "Redraw (area of) the window"),
2325   SM(NAME_flash, 2, T_flash, flashWindow,
2326      NAME_report, "Flash (part of) the window"),
2327   SM(NAME_bubbleScrollBar, 1, "scroll_bar", bubbleScrollBarWindow,
2328      NAME_scroll, "Update bubble of given scroll_bar object"),
2329   SM(NAME_changedUnion, 4, T_changedUnion, changedUnionWindow,
2330      NAME_scroll, "Bounding box of content changed"),
2331   SM(NAME_updateScrollBarValues, 0, NULL, updateScrollbarValuesWindow,
2332      NAME_scroll, "Request scroll_bar update"),
2333   SM(NAME_normalise, 2, T_normalise, normaliseWindow,
2334      NAME_scroll, "Ensure area|graphical|chain is visible"),
2335   SM(NAME_scrollHorizontal, 4, T_scrollHV, scrollHorizontalWindow,
2336      NAME_scroll, "Trap message from horizontal scrollbar"),
2337   SM(NAME_scrollTo, 1, "point", scrollToWindow,
2338      NAME_scroll, "Make point top-left of window"),
2339   SM(NAME_scrollVertical, 4, T_scrollHV, scrollVerticalWindow,
2340      NAME_scroll, "Trap message from vertical scrollbar"),
2341   SM(NAME_expose, 0, NULL, exposeWindow,
2342      NAME_stacking, "Expose (raise) related frame"),
2343   SM(NAME_hide, 0, NULL, hideWindow,
2344      NAME_stacking, "Hide (lower) related frame"),
2345 #ifdef WIN32_GRAPHICS
2346   SM(NAME_winHandle, 1, "hwnd=int", winHandleWindow,
2347      NAME_windows, "Associate this XPCE window with the given MS-Window"),
2348 #endif
2349   SM(NAME_compute, 0, NULL, computeWindow,
2350      NAME_update, "Recompute window")
2351 };
2352 
2353 /* Get Methods */
2354 
2355 static getdecl get_window[] =
2356 { GM(NAME_containedIn, 0, "frame|device", NULL, getContainedInWindow,
2357      DEFAULT, "Frame/graphical device I'm contained in"),
2358   GM(NAME_convert, 1, "window", "graphical", getConvertWindow,
2359      DEFAULT, "Return graphical's <-window"),
2360   GM(NAME_frame, 1, "frame", "create=[bool]", getFrameWindow,
2361      DEFAULT, "Frame of window (create if not there)"),
2362   GM(NAME_tile, 0, "tile", NULL, getTileWindow,
2363      DEFAULT, "Tile of window (create if not there)"),
2364   GM(NAME_foreground, 0, "colour", NULL, getForegroundWindow,
2365      NAME_appearance, "Get foreground colour"),
2366   GM(NAME_boundingBox, 0, "area", NULL, getBoundingBoxWindow,
2367      NAME_area, "Union of graphicals"),
2368   GM(NAME_visible, 0, "area", NULL, getVisibleWindow,
2369      NAME_area, "New area representing visible part"),
2370   GM(NAME_size, 0, "size", NULL, getSizeGraphical,
2371      NAME_area, "New size representing size (avoid class-variable)"),
2372   GM(NAME_monitor, 0, "monitor", NULL, getMonitorWindow,
2373      NAME_organisation, "Monitor window is displayed on"),
2374   GM(NAME_displayedCursor, 0, "cursor*", NULL, getDisplayedCursorDevice,
2375      NAME_cursor, "Currently displayed cursor"),
2376   GM(NAME_confirm, 3, "any", T_confirm, getConfirmWindow,
2377      NAME_modal, "Run sub event-loop until ->return"),
2378 #ifdef WIN32_GRAPHICS
2379   GM(NAME_winHandle, 0, "int", NULL, getWinHandleWindow,
2380      NAME_windows, "Fetch the MS-Windows HWND of the window (if any)"),
2381 #endif
2382   GM(NAME_confirmCentered, 3, "any", T_confirmCentered, getConfirmCenteredWindow,
2383      NAME_modal, "->confirm with frame centered around point"),
2384   GM(NAME_thread, 0, "int", NULL, getThreadWindow,
2385      NAME_thread, "Return system thread-id that owns the window")
2386 };
2387 
2388 /* Resources */
2389 
2390 static classvardecl rc_window[] =
2391 { RC(NAME_background, "colour|pixmap", UXWIN("white", "@_graph_bg"), NULL),
2392   RC(NAME_cursor, "cursor", UXWIN("top_left_arrow", "win_arrow"), NULL),
2393   RC(NAME_pen,              "0..",	     "@_win_pen",      NULL),
2394   RC(NAME_selectionHandles, RC_REFINE,	     "@nil",	       NULL),
2395   RC(NAME_size,		    "size",	     "size(200,100)",  NULL),
2396   RC(NAME_selectionFeedback, NULL,
2397      "when(@colour_display,  colour,  invert)",
2398      NULL),
2399 };
2400 
2401 /* Class Declaration */
2402 
2403 static Name window_termnames[] = { NAME_name };
2404 
2405 ClassDecl(window_decls,
2406           var_window, send_window, get_window, rc_window,
2407           1, window_termnames,
2408           "$Rev$");
2409 
2410 
2411 status
makeClassWindow(Class class)2412 makeClassWindow(Class class)
2413 { declareClass(class, &window_decls);
2414   setLoadStoreFunctionClass(class, loadWindow, storeWindow);
2415 
2416   delegateClass(class, NAME_frame);
2417   delegateClass(class, NAME_tile);
2418   delegateClass(class, NAME_decoration); /* label, scrollbars */
2419   cloneStyleClass(class, NAME_none);
2420   saveStyleVariableClass(class, NAME_device, NAME_normal);
2421   saveStyleVariableClass(class, NAME_currentEvent, NAME_nil);
2422   saveStyleVariableClass(class, NAME_focusEvent, NAME_nil);
2423   setRedrawFunctionClass(class, redrawAreaWindow);
2424 
2425   WindowTable = createHashTable(toInt(32), NAME_none);
2426   grabbedWindows = globalObject(NAME_grabbedWindows, ClassChain, EAV);
2427 
2428   succeed;
2429 }
2430 
2431