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/graphics.h>
37 #include <h/text.h>
38 
39 static status	initOffsetText(TextObj, int);
40 static status	initPositionText(TextObj);
41 static status	initAreaText(TextObj);
42 static status	recomputeText(TextObj t, Name what);
43 static status	get_char_pos_text(TextObj t, Int chr, int *X, int *Y);
44 static status	caretText(TextObj t, Int where);
45 static status	prepareEditText(TextObj t, Name selector);
46 
47 #define Wrapped(t)      ((t)->wrap == NAME_wrap || \
48 			 (t)->wrap == NAME_wrapFixedWidth)
49 #define Before(x, y)    if ( valInt(x) > valInt(y) ) { Int _z = x; x=y; y=_z; }
50 #define Before_i(x, y)  if ( x > y ) { intptr_t _z = x; x=y; y=_z; }
51 #define MakeSel(f, t)   toInt(((valInt(t) & 0xffff) << 16) | \
52 			      (valInt(f) & 0xffff))
53 #define GetSel(s,f,t)	{ *(t) = ((valInt(s) >> 16) & 0xffff); \
54 			  *(f) = (valInt(s) & 0xffff); \
55 			}
56 
57 
58 
59 		/********************************
60 		*            CREATE		*
61 		********************************/
62 
63 static status
initialiseText(TextObj t,CharArray string,Name format,FontObj font)64 initialiseText(TextObj t, CharArray string, Name format, FontObj font)
65 { if ( isDefault(string) )
66     string = CtoCharArray("");
67 
68   initialiseGraphical(t, ZERO, ZERO, ZERO, ZERO);
69 
70   if ( notDefault(format) )
71     assign(t, format,     format);
72   if ( notDefault(font) )
73     assign(t, font,       font);
74   assign(t, underline,	  OFF);
75   assign(t, string,       string);
76   assign(t, margin,	  toInt(100));
77   assign(t, wrap,         NAME_extend);
78   assign(t, position,     newObject(ClassPoint, EAV));
79   assign(t, caret,        getSizeCharArray(string));
80   assign(t, show_caret,   OFF);
81   assign(t, background,   NIL);
82   assign(t, x_offset,	  ZERO);
83   assign(t, x_caret,	  ZERO);
84   assign(t, y_caret,	  ZERO);
85   assign(t, selection,	  NIL);
86 
87   return recomputeText(t, NAME_position);
88 }
89 
90 		/********************************
91 		*            COMPUTE		*
92 		********************************/
93 
94 static status
computeText(TextObj t)95 computeText(TextObj t)
96 { if ( notNil(t->request_compute) )
97   { obtainClassVariablesObject(t);
98 
99     CHANGING_GRAPHICAL(t,
100 	if ( t->request_compute == NAME_position )
101 	  initPositionText(t);
102 	else if ( t->request_compute == NAME_area )
103 	  initAreaText(t);
104 	changedEntireImageGraphical(t));
105 
106     assign(t, request_compute, NIL);
107   }
108 
109   succeed;
110 }
111 
112 
113 static status
recomputeText(TextObj t,Name what)114 recomputeText(TextObj t, Name what)
115 { if ( notNil(t->selection) )		/* normalise the selection */
116   { int from, to;
117     int size = t->string->data.s_size;
118 
119     GetSel(t->selection, &from, &to);
120     if ( from > size || to > size )
121     { if ( from > size ) from = size;
122       if ( from > size ) to = size;
123 
124       assign(t, selection, MakeSel(toInt(from), toInt(to)));
125     }
126   }
127 
128   if ( notNil(t->request_compute) && t->request_compute != what )
129     computeText(t);
130 
131   return requestComputeGraphical(t, what);
132 }
133 
134 
135 
136 		/********************************
137 		*            REDRAW		*
138 		********************************/
139 
140 static status
RedrawAreaText(TextObj t,Area a)141 RedrawAreaText(TextObj t, Area a)
142 { int x, y, w, h;
143 
144   initialiseDeviceGraphical(t, &x, &y, &w, &h);
145 
146   repaintText(t, x, y, w, h);
147   if ( t->pen != ZERO )
148   { r_thickness(valInt(t->pen));
149     r_dash(t->texture);
150     r_box(x, y, w, h, 0, NIL);
151   }
152 
153   return RedrawAreaGraphical(t, a);
154 }
155 
156 
157 void
str_format(PceString out,const PceString in,const int width,const FontObj font)158 str_format(PceString out, const PceString in, const int width, const FontObj font)
159 { int x = 0;
160   int last_is_layout = TRUE;
161 
162   if ( isstrA(in) )			/* 8-bit string */
163   { charA  *s = in->s_textA;
164     charA  *e = &s[in->s_size];
165     charA  *o = out->s_textA;
166     charA *lb = NULL;			/* last-break; */
167 
168     for(;; s++)
169     { *o++ = *s;
170 
171       if ( s == e )
172       { int n = o - out->s_textA - 1;
173 
174 	assert(n <= out->s_size);
175 	out->s_size = n;
176 	return;
177       }
178 
179       if ( !last_is_layout && isspace(*s) )
180 	lb = o-1;
181       last_is_layout = isspace(*s);
182 
183       if ( *s == '\n' )
184 	x = 0;
185       else
186 	x += c_width(*s, font);
187 
188       if ( x > width )
189       { if ( lb )
190 	{ o = lb;
191 	  s = in->s_textA + (lb-out->s_textA);
192 
193 	  while( isspace(s[1]) )
194 	    s++, o++;			/* map (<sp>*)<sp> --> \1\n */
195 	  *o++ = '\n';
196 	  lb = NULL;
197 	  x = 0;
198 	}
199       }
200     }
201   } else				/* 16-bit string */
202   { charW  *s = in->s_textW;
203     charW  *e = &s[in->s_size];
204     charW  *o = out->s_textW;
205     charW *lb = NULL;			/* last-break; */
206 
207     for(;; s++)
208     { *o++ = *s;
209 
210       if ( s == e )
211       { out->s_size = o - out->s_textW - 1;
212 	return;
213       }
214 
215       if ( !last_is_layout && iswspace(*s) )
216 	lb = o-1;
217       last_is_layout = iswspace(*s);
218 
219       if ( *s == '\n' )
220 	x = 0;
221       else
222 	x += c_width(*s, font);
223 
224       if ( x > width )
225       { if ( lb )
226 	{ o = lb;
227 	  s = in->s_textW + (lb-out->s_textW);
228 
229 	  while( iswspace(s[1]) )
230 	    s++, o++;			/* map (<sp>*)<sp> --> \1\n */
231 	  *o++ = '\n';
232 	  lb = NULL;
233 	  x = 0;
234 	}
235       }
236     }
237   }
238 }
239 
240 
241 void
str_one_line(PceString to,PceString from)242 str_one_line(PceString to, PceString from)
243 { int n;
244 
245   for(n=0; n<from->s_size; n++)
246   { unsigned int c = str_fetch(from, n);
247 
248     if      ( c == '\n' ) c = 0xb6;	/* Paragraph sign */
249     else if ( c == '\t' ) c = 0xbb;	/* >> */
250     else if ( c == '\r' ) c = 0xab;	/* << */
251     str_store(to, n, c);
252   }
253 
254   to->s_size = from->s_size;
255 }
256 
257 
258 static void
draw_caret(int x,int y,int w,int h,int active)259 draw_caret(int x, int y, int w, int h, int active)
260 { if ( active )
261   { int cx = x + w/2;
262 
263     r_fillpattern(BLACK_IMAGE, NAME_foreground);
264     r_fill_triangle(cx, y, x, y+h, x+w, y+h);
265   } else
266   { ipoint pts[4];
267     int cx = x + w/2;
268 
269     int cy = y + h/2;
270     int i = 0;
271 
272     pts[i].x = cx;  pts[i].y = y;   i++;
273     pts[i].x = x;   pts[i].y = cy;  i++;
274     pts[i].x = cx;  pts[i].y = y+h; i++;
275     pts[i].x = x+w; pts[i].y = cy;  i++;
276 
277     r_fillpattern(GREY50_IMAGE, NAME_foreground);
278     r_fill_polygon(pts, i);
279   }
280 }
281 
282 
283 #ifndef OL_CURSOR_SIZE
284 #define OL_CURSOR_SIZE	9
285 #endif
286 
287 status
repaintText(TextObj t,int x,int y,int w,int h)288 repaintText(TextObj t, int x, int y, int w, int h)
289 { PceString s = &t->string->data;
290   int b = valInt(t->border);
291   int sf = 0, st = 0;
292   int flags = 0;
293   Style style = NIL;
294 
295   if ( notNil(t->background) )
296   { if ( isDefault(t->background) )
297       r_clear(x, y, w, h);
298     else
299       r_fill(x, y, w, h, t->background);
300   }
301 
302   if ( t->underline == ON )
303     flags |= TXT_UNDERLINED;
304 
305   x += b;
306   y += b;
307   w -= 2*b;
308   h -= 2*b;
309 
310   if ( t->wrap == NAME_clip )
311     d_clip(x, y, w, h);
312 
313   if ( notNil(t->selection) )
314   { GetSel(t->selection, &sf, &st);
315     style = getClassVariableValueObject(t, NAME_selectionStyle);
316   }
317 
318   if ( Wrapped(t) )
319   { LocalString(buf, s->s_iswide, s->s_size+1);
320 
321     DEBUG(NAME_text,
322 	  Cprintf("RedrawAreaText(%s): \"%s\"\n", pp(t), s->s_textA));
323     str_format(buf, s, valInt(t->margin), t->font);
324     if ( notNil(t->selection) )
325       str_selected_string(buf, t->font, sf, st, style,
326 			  x+valInt(t->x_offset), y, w, h,
327 			  t->format, NAME_top);
328     else
329       str_string(buf, t->font,
330 		 x+valInt(t->x_offset), y, w, h,
331 		 t->format, NAME_top, flags);
332   } else
333   { if ( t->wrap == NAME_clip )
334     { LocalString(buf, s->s_iswide, s->s_size+1);
335 
336       str_one_line(buf, s);
337       if ( notNil(t->selection) )
338       { str_selected_string(buf, t->font, sf, st, style,
339 			    x+valInt(t->x_offset), y, w, h,
340 			    t->format, NAME_top);
341       } else
342       { str_string(buf, t->font,
343 		   x+valInt(t->x_offset), y, w, h,
344 		   t->format, NAME_top, flags);
345       }
346     } else
347     { if ( notNil(t->selection) )
348       { str_selected_string(s, t->font, sf, st, style,
349 			    x+valInt(t->x_offset), y, w, h,
350 			    t->format, NAME_top);
351       } else
352       { str_string(s, t->font,
353 		   x+valInt(t->x_offset), y, w, h,
354 		   t->format, NAME_top, flags);
355       }
356     }
357   }
358 
359   if ( t->wrap == NAME_clip )
360     d_clip_done();
361 
362   if ( t->show_caret != OFF )
363   { int fh = valInt(getAscentFont(t->font));
364     int active = (t->show_caret == ON);
365     Any colour = getClassVariableValueClass(ClassTextCursor,
366 					    active ? NAME_colour
367 					           : NAME_inactiveColour);
368     Any old = r_colour(colour);
369 
370     draw_caret(valInt(t->x_caret) - OL_CURSOR_SIZE/2 + x - b,
371 	       valInt(t->y_caret) + y + fh - b - 3,
372 	       OL_CURSOR_SIZE, OL_CURSOR_SIZE,
373 	       active);
374 
375     r_colour(old);
376   }
377 
378   succeed;
379 }
380 
381 
382 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
383 To avoid texts moving  on type actions  a position is  maintained.  If
384 the string changes  the area is recomputed  relative to  this position
385 argument.  If the text gets a `change area'  request it will recompute
386 the position attribute to be used in subsequent string changes.
387 
388 initAreaText()		recomputes the area from the position after the
389 			string or font has been changed.
390 initPositionText()	recomputes the position from the area after the
391 			area has been changed from outside.
392 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
393 
394 static status
initAreaText(TextObj t)395 initAreaText(TextObj t)
396 { int tw, x, y, w, h;
397   Point pos = t->position;
398   PceString s = &t->string->data;
399   int size = s->s_size;
400   int b = valInt(t->border);
401 
402   if ( valInt(t->caret) < 0 )
403     assign(t, caret, ZERO);
404   if ( valInt(t->caret) > size )
405     assign(t, caret, toInt(size));
406 
407   if ( Wrapped(t) )
408   { LocalString(buf, s->s_iswide, s->s_size + MAX_WRAP_LINES);
409 
410     str_format(buf, s, valInt(t->margin), t->font);
411     str_size(buf, t->font, &tw, &h);
412     if ( t->wrap == NAME_wrapFixedWidth && tw < valInt(t->margin) )
413       tw = valInt(t->margin);
414   } else
415   { if ( t->wrap == NAME_clip )
416     { LocalString(buf, s->s_iswide, s->s_size + 1);
417 
418       str_one_line(buf, s);
419       str_size(buf, t->font, &tw, &h);
420     } else
421     { str_size(s, t->font, &tw, &h);
422     }
423   }
424 
425   if ( t->wrap == NAME_clip )
426     w = valInt(t->area->w) - 2*b;
427   else
428     w = tw;
429 
430   if ( t->format == NAME_right )
431   { x = valInt(pos->x) - w;
432     y = valInt(pos->y);
433   } else if ( t->format == NAME_center )
434   { x = valInt(pos->x) - w/2;
435     y = valInt(pos->y) - h/2;
436   } else
437   { x = valInt(pos->x);
438     y = valInt(pos->y);
439   }
440 
441   x -= b; y -= b; w += 2*b; h+= 2*b;
442 
443   assign(t->area, x, toInt(x));
444   assign(t->area, y, toInt(y));
445   assign(t->area, w, toInt(w));
446   assign(t->area, h, toInt(h));
447 
448   return initOffsetText(t, tw);
449 }
450 
451 
452 static status
initPositionText(TextObj t)453 initPositionText(TextObj t)
454 { int tw, x, y, w, h;
455   Point pos = t->position;
456   PceString s = &t->string->data;
457   int b = valInt(t->border);
458 
459   if ( Wrapped(t) )
460   { LocalString(buf, s->s_iswide, s->s_size + MAX_WRAP_LINES);
461 
462     str_format(buf, s, valInt(t->margin), t->font);
463     str_size(buf, t->font, &tw, &h);
464     if ( t->wrap == NAME_wrapFixedWidth && tw < valInt(t->margin) )
465       tw = valInt(t->margin);
466   } else
467   { if ( t->wrap == NAME_clip )
468     { LocalString(buf, s->s_iswide, s->s_size + 1);
469 
470       str_one_line(buf, s);
471       str_size(buf, t->font, &tw, &h);
472     } else
473     { str_size(s, t->font, &tw, &h);
474     }
475   }
476 
477   if ( t->wrap == NAME_clip )
478     w = valInt(t->area->w) - 2*b;
479   else
480     w = tw;
481 
482   if ( equalName(t->format, NAME_left) )
483   { x = valInt(t->area->x);
484     y = valInt(t->area->y) + b;
485   } else if ( equalName(t->format, NAME_right) )
486   { x = valInt(t->area->x) + w;
487     y = valInt(t->area->y) + b;
488   } else
489   { x = valInt(t->area->x) + w/2;
490     y = valInt(t->area->y) + h/2;
491   }
492 
493   x += b;
494   y += b;				/* was missing? */
495   w += 2*b;
496   h += 2*b;
497 
498   assign(pos, x, toInt(x));
499   assign(pos, y, toInt(y));
500   assign(t->area, w, toInt(w));
501   assign(t->area, h, toInt(h));
502 
503   return initOffsetText(t, tw);
504 }
505 
506 
507 static int
initOffsetText(TextObj t,int tw)508 initOffsetText(TextObj t, int tw)
509 { if ( t->wrap != NAME_clip )
510   { int x, y;
511 
512     assign(t, x_offset, ZERO);
513     get_char_pos_text(t, DEFAULT, &x, &y);
514     assign(t, x_caret, toInt(x));
515     assign(t, y_caret, toInt(y));
516   } else
517   { int x, y, w = valInt(t->area->w) - valInt(t->border), shift;
518     int xoff;
519 
520     if ( tw <= w || t->caret == ZERO )
521       assign(t, x_offset, ZERO);
522     else if ( t->caret == getSizeCharArray(t->string) )
523       assign(t, x_offset, toInt(w - tw));
524 
525     xoff = valInt(t->x_offset);
526 
527     get_char_pos_text(t, DEFAULT, &x, &y);
528     if ( x >= w )
529       shift = w - x;
530     else if ( x < 0 )
531       shift = - x;
532     else
533       shift = 0;
534 
535     if ( shift )
536     { xoff += shift;
537       x += shift;
538       assign(t, x_offset, toInt(xoff));
539     }
540     assign(t, x_caret, toInt(x));
541     assign(t, y_caret, toInt(y));
542   }
543 
544   succeed;
545 }
546 
547 
548 static status
resizeText(TextObj t,Real xfactor,Real yfactor,Point origin)549 resizeText(TextObj t, Real xfactor, Real yfactor, Point origin)
550 { float xf, yf;
551   int ox = valInt(t->position->x);
552   int oy = valInt(t->position->y);
553   int nx, ny;
554 
555   init_resize_graphical(t, xfactor, yfactor, origin, &xf, &yf, &ox, &oy);
556   if ( xf == 1.0 && yf == 1.0 )
557     succeed;
558 
559   nx = ox + rfloat((float) (valInt(t->position->x)-ox) * xf);
560   ny = oy + rfloat((float) (valInt(t->position->y)-oy) * yf);
561   assign(t->position, x, toInt(nx));
562   assign(t->position, y, toInt(ny));
563 
564   return recomputeText(t, NAME_area);
565 }
566 
567 
568 /*  Determine the position of a character  in  pixels.   It  returns the
569     coordinate  of  the  upper left corner of the character.  By default
570     the position of the caret is returned.
571 
572  ** Tue Nov  8 17:24:58 1988  jan@swivax.UUCP (Jan Wielemaker)  */
573 
574 static Point
getCharacterPositionText(TextObj t,Int chr)575 getCharacterPositionText(TextObj t, Int chr)
576 { int x, y;
577 
578   get_char_pos_text(t, chr, &x, &y);
579 
580   answer(answerObject(ClassPoint, toInt(x), toInt(y), EAV));
581 }
582 
583 
584 static void
get_char_pos_helper(TextObj t,PceString s,int caret,int * cx,int * cy)585 get_char_pos_helper(TextObj t, PceString s, int caret, int *cx, int *cy)
586 { int b = valInt(t->border);
587   int ch  = valInt(getHeightFont(t->font));
588   int w   = abs((int)valInt(t->area->w));
589   int lw, sl;
590 
591   if ( (sl = str_next_rindex(s, caret-1, '\n')) < 0 )
592   { sl = 0;
593   } else
594   { sl++;
595     *cy += (str_lineno(s, sl)-1) * ch;
596   }
597 
598   lw = str_width(s, sl, caret, t->font);
599   w -= 2 * b;
600 
601   if ( t->format == NAME_left )
602   { *cx = lw;
603   } else
604   { int el;
605     int rw;
606 
607     if ( (el = str_next_index(s, caret, '\n')) < 0 )
608       el = s->s_size;
609     rw = str_width(s, caret, el, t->font);
610 
611     if ( t->format == NAME_center )
612       *cx = w/2 - (lw+rw)/2 + lw;
613     else				/* right */
614       *cx = w - rw;
615   }
616 }
617 
618 
619 static status
get_char_pos_text(TextObj t,Int chr,int * X,int * Y)620 get_char_pos_text(TextObj t, Int chr, int *X, int *Y)
621 { int caret = (isDefault(chr) ? valInt(t->caret) : valInt(chr));
622   int cx = 0;			/* clang doesn't see this is not needed */
623   int cy = 0;
624   PceString s = &t->string->data;
625   int b = valInt(t->border);
626 
627   if ( Wrapped(t) )
628   { LocalString(buf, s->s_iswide, Wrapped(t) ? s->s_size + MAX_WRAP_LINES : 0);
629 
630     str_format(buf, s, valInt(t->margin), t->font);
631     get_char_pos_helper(t, s, caret, &cx, &cy);
632   } else if ( t->wrap == NAME_clip )
633   { LocalString(buf, s->s_iswide, s->s_size + 1);
634 
635     str_one_line(buf, s);
636     get_char_pos_helper(t, s, caret, &cx, &cy);
637   }
638 
639   *X = cx + valInt(t->x_offset) + b;
640   *Y = cy + b;
641 
642   succeed;
643 }
644 
645 
646 Int
get_pointed_text(TextObj t,int x,int y)647 get_pointed_text(TextObj t, int x, int y)
648 { PceString s = &t->string->data;
649   int ch = valInt(getHeightFont(t->font));
650   int b = valInt(t->border);
651   int cw, w;
652   int caret = 0, el;
653   int line = (y-b) / ch;			/* line for caret */
654   string buf;
655 
656   if ( s->s_size == 0 )
657     answer(ZERO);
658 
659   x -= b;
660   if ( Wrapped(t) )
661   { str_init(&buf, s, alloca(str_allocsize(s)));
662     str_format(&buf, s, valInt(t->margin), t->font);
663     s = &buf;
664   }
665 
666   /* Find the start of the line pointed at by pos. */
667 
668   while(line-- > 0)
669   { int c2;
670 
671     if ( (c2 = str_next_index(s, caret, '\n')) < 0 )
672       break;
673     caret = c2+1;
674   }
675   if ( caret > s->s_size )
676     caret = s->s_size;
677   if ( (el = str_next_index(s, caret, '\n')) < 0 )
678     el = s->s_size;
679 
680   /* caret = start of line, el = end of line */
681 
682   if ( t->format == NAME_left )
683     w = 0;
684   else
685   { int lw = str_width(s, caret, el, t->font);
686 
687     if ( t->format == NAME_center )
688       w = (valInt(t->area->w) - lw)/2 - b;
689     else
690       w = valInt(t->area->w) - lw - 2*b;
691   }
692   w += valInt(t->x_offset);
693 
694   if ( caret < el-1 )
695   { for( cw = c_width(str_fetch(s, caret), t->font);
696 	 x > w + cw/2;
697 	 caret++, w += cw, cw = c_width(str_fetch(s, caret), t->font) )
698     { if ( caret >= el )
699 	break;
700     }
701   }
702 
703   answer(toInt(caret));
704 }
705 
706 
707 static Int
getPointedText(TextObj t,Point pos)708 getPointedText(TextObj t, Point pos)
709 { int x = valInt(pos->x);
710   int y = valInt(pos->y);
711 
712   return get_pointed_text(t, x, y);
713 }
714 
715 		/********************************
716 		*          ATTRIBUTES		*
717 		********************************/
718 
719 static status
backgroundText(TextObj t,Any bg)720 backgroundText(TextObj t, Any bg)
721 { if ( t->background != bg)
722   { CHANGING_GRAPHICAL(t,
723 		       assign(t, background, bg);
724 		       changedEntireImageGraphical(t));
725   }
726 
727   succeed;
728 }
729 
730 
731 static status
underlineText(TextObj t,BoolObj underline)732 underlineText(TextObj t, BoolObj underline)
733 { if ( t->underline != underline )
734   { CHANGING_GRAPHICAL(t, assign(t, underline, underline);
735 		       changedEntireImageGraphical(t));
736   }
737 
738   succeed;
739 }
740 
741 
742 status
transparentText(TextObj t,BoolObj val)743 transparentText(TextObj t, BoolObj val)
744 { Any bg = (val == ON ? NIL : DEFAULT);
745 
746   return backgroundText(t, bg);
747 }
748 
749 
750 static BoolObj
getTransparentText(TextObj t)751 getTransparentText(TextObj t)
752 { answer(isNil(t->background) ? ON : OFF);
753 }
754 
755 
756 
757 status
fontText(TextObj t,FontObj font)758 fontText(TextObj t, FontObj font)
759 { if (t->font != font)
760   { assign(t, font, font);
761     recomputeText(t, NAME_area);
762   }
763   succeed;
764 }
765 
766 
767 static status
formatText(TextObj t,Name format)768 formatText(TextObj t, Name format)
769 { if (t->format != format)
770   { assign(t, format, format);
771     recomputeText(t, NAME_position);
772   }
773   succeed;
774 }
775 
776 
777 status
borderText(TextObj t,Int border)778 borderText(TextObj t, Int border)
779 { if (t->border != border)
780   { assign(t, border, border);
781     recomputeText(t, NAME_area);
782   }
783   succeed;
784 }
785 
786 
787 status
stringText(TextObj t,CharArray s)788 stringText(TextObj t, CharArray s)
789 { if ( t->string != s )
790   { prepareEditText(t, DEFAULT);
791 
792     valueString((StringObj) t->string, s);
793     caretText(t, DEFAULT);
794     recomputeText(t, NAME_area);
795   }
796 
797   succeed;
798 }
799 
800 
801 status
showCaretText(TextObj t,Any val)802 showCaretText(TextObj t, Any val)
803 { if ( t->show_caret == val )
804     succeed;
805 
806   CHANGING_GRAPHICAL(t,
807 		     assign(t, show_caret, val);
808 		     changedEntireImageGraphical(t));
809 
810   succeed;
811 }
812 
813 		 /*******************************
814 		 *	     SELECTION		*
815 		 *******************************/
816 
817 static status
selectionText(TextObj t,Int from,Int to)818 selectionText(TextObj t, Int from, Int to)
819 { int changed = FALSE;
820 
821   if ( from == to )
822     from = NIL;
823 
824   if ( isNil(from) )
825   { if ( notNil(t->selection) )
826     { assign(t, selection, NIL);
827       changed++;
828     }
829   } else
830   { int ofrom, oto;
831     Int new;
832 
833     if ( notNil(t->selection) )
834     { GetSel(t->selection, &ofrom, &oto);
835     } else
836       ofrom = oto = 0;
837 
838     if ( isDefault(from) )
839       from = toInt(ofrom);
840     if ( isDefault(to) )
841       to = toInt(oto);
842 
843     Before(from, to);
844     new = MakeSel(from, to);
845 
846     if ( new != t->selection )
847     { assign(t, selection, MakeSel(from, to));
848       changed++;
849     }
850   }
851 
852   if ( changed )
853     changedEntireImageGraphical(t);
854 
855   succeed;
856 }
857 
858 
859 static Point
getSelectionText(TextObj t)860 getSelectionText(TextObj t)
861 { if ( notNil(t->selection) )
862   { int from, to;
863 
864     GetSel(t->selection, &from, &to);
865 
866     answer(answerObject(ClassPoint, toInt(from), toInt(to), EAV));
867   }
868 
869   fail;
870 }
871 
872 
873 static StringObj
getSelectedTextText(TextObj t)874 getSelectedTextText(TextObj t)
875 { if ( notNil(t->selection) )
876   { int from, to;
877 
878     GetSel(t->selection, &from, &to);
879     answer(getSubString((StringObj)t->string, toInt(from), toInt(to)));
880   }
881 
882   fail;
883 }
884 
885 
886 static status
copyText(TextObj t)887 copyText(TextObj t)
888 { StringObj s = getSelectedTextText(t);
889   DisplayObj d = getDisplayGraphical((Graphical)t);
890 
891   if ( !d )
892   { if ( instanceOfObject(EVENT->value, ClassEvent) )
893       d = getDisplayEvent(EVENT->value);
894   }
895 
896   if ( s && d )
897     return send(d, NAME_copy, s, EAV);
898 
899   fail;
900 }
901 
902 
903 static status
deleteSelectionText(TextObj t)904 deleteSelectionText(TextObj t)
905 { if ( notNil(t->selection) )
906   { int from, to;
907 
908     GetSel(t->selection, &from, &to);
909 
910     prepareEditText(t, DEFAULT);
911     deleteString((StringObj)t->string, toInt(from), toInt(to-from));
912     assign(t, selection, NIL);
913     if ( valInt(t->caret) > from )
914       caretText(t, toInt(from));
915     recomputeText(t, NAME_area);
916   }
917 
918   succeed;
919 }
920 
921 
922 static status
cutText(TextObj t)923 cutText(TextObj t)
924 { if ( send(t, NAME_copy, EAV) )
925   { int from, to;
926 
927     GetSel(t->selection, &from, &to);
928     return deleteSelectionText(t);
929   }
930 
931   fail;
932 }
933 
934 
935 
936 
937 		 /*******************************
938 		 *	     GEOMETRY		*
939 		 *******************************/
940 
941 
942 static status
geometryText(TextObj t,Int x,Int y,Int w,Int h)943 geometryText(TextObj t, Int x, Int y, Int w, Int h)
944 { Int ox = t->area->x;
945   Int oy = t->area->y;
946   Point p = t->position;
947   Area a = t->area;
948 
949   if ( Wrapped(t) && notDefault(w) )
950   { assign(t, margin, w);
951     CHANGING_GRAPHICAL(t,
952 		       initAreaText(t);
953 		       setArea(t->area, x, y, DEFAULT, DEFAULT));
954   } else
955   { if ( t->wrap != NAME_clip )
956       w = (Int) DEFAULT;
957     geometryGraphical(t, x, y, w, DEFAULT);
958   }
959 
960   assign(p, x, toInt(valInt(p->x) + valInt(a->x) - valInt(ox)));
961   assign(p, y, toInt(valInt(p->y) + valInt(a->y) - valInt(oy)));
962   if ( notDefault(w) )
963   { int tw, h;
964 
965     if ( isDefault(t->font) )
966       obtainClassVariablesObject(t);		/* resolve the font */
967     str_size(&t->string->data, t->font, &tw, &h);
968     initOffsetText(t, tw);
969   }
970 
971   succeed;
972 }
973 
974 
975 static status
updateShowCaretText(TextObj t)976 updateShowCaretText(TextObj t)
977 { if ( t->show_caret != OFF )
978   { PceWindow sw = getWindowGraphical((Graphical)t);
979     int active = (sw && sw->input_focus == ON);
980 
981     showCaretText(t, active ? (Any)ON : (Any)NAME_passive);
982   }
983 
984   succeed;
985 }
986 
987 
988 static status
eventText(TextObj t,EventObj ev)989 eventText(TextObj t, EventObj ev)
990 { if ( eventGraphical(t, ev) )
991     succeed;
992 
993   if ( isAEvent(ev, NAME_focus) )
994   { if ( isAEvent(ev, NAME_obtainKeyboardFocus) )
995       showCaretText(t, ON);
996     else if ( isAEvent(ev, NAME_releaseKeyboardFocus) )
997       showCaretText(t, OFF);
998 
999     return updateShowCaretText(t);
1000   }
1001 
1002   if ( t->show_caret == ON && isAEvent(ev, NAME_keyboard) )
1003     return send(t, NAME_typed, ev, EAV);
1004 
1005   fail;
1006 }
1007 
1008 
1009 static status
typedText(TextObj t,EventId id)1010 typedText(TextObj t, EventId id)
1011 { return typedKeyBinding(KeyBindingText(), id, (Graphical) t);
1012 }
1013 
1014 
1015 static int
start_of_line(PceString s,int n)1016 start_of_line(PceString s, int n)
1017 { if ( n > 0 && str_fetch(s, n) == '\n' )
1018     n--;
1019 
1020   n = str_next_rindex(s, n, '\n') + 1; /* returns -1 on not found! */
1021 
1022   return n;
1023 }
1024 
1025 
1026 static int
end_of_line(PceString s,int n)1027 end_of_line(PceString s, int n)
1028 { if ( (n = str_next_index(s, n, '\n')) < 0 )
1029     n = s->s_size;
1030 
1031   return n;
1032 }
1033 
1034 
1035 static int
forward_word(PceString s,int i,int n)1036 forward_word(PceString s, int i, int n)
1037 { while( n-- > 0 && i < s->s_size )
1038   { while( i < s->s_size && !isalnum(str_fetch(s, i)) ) i++;
1039     while( i < s->s_size && isalnum(str_fetch(s, i)) ) i++;
1040   }
1041 
1042   return i;
1043 }
1044 
1045 
1046 static int
backward_word(PceString s,int i,int n)1047 backward_word(PceString s, int i, int n)
1048 { while( n-- > 0 && i > 0 )
1049   { i--;
1050     while( i > 0 && !isalnum(str_fetch(s, i)) ) i--;
1051     while( i > 0 && isalnum(str_fetch(s, i-1)) ) i--;
1052   }
1053 
1054   return i;
1055 }
1056 
1057 
1058 		/********************************
1059 		*   INTERACTIVE EDIT COMMANDS   *
1060 		********************************/
1061 
1062 #define UArg(t)	(isDefault(arg) ? 1 : valInt(arg))
1063 
1064 static void
deselectText(TextObj t)1065 deselectText(TextObj t)
1066 { if ( notNil(t->selection) )
1067     selectionText(t, NIL, DEFAULT);
1068 }
1069 
1070 
1071 static status
caretText(TextObj t,Int where)1072 caretText(TextObj t, Int where)
1073 { int size = t->string->data.s_size;
1074 
1075   if ( isDefault(where) || valInt(where) >= size )
1076   { where = toInt(size);
1077   } else if ( valInt(where) < 0 )
1078   { where = ZERO;
1079   }
1080   assign(t, caret, where);
1081   if ( t->show_caret == ON )
1082     recomputeText(t, NAME_area);
1083 
1084   succeed;
1085 }
1086 
1087 
1088 static status
forwardCharText(TextObj t,Int arg)1089 forwardCharText(TextObj t, Int arg)
1090 { deselectText(t);
1091 
1092   return caretText(t, add(t->caret, toInt(UArg(t))));
1093 }
1094 
1095 
1096 static status
backwardCharText(TextObj t,Int arg)1097 backwardCharText(TextObj t, Int arg)
1098 { deselectText(t);
1099 
1100   return caretText(t, sub(t->caret, toInt(UArg(t))));
1101 }
1102 
1103 
1104 static status
nextLineText(TextObj t,Int arg,Int column)1105 nextLineText(TextObj t, Int arg, Int column)
1106 { int cx, cy;
1107   int fw, fh;
1108 
1109   deselectText(t);
1110   fw = valInt(getExFont(t->font));
1111   fh = valInt(getHeightFont(t->font));
1112   get_char_pos_text(t, DEFAULT, &cx, &cy);
1113   cy += UArg(t) * fh + fh/2;
1114   cx  = (isDefault(column) ? cx + fw/2 : valInt(column));
1115 
1116   return caretText(t, get_pointed_text(t, cx, cy));
1117 }
1118 
1119 
1120 static status
previousLineText(TextObj t,Int arg,Int column)1121 previousLineText(TextObj t, Int arg, Int column)
1122 { deselectText(t);
1123 
1124   return nextLineText(t, toInt(-UArg(t)), column);
1125 }
1126 
1127 
1128 static Int
getColumnText(TextObj t)1129 getColumnText(TextObj t)
1130 { int cx, cy;
1131   int fw;
1132 
1133   fw = valInt(getExFont(t->font));
1134   get_char_pos_text(t, DEFAULT, &cx, &cy);
1135 
1136   answer(toInt(cx + fw/2));
1137 }
1138 
1139 
1140 static status
endOfLineText(TextObj t,Int arg)1141 endOfLineText(TextObj t, Int arg)
1142 { PceString s = &t->string->data;
1143   int caret = valInt(t->caret);
1144   int n;
1145 
1146   deselectText(t);
1147   caret = end_of_line(s, caret);
1148   for(n = UArg(t)-1; caret < t->string->data.s_size && n > 0; n--)
1149   { caret++;
1150     caret = end_of_line(s, caret);
1151   }
1152   return caretText(t, toInt(caret));
1153 }
1154 
1155 
1156 static status
beginningOfLineText(TextObj t,Int arg)1157 beginningOfLineText(TextObj t, Int arg)
1158 { PceString s = &t->string->data;
1159   int caret = valInt(t->caret);
1160   int n;
1161 
1162   deselectText(t);
1163   caret = start_of_line(s, caret);
1164   for(n = UArg(t)-1; caret > 0 && n > 0; n--)
1165   { caret--;
1166     caret = start_of_line(s, caret);
1167   }
1168   return caretText(t, toInt(caret));
1169 }
1170 
1171 
1172 static status
forwardWordText(TextObj t,Int arg)1173 forwardWordText(TextObj t, Int arg)
1174 { int caret = valInt(t->caret);
1175 
1176   deselectText(t);
1177   caret = forward_word(&t->string->data, caret, UArg(t));
1178   return caretText(t, toInt(caret));
1179 }
1180 
1181 
1182 static status
backwardWordText(TextObj t,Int arg)1183 backwardWordText(TextObj t, Int arg)
1184 { int caret = valInt(t->caret);
1185 
1186   deselectText(t);
1187   caret = backward_word(&t->string->data, caret, UArg(t));
1188   return caretText(t, toInt(caret));
1189 }
1190 
1191 
1192 		 /*******************************
1193 		 *	  EDIT COMMANDS		*
1194 		 *******************************/
1195 
1196 static void
prepareInsertText(TextObj t)1197 prepareInsertText(TextObj t)
1198 { if ( !instanceOfObject(t->string, ClassString) )
1199     assign(t, string, newObject(ClassString, name_procent_s,
1200 				t->string, EAV));
1201 
1202   if ( getClassVariableValueObject(t, NAME_insertDeletesSelection) == ON )
1203     deleteSelectionText(t);
1204 }
1205 
1206 
1207 static status
prepareEditText(TextObj t,Name selector)1208 prepareEditText(TextObj t, Name selector)
1209 { if ( notDefault(selector) &&
1210        !getSendMethodClass(ClassString, selector) )
1211     fail;
1212 
1213   if ( !instanceOfObject(t->string, ClassString) )
1214     assign(t, string, newObject(ClassString, name_procent_s,
1215 				t->string, EAV));
1216 
1217   selectionText(t, NIL, DEFAULT);
1218   succeed;
1219 }
1220 
1221 
1222 status
pasteText(TextObj t,Name which)1223 pasteText(TextObj t, Name which)
1224 { CharArray str;
1225   Any selection;
1226   DisplayObj d = CurrentDisplay(t);
1227 
1228   if ( d &&
1229        (selection=get(d, NAME_paste, which, EAV)) &&
1230        (str=checkType(selection, TypeCharArray, NIL)) )
1231   { prepareInsertText(t);
1232     insertString((StringObj) t->string, t->caret, str);
1233     caretText(t, add(t->caret, getSizeCharArray(str)));
1234     doneObject(str);
1235     return recomputeText(t, NAME_area);
1236   }
1237 
1238   fail;
1239 }
1240 
1241 
1242 static status
backwardDeleteCharText(TextObj t,Int arg)1243 backwardDeleteCharText(TextObj t, Int arg)
1244 { int caret = valInt(t->caret);
1245   int len  = UArg(t);
1246   int from = (len > 0 ? caret - len : caret);
1247   int size = t->string->data.s_size;
1248 
1249   deselectText(t);
1250 
1251   len = abs(len);
1252   if ( from < 0 )
1253   { len += from;
1254     from = 0;
1255   }
1256   if ( from + len > size )
1257     len = size - from;
1258 
1259   if ( len > 0 )
1260   { caretText(t, toInt(from));
1261     prepareEditText(t, DEFAULT);
1262     deleteString((StringObj) t->string, toInt(from), toInt(len));
1263     return recomputeText(t, NAME_area);
1264   }
1265 
1266   succeed;
1267 }
1268 
1269 
1270 static status
deleteCharText(TextObj t,Int arg)1271 deleteCharText(TextObj t, Int arg)
1272 { return backwardDeleteCharText(t, toInt(-UArg(t)));
1273 }
1274 
1275 
1276 static status
cutOrDeleteCharText(TextObj t,Int arg)1277 cutOrDeleteCharText(TextObj t, Int arg)
1278 { if ( notNil(t->selection) && isDefault(arg) )
1279     return cutText(t);
1280   else
1281     return deleteCharText(t, arg);
1282 }
1283 
1284 
1285 static status
cutOrBackwardDeleteCharText(TextObj t,Int arg)1286 cutOrBackwardDeleteCharText(TextObj t, Int arg)
1287 { if ( notNil(t->selection) && isDefault(arg) )
1288     return cutText(t);
1289   else
1290     return backwardDeleteCharText(t, arg);
1291 }
1292 
1293 
1294 static status
killLineText(TextObj t,Int arg)1295 killLineText(TextObj t, Int arg)
1296 { PceString s = &t->string->data;
1297   int caret = valInt(t->caret);
1298   int end, n;
1299 
1300   deselectText(t);
1301 
1302   if ( isDefault(arg) && str_fetch(s, caret) == '\n' )
1303     return deleteCharText(t, DEFAULT);
1304 
1305   end = end_of_line(s, caret);
1306   if ( notDefault(arg) )
1307     for( n=UArg(t); end < s->s_size && n > 0; n--, end++ )
1308       end = end_of_line(s, end);
1309 
1310   prepareEditText(t, DEFAULT);
1311   deleteString((StringObj) t->string, t->caret, toInt(end-caret));
1312   return recomputeText(t, NAME_area);
1313 }
1314 
1315 
1316 static status
clearText(TextObj t)1317 clearText(TextObj t)
1318 { deselectText(t);
1319 
1320   prepareEditText(t, DEFAULT);
1321   deleteString((StringObj) t->string, ZERO, DEFAULT);
1322   caretText(t, ZERO);
1323   return recomputeText(t, NAME_area);
1324 }
1325 
1326 
1327 static status
insertText(TextObj t,Int where,CharArray str)1328 insertText(TextObj t, Int where, CharArray str)
1329 { if ( isDefault(where) )
1330     where = t->caret;
1331 
1332   prepareEditText(t, DEFAULT);
1333   insertString((StringObj)t->string, where, str);
1334   caretText(t, add(where, getSizeCharArray(str)));
1335 
1336   return recomputeText(t, NAME_area);
1337 }
1338 
1339 
1340 static status
insertSelfText(TextObj t,Int times,Int chr)1341 insertSelfText(TextObj t, Int times, Int chr)
1342 { wint_t c;
1343   int tms;
1344 
1345   if ( isDefault(times) )
1346     times = ONE;
1347   tms = valInt(times);
1348 
1349   if ( isDefault(chr) )
1350   { EventObj ev = EVENT->value;
1351 
1352     if ( instanceOfObject(ev, ClassEvent) && isAEvent(ev, NAME_printable) )
1353       c = valInt(getIdEvent(ev));
1354     else
1355       return errorPce(t, NAME_noCharacter);
1356   } else
1357     c = valInt(chr);
1358 
1359   prepareInsertText(t);
1360 
1361   { LocalString(buf, c > 0xff, tms);
1362     int i;
1363 
1364     for(i=0; i<tms; i++)
1365       str_store(buf, i, c);
1366     buf->s_size = i;
1367 
1368     str_insert_string((StringObj) t->string, t->caret, buf);
1369     caretText(t, add(t->caret, times));
1370 
1371     return recomputeText(t, NAME_area);
1372   }
1373 }
1374 
1375 
1376 static status
newlineText(TextObj t,Int arg)1377 newlineText(TextObj t, Int arg)
1378 { return insertSelfText(t, arg, toInt('\n'));
1379 }
1380 
1381 
1382 static status
openLineText(TextObj t,Int arg)1383 openLineText(TextObj t, Int arg)
1384 { int tms = UArg(t);
1385 
1386   if ( tms > 0 )
1387   { PceString nl = str_nl(&t->string->data);
1388     LocalString(buf, t->string->data.s_iswide, nl->s_size * tms);
1389     int i;
1390 
1391     for(i=0; i<tms; i++)
1392       str_ncpy(buf, i * nl->s_size, nl, 0, nl->s_size);
1393     buf->s_size = nl->s_size * tms;
1394 
1395     prepareInsertText(t);
1396     str_insert_string((StringObj) t->string, t->caret, buf);
1397     recomputeText(t, NAME_area);
1398   }
1399 
1400   succeed;
1401 }
1402 
1403 
1404 static status
gosmacsTransposeText(TextObj t)1405 gosmacsTransposeText(TextObj t)
1406 { int caret = valInt(t->caret);
1407 
1408   if ( caret >= 2 )
1409   { wint_t tmp;
1410     PceString s;
1411 
1412     deselectText(t);
1413     prepareEditText(t, DEFAULT);
1414     s = &((StringObj)t->string)->data;
1415     tmp = str_fetch(s, caret-2);
1416     str_store(s, caret-2, str_fetch(s, caret-1));
1417     str_store(s, caret-1, tmp);
1418     return recomputeText(t, NAME_area);
1419   }
1420 
1421   fail;
1422 }
1423 
1424 
1425 static status
transposeCharsText(TextObj t)1426 transposeCharsText(TextObj t)
1427 { int caret = valInt(t->caret);
1428 
1429   if ( caret >= 1 )
1430   { wint_t tmp;
1431     PceString s;
1432 
1433     deselectText(t);
1434     prepareEditText(t, DEFAULT);
1435     s = &((StringObj)t->string)->data;
1436     tmp = str_fetch(s, caret-1);
1437     str_store(s, caret-1, str_fetch(s, caret));
1438     str_store(s, caret, tmp);
1439     return recomputeText(t, NAME_area);
1440   }
1441 
1442   fail;
1443 }
1444 
1445 
1446 static status
killWordText(TextObj t,Int arg)1447 killWordText(TextObj t, Int arg)
1448 { int caret = valInt(t->caret);
1449 
1450   deselectText(t);
1451   prepareEditText(t, DEFAULT);
1452   caret = forward_word(&t->string->data, caret, UArg(t));
1453   deleteString((StringObj) t->string, t->caret, sub(toInt(caret), t->caret));
1454   return recomputeText(t, NAME_area);
1455 }
1456 
1457 
1458 static status
backwardKillWordText(TextObj t,Int arg)1459 backwardKillWordText(TextObj t, Int arg)
1460 { Int caret = t->caret;
1461 
1462   deselectText(t);
1463   prepareEditText(t, DEFAULT);
1464   caret = toInt(backward_word(&t->string->data, valInt(caret), UArg(t)));
1465   deleteString((StringObj) t->string, caret, sub(t->caret, caret));
1466   caretText(t, caret);
1467   return recomputeText(t, NAME_area);
1468 }
1469 
1470 
1471 static status
formatCenterText(TextObj t)1472 formatCenterText(TextObj t)
1473 { deselectText(t);
1474   return formatText(t, NAME_center);
1475 }
1476 
1477 
1478 static status
formatLeftText(TextObj t)1479 formatLeftText(TextObj t)
1480 { deselectText(t);
1481   return formatText(t, NAME_left);
1482 }
1483 
1484 
1485 static status
formatRightText(TextObj t)1486 formatRightText(TextObj t)
1487 { deselectText(t);
1488   return formatText(t, NAME_right);
1489 }
1490 
1491 
1492 		/********************************
1493 		*	HANDLING LONG TEXT	*
1494 		********************************/
1495 
1496 status
lengthText(TextObj t,Int l)1497 lengthText(TextObj t, Int l)
1498 { int fw, len;
1499 
1500   if ( isDefault(t->font) )
1501     obtainClassVariablesObject(t);
1502 
1503   fw = valInt(getExFont(t->font));
1504   len = (valInt(l)+1) * fw;
1505 
1506   return marginText(t, toInt(len), NAME_clip);
1507 }
1508 
1509 
1510 status
marginText(TextObj t,Int width,Name wrap)1511 marginText(TextObj t, Int width, Name wrap)
1512 { int changed = FALSE;
1513 
1514   if ( isNil(width) )
1515   { width = toInt(100);			/* initial default */
1516     wrap = NAME_extend;
1517   } else if ( isDefault(wrap) )
1518   { wrap = NAME_wrap;
1519   }
1520 
1521   if ( t->wrap != wrap )
1522   { assign(t, wrap, wrap);
1523     changed++;
1524   }
1525 
1526   assign(t, margin, width);
1527 
1528   if ( Wrapped(t) )
1529     changed++;
1530   else if ( wrap == NAME_clip )
1531     setGraphical(t, DEFAULT, DEFAULT, width, DEFAULT);
1532 
1533   if ( changed )
1534     recomputeText(t, NAME_area);
1535 
1536   succeed;
1537 }
1538 
1539 
1540 		/********************************
1541 		*          LOAD-STORE		*
1542 		********************************/
1543 
1544 static status
loadText(TextObj t,IOSTREAM * fd,ClassDef def)1545 loadText(TextObj t, IOSTREAM *fd, ClassDef def)
1546 { TRY(loadSlotsObject(t, fd, def));
1547   if ( restoreVersion <= 6 && t->pen != ZERO )
1548     assign(t, pen, ZERO);
1549 
1550   if ( isNil(t->wrap) )
1551     assign(t, wrap, NAME_extend);
1552   if ( isNil(t->margin) )
1553     assign(t, margin, toInt(100));
1554   if ( isNil(t->border) )
1555     assign(t, border, ZERO);
1556   if ( isNil(t->underline) )
1557     assign(t, underline, OFF);
1558 
1559   succeed;
1560 }
1561 
1562 
1563 static status
convertOldSlotText(TextObj t,Name slot,Any value)1564 convertOldSlotText(TextObj t, Name slot, Any value)
1565 { if ( slot == NAME_transparent && isNil(t->background) )
1566     assign(t, background, (value == ON ? NIL : DEFAULT));
1567 
1568   succeed;
1569 }
1570 
1571 		 /*******************************
1572 		 *	    DELEGATION		*
1573 		 *******************************/
1574 
1575 static status
catchAllText(TextObj t,Name sel,int argc,Any * argv)1576 catchAllText(TextObj t, Name sel, int argc, Any* argv)
1577 { if ( qadSendv(t->string, NAME_hasSendMethod, 1, (Any *)&sel) ||
1578        prepareEditText(t, sel) )
1579   { status rval;
1580 
1581     if ( (rval = vm_send(t->string, sel, NULL, argc, argv)) )
1582       recomputeText(t, NAME_area);
1583 
1584     return rval;
1585   }
1586 
1587   return errorPce(t, NAME_noBehaviour, CtoName("->"), sel);
1588 }
1589 
1590 
1591 static Any
getCatchAllText(TextObj t,Name sel,int argc,Any * argv)1592 getCatchAllText(TextObj t, Name sel, int argc, Any *argv)
1593 { if ( qadSendv(t->string, NAME_hasGetMethod, 1, (Any *)&sel) )
1594     answer(vm_get(t->string, sel, NULL, argc, argv));
1595 
1596   errorPce(t, NAME_noBehaviour, CtoName("<-"), sel);
1597   fail;
1598 }
1599 
1600 
1601 static status
hasSendMethodText(TextObj t,Name sel)1602 hasSendMethodText(TextObj t, Name sel)
1603 { if ( hasSendMethodObject(t, sel) ||
1604        hasSendMethodObject(t->string, sel) ||
1605        getSendMethodClass(ClassString, sel) )
1606     succeed;
1607 
1608   fail;
1609 }
1610 
1611 
1612 static status
hasGetMethodText(TextObj t,Name sel)1613 hasGetMethodText(TextObj t, Name sel)
1614 { if ( hasGetMethodObject(t, sel) ||
1615        hasGetMethodObject(t->string, sel) )
1616     succeed;
1617 
1618   fail;
1619 }
1620 
1621 
1622 		 /*******************************
1623 		 *	 CLASS DECLARATION	*
1624 		 *******************************/
1625 
1626 /* Type declarations */
1627 
1628 static char *T_insert[] =
1629         { "at=[int]", "text=char_array" };
1630 static char *T_resize[] =
1631         { "factor_x=real", "factor_y=[real]", "origin=[point]" };
1632 static char *T_margin[] =
1633         { "int*", "[{wrap,wrap_fixed_width,clip}]" };
1634 static char *T_linesADintD_columnADintD[] =
1635         { "lines=[int]", "column=[int]" };
1636 static char *T_convertOldSlot[] =
1637         { "slot=name", "value=unchecked" };
1638 static char *T_initialise[] =
1639         { "string=[char_array]", "format=[{left,center,right}]",
1640 	  "font=[font]" };
1641 static char *T_insertSelf[] =
1642         { "times=[int]", "character=[char]" };
1643 static char *T_geometry[] =
1644         { "x=[int]", "y=[int]", "width=[int]", "height=[int]" };
1645 static char *T_selection[] =
1646         { "from=[int]*", "to=[int]" };
1647 static char *T_catchAll[] =
1648         { "selector=name", "argument=unchecked ..." };
1649 
1650 /* Instance Variables */
1651 
1652 static vardecl var_text[] =
1653 { IV(NAME_string, "char_array", IV_GET,
1654      NAME_storage, "Represented string (may contain newlines)"),
1655   SV(NAME_font, "font", IV_GET|IV_STORE, fontText,
1656      NAME_appearance, "Font used to draw the string"),
1657   SV(NAME_format, "{left,center,right}", IV_GET|IV_STORE, formatText,
1658      NAME_appearance, "Left, center or right alignment"),
1659   IV(NAME_margin, "int", IV_GET,
1660      NAME_appearance, "Margin for <->wrap equals wrap"),
1661   SV(NAME_underline, "bool", IV_GET|IV_STORE, underlineText,
1662      NAME_appearance, "Underlined text?"),
1663   IV(NAME_position, "point", IV_NONE,
1664      NAME_internal, "Avoid `walking' with alignment"),
1665   IV(NAME_caret, "int", IV_GET,
1666      NAME_caret, "Index (0-based) of caret"),
1667   SV(NAME_showCaret, "bool|{passive}", IV_GET|IV_STORE, showCaretText,
1668      NAME_appearance, "If not @off, show the caret"),
1669   SV(NAME_background, "[colour|pixmap]*", IV_GET|IV_STORE, backgroundText,
1670      NAME_appearance, "@nil: transparent; @default: cleared"),
1671   SV(NAME_border, "0..", IV_GET|IV_STORE, borderText,
1672      NAME_appearance, "Border around actual text"),
1673   IV(NAME_wrap, "{extend,wrap,wrap_fixed_width,clip}", IV_GET,
1674      NAME_appearance, "How long text is handled"),
1675   IV(NAME_xOffset, "int", IV_NONE,
1676      NAME_internal, "Horizontal scroll when nonzero length"),
1677   IV(NAME_xCaret, "int", IV_NONE,
1678      NAME_internal, "X-position of caret"),
1679   IV(NAME_yCaret, "int", IV_NONE,
1680      NAME_internal, "Y-position of caret"),
1681   IV(NAME_Selection, "int*", IV_NONE,
1682      NAME_internal, "Selected text")
1683 };
1684 
1685 /* Send Methods */
1686 
1687 static senddecl send_text[] =
1688 { SM(NAME_event, 1, "event", eventText,
1689      DEFAULT, "Handle focus and keyboard events"),
1690   SM(NAME_geometry, 4, T_geometry, geometryText,
1691      DEFAULT, "Only move text"),
1692   SM(NAME_initialise, 3, T_initialise, initialiseText,
1693      DEFAULT, "Create from string, format and font"),
1694   SM(NAME_resize, 3, T_resize, resizeText,
1695      DEFAULT, "Resize text with specified factor"),
1696   SM(NAME_string, 1, "char_array", stringText,
1697      NAME_storage, "Represented string"),
1698   SM(NAME_formatCenter, 0, NULL, formatCenterText,
1699      NAME_appearance, "Set center alignment"),
1700   SM(NAME_formatLeft, 0, NULL, formatLeftText,
1701      NAME_appearance, "Set left alignment"),
1702   SM(NAME_formatRight, 0, NULL, formatRightText,
1703      NAME_appearance, "Set right alignment"),
1704   SM(NAME_margin, 2, T_margin, marginText,
1705      NAME_appearance, "Determine how long text is handled"),
1706   SM(NAME_length, 1, "int", lengthText,
1707      NAME_area, "(compatibility)"),
1708   SM(NAME_prefix, 0, NULL, succeedObject,
1709      NAME_binding, "Multi-key prefix (see class key_binding)"),
1710   SM(NAME_backwardChar, 1, "times=[int]", backwardCharText,
1711      NAME_caret, "Move caret characters backward (\\C-f)"),
1712   SM(NAME_backwardWord, 1, "times=[int]", backwardWordText,
1713      NAME_caret, "Move caret words backward (\\eb)"),
1714   SM(NAME_beginningOfLine, 1, "times=[int]", beginningOfLineText,
1715      NAME_caret, "Move caret to start of line (\\C-a)"),
1716   SM(NAME_caret, 1, "[int]", caretText,
1717      NAME_caret, "Move caret to 0-based index"),
1718   SM(NAME_endOfLine, 1, "times=[int]", endOfLineText,
1719      NAME_caret, "Move caret to end of line (\\C-e)"),
1720   SM(NAME_forwardChar, 1, "times=[int]", forwardCharText,
1721      NAME_caret, "Move caret characters forwards (\\C-f)"),
1722   SM(NAME_forwardWord, 1, "times=[int]", forwardWordText,
1723      NAME_caret, "Move caret words forward (\\ef)"),
1724   SM(NAME_nextLine, 2, T_linesADintD_columnADintD, nextLineText,
1725      NAME_caret, "Move caret lines down (\\C-n)"),
1726   SM(NAME_previousLine, 2, T_linesADintD_columnADintD, previousLineText,
1727      NAME_caret, "Move caret lines up (\\C-n)"),
1728   SM(NAME_convertOldSlot, 2, T_convertOldSlot, convertOldSlotText,
1729      NAME_compatibility, "Convert <-transparent to <-background"),
1730   SM(NAME_transparent, 1, "bool", transparentText,
1731      NAME_compatibility, "Defines <-background"),
1732   SM(NAME_backwardDeleteChar, 1, "times=[int]", backwardDeleteCharText,
1733      NAME_delete, "Delete chars backward from caret (DEL)"),
1734   SM(NAME_backwardKillWord, 1, "times=[int]", backwardKillWordText,
1735      NAME_delete, "Deletes words backward from caret (\\eDEL)"),
1736   SM(NAME_clear, 0, NULL, clearText,
1737      NAME_delete, "Wipe out all text (\\C-u)"),
1738   SM(NAME_deleteChar, 1, "times=[int]", deleteCharText,
1739      NAME_delete, "Delete characters forwards (\\C-d)"),
1740   SM(NAME_cutOrDeleteChar, 1, "times=[int]", cutOrDeleteCharText,
1741      NAME_delete, "Cut or delete characters forwards (DEL)"),
1742   SM(NAME_cutOrBackwardDeleteChar, 1, "times=[int]",
1743      cutOrBackwardDeleteCharText,
1744      NAME_delete, "Cut or delete characters backward (BS)"),
1745   SM(NAME_killLine, 1, "times=[int]", killLineText,
1746      NAME_delete, "Delete lines from caret \\C-k)"),
1747   SM(NAME_killWord, 1, "times=[int]", killWordText,
1748      NAME_delete, "Deletes words forward from caret (\\ed)"),
1749   SM(NAME_typed, 1, "event|event_id", typedText,
1750      NAME_event, "Handle a keystroke"),
1751   SM(NAME_insert, 2, T_insert, insertText,
1752      NAME_insert, "Insert text at position [<-caret]"),
1753   SM(NAME_insertSelf, 2, T_insertSelf, insertSelfText,
1754      NAME_insert, "Insert n-times char at caret"),
1755   SM(NAME_newline, 1, "times=[int]", newlineText,
1756      NAME_insert, "Insert newlines (RET, LFD)"),
1757   SM(NAME_openLine, 1, "times=[int]", openLineText,
1758      NAME_insert, "Insert newlines after caret (\\C-o)"),
1759   SM(NAME_DrawPostScript, 1, "{head,body}", drawPostScriptText,
1760      NAME_postscript, "Create PostScript"),
1761   SM(NAME_compute, 0, NULL, computeText,
1762      NAME_repaint, "Recompute area/offset"),
1763   SM(NAME_paste, 1, "which=[{primary,clipboard}]", pasteText,
1764      NAME_selection, "Paste primary selection or clipboard"),
1765   SM(NAME_gosmacsTranspose, 0, NULL, gosmacsTransposeText,
1766      NAME_transpose, "Transpose two char_array before caret"),
1767   SM(NAME_transposeChars, 0, NULL, transposeCharsText,
1768      NAME_transpose, "Transpose two char_array around caret"),
1769   SM(NAME_selection, 2, T_selection, selectionText,
1770      NAME_selection, "Make [from, to) the selection"),
1771   SM(NAME_copy, 0, NULL, copyText,
1772      NAME_selection, "Copy selection (\\C-c)"),
1773   SM(NAME_cut, 0, NULL, cutText,
1774      NAME_selection, "Copy and delete selection"),
1775   SM(NAME_cutOrDeleteChar, 1, "times=[int]", cutOrDeleteCharText,
1776      NAME_delete, "Delete characters forwards (DEL)"),
1777   SM(NAME_catchAll, 2, T_catchAll, catchAllText,
1778      NAME_delegate, "Delegate to <-string"),
1779   SM(NAME_hasSendMethod, 1, "name", hasSendMethodText,
1780      DEFAULT, "Test if text or <-string defines method"),
1781   SM(NAME_hasGetMethod, 1, "name", hasGetMethodText,
1782      DEFAULT, "Test if text or <-string defines method")
1783 };
1784 
1785 /* Get Methods */
1786 
1787 static getdecl get_text[] =
1788 { GM(NAME_characterPosition, 1, "point", "index=[int]",
1789      getCharacterPositionText,
1790      NAME_calculate, "Convert index to position of character"),
1791   GM(NAME_column, 0, "pixels=int", NULL, getColumnText,
1792      NAME_caret, "Current X-location of caret (pixels)"),
1793   GM(NAME_upDownColumn, 0, "pixels=int", NULL, getColumnText,
1794      NAME_caret, "Current X-location of caret (pixels)"),
1795   GM(NAME_transparent, 0, "bool", NULL, getTransparentText,
1796      NAME_compatibility, "Map <-background"),
1797   GM(NAME_pointed, 1, "index=int", "at=point", getPointedText,
1798      NAME_event, "Convert position to character index"),
1799   GM(NAME_selectedText, 0, "string", NULL, getSelectedTextText,
1800      NAME_selection, "New string with contents of selection"),
1801   GM(NAME_selection, 0, "point", NULL, getSelectionText,
1802      NAME_selection, "New point with start and end of selection"),
1803   GM(NAME_catchAll, 2, "unchecked", T_catchAll, getCatchAllText,
1804      NAME_delegate, "Delegate to <-string")
1805 };
1806 
1807 /* Resources */
1808 
1809 static classvardecl rc_text[] =
1810 { RC(NAME_pen, RC_REFINE, "0", NULL),
1811   RC(NAME_border, "0..", "0",
1812      "Space around the actual text"),
1813   RC(NAME_font, "font", "normal",
1814      "Default font"),
1815   RC(NAME_format, "name", "left",
1816      "Default adjustment: {left,center,right}"),
1817   RC(NAME_selectionStyle, "style",
1818      UXWIN("style(colour := white, background := black)",
1819 	   "@_select_style"),
1820      "Style for <-selection"),
1821   RC(NAME_insertDeletesSelection, "bool", "@on",
1822      "->insert_self and ->paste delete the selection"),
1823   RC(NAME_keyBinding, "string", "",
1824      "`Key = selector' binding list")
1825 };
1826 
1827 /* Class Declaration */
1828 
1829 static Name text_termnames[] = { NAME_string, NAME_format, NAME_font };
1830 
1831 ClassDecl(text_decls,
1832           var_text, send_text, get_text, rc_text,
1833           3, text_termnames,
1834           "$Rev$");
1835 
1836 
1837 status
makeClassText(Class class)1838 makeClassText(Class class)
1839 { declareClass(class, &text_decls);
1840   setRedrawFunctionClass(class, RedrawAreaText);
1841   setLoadStoreFunctionClass(class, loadText, NULL);
1842 
1843   succeed;
1844 }
1845 
1846