1 /*  Part of XPCE --- The SWI-Prolog GUI toolkit
2 
3     Author:        Jan Wielemaker and Anjo Anjewierden
4     E-mail:        J.Wielemaker@cs.nl
5     WWW:           http://www.swi-prolog.org/projects/xpce/
6     Copyright (c)  1985-2017, University of Amsterdam
7                               VU University Amsterdam
8     All rights reserved.
9 
10     Redistribution and use in source and binary forms, with or without
11     modification, are permitted provided that the following conditions
12     are met:
13 
14     1. Redistributions of source code must retain the above copyright
15        notice, this list of conditions and the following disclaimer.
16 
17     2. Redistributions in binary form must reproduce the above copyright
18        notice, this list of conditions and the following disclaimer in
19        the documentation and/or other materials provided with the
20        distribution.
21 
22     THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
23     "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
24     LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
25     FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
26     COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
27     INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
28     BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
29     LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
30     CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
31     LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
32     ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
33     POSSIBILITY OF SUCH DAMAGE.
34 */
35 
36 #include <h/kernel.h>
37 #include <h/graphics.h>
38 #include <h/text.h>
39 #include <h/unix.h>
40 
41 static Int		getMarginWidthEditor(Editor);
42 static Int		getColumnEditor(Editor, Int);
43 static Int		getLineNumberEditor(Editor, Int);
44 static Int		getLengthEditor(Editor);
45 static Int		normalise_index(Editor, Int);
46 static FragmentCache	newFragmentCache(Editor);
47 static void		freeFragmentCache(FragmentCache);
48 static void		resetFragmentCache(FragmentCache, TextBuffer);
49 static ISearchCache	newISearchCache(Editor);
50 static void		freeISearchCache(ISearchCache);
51 static status		CaretEditor(Editor, Int);
52 static status		caretEditor(Editor, Int);
53 static status		IsearchEditor(Editor, EventId);
54 static status		DabbrevExpandEditor(Editor, EventId);
55 static status		centerWindowEditor(Editor, Int);
56 static status		columnEditor(Editor, Int);
57 static status		ChangedRegionEditor(Editor, Int, Int);
58 static status		ChangedEditor(Editor);
59 static status		appendKill(CharArray);
60 static status		prependKill(CharArray);
61 static status		geometryEditor(Editor, Int, Int, Int, Int);
62 static status		ensureVisibleEditor(Editor, Int, Int);
63 static status		ensureCaretInWindowEditor(Editor);
64 static status		endIsearchEditor(Editor, BoolObj save_mark);
65 static status		updateStyleCursorEditor(Editor);
66 static status		selectedFragmentEditor(Editor, Fragment);
67 static status		showMatchingBracketEditor(Editor, Int);
68 static status		insertSelfFillEditor(Editor, Int, Int);
69 static status		scrollDownEditor(Editor, Int);
70 static status		selectionOriginEditor(Editor, Int);
71 static status		selectionExtendEditor(Editor, Int);
72 static status		selection_editor(Editor, Int, Int, Name);
73 static status		selectionToCutBufferEditor(Editor, Int);
74 static status		insertCutBufferEditor(Editor, Int);
75 static status		insertEditor(Editor e, CharArray str);
76 static status		lineNumberEditor(Editor, Int);
77 static status		saveEditor(Editor, SourceSink);
78 static status		newKill(CharArray);
79 static CharArray	killRegister(Int);
80 static status		tabDistanceEditor(Editor e, Int tab);
81 static status		isisearchingEditor(Editor e);
82 static status		changedHitsEditor(Editor e);
83 static status		showLabelEditor(Editor e, BoolObj val);
84 static Int		countLinesEditor(Editor e, Int from, Int to);
85 static status		deleteEditor(Editor e, Int from, Int to);
86 static status		deleteSelectionEditor(Editor e);
87 static status		abortIsearchEditor(Editor e, BoolObj save_mark);
88 static status		scrollUpEditor(Editor e, Int arg);
89 static Int		getColumnLocationEditor(Editor e, Int c, Int from);
90 
91 static Timer	ElectricTimer;
92 
93 #define Caret(e)	valInt(e->caret)
94 #define Receiver(e)	ReceiverOfEditor(e)
95 #define Round(n, r)	((((n) + ((r)-1)) / (r)) * (r))
96 #define Before(f, t)	{ if ( valInt(f) > valInt(t) ) \
97 			  { Int _tmp = t; t = f; f = _tmp; \
98 			  } \
99 			}
100 
101 #define HasSelection(e) ((e)->mark != (e)->caret && \
102 			 (e)->mark_status == NAME_active)
103 #define SelectionRegion(e, from, to) \
104   { if ( !HasSelection(e) ) \
105     { send(e, NAME_report, NAME_warning, CtoName("No selection"), EAV); \
106       fail; \
107     } \
108     from = e->mark; \
109     to   = e->caret; \
110     Before(from, to); \
111   }
112 
113 #define Fetch(e, i)		fetch_textbuffer((e)->text_buffer, (i))
114 #define InRegion(i, l, h)	( (l < h && i >= l && i < h) || \
115 				  (l > h && i >= h && i < l) )
116 
117 /* Scroll using line-parameters upto this size for the buffer */
118 #define MAXPRECISESCROLLING   10000
119 #define MAXLINEBASEDSCROLLING 25000
120 
121 struct isearch_cache
122 { Style		style;			/* Style used for search hits */
123   intptr_t	hit_start;		/* Start of a hit */
124   intptr_t	hit_end;		/* Start of a hit */
125 };
126 
127 		/********************************
128 		*            CREATE		*
129 		********************************/
130 
131 static status
initialiseEditor(Editor e,TextBuffer tb,Int w,Int h,Int tmw)132 initialiseEditor(Editor e, TextBuffer tb, Int w, Int h, Int tmw)
133 { Int fw, fh, iw, ih, ew;
134   Size sz = getClassVariableValueObject(e, NAME_size);
135 
136   if ( isDefault(tb) ) tb = newObject(ClassTextBuffer, EAV);
137   if ( isDefault(tmw)) tmw = ZERO;
138 
139   assign(e, size, newObject(ClassSize, sz->w, sz->h, EAV));
140   if ( notDefault(w) ) assign(e->size, w, w);
141   if ( notDefault(h) ) assign(e->size, h, h);
142 
143   initialiseDevice((Device) e);		/* also obtains class-variables! */
144 /*assign(e, pen, getClassVariableValueObject(e, NAME_pen));*/
145   assign(e, text_buffer, tb);
146 /*assign(e, font, getClassVariableValueObject(e, NAME_font));*/
147   fw = getExFont(e->font);
148   fh = getHeightFont(e->font);
149   iw = toInt(valInt(e->size->w) * valInt(fw) + 2 * TXT_X_MARGIN);
150   ih = toInt(valInt(e->size->h) * valInt(fh) + 2 * TXT_Y_MARGIN);
151 
152   assign(e, image, newObject(ClassTextImage, e, iw, ih, EAV));
153   assign(e, scroll_bar, newObject(ClassScrollBar, e, NAME_vertical, EAV));
154 
155   if ( valInt(tmw) > 0 )
156     assign(e, margin, newObject(ClassTextMargin, e, tmw, ih, EAV));
157   else
158     assign(e, margin, NIL);
159   assign(e, text_cursor, newObject(ClassTextCursor, e->font, EAV));
160   send(e->text_cursor, NAME_active, OFF, EAV);
161   assign(e, caret, ZERO);
162   assign(e, mark, toInt(tb->size));
163   assign(e, mark_status, NAME_inactive);
164   assign(e, mark_ring, newObject(ClassVector, EAV));
165   assign(e, selected_fragment, NIL);
166   assign(e, selected_fragment_style, newObject(ClassStyle, EAV));
167   boldStyle(e->selected_fragment_style, ON);
168   assign(e, bindings, newObject(ClassKeyBinding, NIL, NAME_editor, EAV));
169   assign(e, focus_function, NIL);
170 /*assign(e, fill_mode, getClassVariableValueObject(e, NAME_fillMode));
171   assign(e, exact_case, getClassVariableValueObject(e, NAME_exactCase));*/
172   assign(e, kill_location, NIL);
173   assign(e, search_direction, NAME_forward);
174   assign(e, search_string, NIL);
175   assign(e, search_origin, ZERO);
176   assign(e, search_base, ZERO);
177   assign(e, search_wrapped, NIL);
178   assign(e, search_wrapped_warned, OFF);
179   assign(e, selection_origin, ZERO);
180   assign(e, selection_unit, NAME_character);
181 /*assign(e, selection_style, getClassVariableValueObject(e, NAME_selectionStyle));*/
182   assign(e, editable, ON);
183   assign(e, error_message, NIL);
184   assign(e, left_margin, ZERO);
185 /*assign(e, right_margin, getClassVariableValueObject(e, NAME_rightMargin));
186   assign(e, indent_increment, getClassVariableValueObject(e, NAME_indentIncrement)); */
187   assign(e, auto_newline, OFF);
188   assign(e, file, NIL);
189   assign(e, dabbrev_target, NIL);
190   assign(e, dabbrev_reject, NIL);
191   assign(e, dabbrev_pos, NIL);
192   assign(e, dabbrev_origin, NIL);
193   assign(e, styles, newObject(ClassSheet, EAV));
194 
195   e->fragment_cache = newFragmentCache(e);
196   e->isearch_cache = newISearchCache(e);
197 
198   send(e->image, NAME_cursor, getClassVariableValueObject(e, NAME_cursor), EAV);
199   send(e->image, NAME_set, e->scroll_bar->area->w, ZERO, EAV);
200   tabDistanceTextImage(e->image, mul(e->tab_distance, getExFont(e->font)));
201   heightGraphical((Graphical) e->scroll_bar, ih);
202   displayDevice(e, e->scroll_bar, DEFAULT);
203   displayDevice(e, e->image, DEFAULT);
204   displayDevice(e, e->text_cursor, DEFAULT);
205   ew = add(e->scroll_bar->area->w,e->image->area->w);
206 
207   if ( notNil(e->margin) )
208   { send(e->margin, NAME_set, ew, EAV);
209     ew = add(ew, e->margin->area->w);
210     displayDevice(e, e->margin, DEFAULT);
211   }
212 
213   updateStyleCursorEditor(e);		/* also does position */
214   send(tb, NAME_attach, e, EAV);
215   geometryEditor(e, ZERO, ZERO, ew, ih);
216 
217   succeed;
218 }
219 
220 
221 static Editor
getConvertEditor(Any ctx,View v)222 getConvertEditor(Any ctx, View v)
223 { answer(v->editor);
224 }
225 
226 
227 static status
unlinkEditor(Editor e)228 unlinkEditor(Editor e)
229 { View view = Receiver(e);
230 
231   if ( ElectricTimer && ((Message)(ElectricTimer->message))->receiver == e )
232   { stopTimer(ElectricTimer);
233     assign((Message)ElectricTimer->message, receiver, NIL);
234   }
235 
236   if ( notNil(e->text_buffer) )
237   { send(e->text_buffer, NAME_detach, e, EAV);
238     assign(e, text_buffer, NIL);
239   }
240   if ( e->fragment_cache != NULL )
241   { freeFragmentCache(e->fragment_cache);
242     e->fragment_cache = NULL;
243   }
244   if ( e->isearch_cache != NULL )
245   { freeISearchCache(e->isearch_cache);
246     e->isearch_cache = NULL;
247   }
248 
249   unlinkDevice((Device) e);
250 
251   freeObject(e->image);			/* make sure */
252   freeObject(e->scroll_bar);
253   freeObject(e->text_cursor);
254 
255   if ( instanceOfObject(view, ClassView) && !isFreedObj(view) )
256     send(view, NAME_free, EAV);
257 
258   succeed;
259 }
260 
261 
262 static status
lostTextBufferEditor(Editor e)263 lostTextBufferEditor(Editor e)
264 { if ( !onFlag(e, F_FREED|F_FREEING) )
265     send(Receiver(e), NAME_free, EAV);
266 
267   succeed;
268 }
269 
270 
271 		 /*******************************
272 		 *		REDRAW		*
273 		 *******************************/
274 
275 static status
RedrawAreaEditor(Editor e,Area a)276 RedrawAreaEditor(Editor e, Area a)
277 { Any obg = r_background(getClassVariableValueObject(e, NAME_background));
278 
279   RedrawAreaDevice((Device)e, a);
280   if ( e->pen != ZERO )
281   { int p = valInt(e->pen);
282     int x, y, w, h;
283     int th = valInt(e->image->area->y);
284 
285     initialiseDeviceGraphical(e, &x, &y, &w, &h);
286     y += th;
287     h -= th;
288 
289 					/* test for overlap with border */
290     if ( valInt(a->x) < p || valInt(a->y) < p ||
291 	 valInt(a->x) + valInt(a->w) > w - p ||
292 	 valInt(a->y) + valInt(a->h) > h - p )
293     { r_thickness(p);
294       r_dash(e->texture);
295 
296       r_box(x, y, w, h, 0, NIL);
297     }
298   }
299 
300   r_background(obg);
301 
302   succeed;
303 }
304 
305 		 /*******************************
306 		 *	  CLONE/SAVE/LOAD	*
307 		 *******************************/
308 
309 static status
storeEditor(Editor e,FileObj file)310 storeEditor(Editor e, FileObj file)
311 { return storeSlotsObject(e, file);
312 }
313 
314 
315 static status
loadFdEditor(Editor e,IOSTREAM * fd,ClassDef def)316 loadFdEditor(Editor e, IOSTREAM *fd, ClassDef def)
317 { TRY(loadSlotsObject(e, fd, def));
318 
319   e->fragment_cache = newFragmentCache(e);
320   e->internal_mark = 0;
321 
322   succeed;
323 }
324 
325 
326 static status
cloneEditor(Editor e,Editor clone)327 cloneEditor(Editor e, Editor clone)
328 { clonePceSlots(e, clone);
329 
330   e->fragment_cache = newFragmentCache(e);
331 
332   succeed;
333 }
334 
335 
336 		 /*******************************
337 		 *	    TEXT-BUFFER		*
338 		 *******************************/
339 
340 static status
textBufferEditor(Editor e,TextBuffer tb)341 textBufferEditor(Editor e, TextBuffer tb)
342 { if ( e->text_buffer != tb )
343   { TextImage ti = e->image;
344 
345     selectedFragmentEditor(e, NIL);
346     send(e->text_buffer, NAME_detach, e, EAV);
347 
348     assign(e, text_buffer, tb);
349     assign(e, caret, ZERO);
350     assign(e, mark, toInt(tb->size));
351     assign(e, mark_status, NAME_inactive);
352     if ( e->fragment_cache )
353       resetFragmentCache(e->fragment_cache, e->text_buffer);
354 
355     send(tb, NAME_attach, e, EAV);
356 
357     ChangedEntireTextImage(ti);
358     requestComputeGraphical(e, DEFAULT);
359   }
360 
361   succeed;
362 }
363 
364 
365 		/********************************
366 		*            CURSOR		*
367 		********************************/
368 
369 static status
showCaretAtEditor(Editor e,Int caret)370 showCaretAtEditor(Editor e, Int caret)
371 { int x, y, w, h, b;
372   int displaced = notDefault(caret);
373 
374   caret = normalise_index(e, isDefault(caret) ? e->caret : caret);
375   if ( get_character_box_textimage(e->image, valInt(caret),
376 				   &x, &y, &w, &h, &b) )
377   { x += valInt(e->image->area->x);
378     y += valInt(e->image->area->y);
379     w = valInt(getExFont(e->font));
380 
381     setTextCursor(e->text_cursor,
382 		  toInt(x), toInt(y), toInt(w), toInt(h), toInt(b));
383     if ( displaced )
384       requestComputeGraphical(e, NAME_showCaretAt);
385 
386     succeed;
387   }
388 
389   fail;
390 }
391 
392 
393 static status
updateCursorEditor(Editor e)394 updateCursorEditor(Editor e)
395 { return showCaretAtEditor(e, DEFAULT);
396 }
397 
398 
399 static status
electricCaretEditor(Editor e,Int caret,Real time)400 electricCaretEditor(Editor e, Int caret, Real time)
401 { TRY( showCaretAtEditor(e, caret) );
402 
403   if ( !ElectricTimer )
404   { if ( isDefault(time) )
405       time = CtoReal(0.5);
406 
407     ElectricTimer = globalObject(NAME_electricTimer, ClassTimer, time,
408 				 newObject(ClassMessage, e,
409 					   NAME_showCaretAt, EAV),
410 				 EAV);
411   } else
412   { assign((Message)ElectricTimer->message, receiver, e);
413     if ( notDefault(time) )
414       intervalTimer(ElectricTimer, time);
415   }
416 
417   return startTimer(ElectricTimer, NAME_once);
418 }
419 
420 
421 static status
updateStyleCursorEditor(Editor e)422 updateStyleCursorEditor(Editor e)
423 { send(e->text_cursor, NAME_font, e->font, EAV);
424 
425   return updateCursorEditor(e);
426 }
427 
428 
429 static status
showCaretEditor(Editor e,BoolObj show)430 showCaretEditor(Editor e, BoolObj show)
431 { DisplayedGraphical(e->text_cursor, show);
432 
433   succeed;
434 }
435 
436 
437 		/********************************
438 		*          SCROLLBAR		*
439 		********************************/
440 
441 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
442 Scrollbar updates. This can all be  optimised  further, both by scanning
443 the text only once, avoiding fetch() while scanning and finally and most
444 importantly, by caching some of these values,  such as the start-line of
445 the view and the number of lines in the buffer.
446 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
447 
448 static status
bubbleScrollBarEditor(Editor e,ScrollBar sb)449 bubbleScrollBarEditor(Editor e, ScrollBar sb)
450 { TextBuffer tb = e->text_buffer;
451   Int start = getStartTextImage(e->image, ONE);
452 
453   if ( tb->size < MAXPRECISESCROLLING )
454   { return bubbleScrollBarTextImage(e->image, sb);
455   } else if ( tb->size < MAXLINEBASEDSCROLLING ) /* short, work line-based */
456   { Int len   = countLinesEditor(e, ZERO, toInt(tb->size));
457     Int first = sub(getLineNumberEditor(e, start), ONE); /* 1-based! */
458     Int view  = countLinesEditor(e, start, e->image->end);
459 
460     if ( tb->size > 0 &&
461 	 !tisendsline(tb->syntax, Fetch(e, tb->size-1)) )
462       incrInt(len);			/* incomplete last line */
463     if ( valInt(e->image->end) > 0 &&
464 	 !tisendsline(tb->syntax, Fetch(e, valInt(e->image->end)-1)) )
465       incrInt(view);
466 
467     return bubbleScrollBar(sb, len, first, view);
468   } else				/* long, work character-based */
469   { Int len  = toInt(tb->size);
470     Int view = getViewTextImage(e->image);
471 
472     return bubbleScrollBar(sb, len, start, view);
473   }
474 }
475 
476 
477 static Int
getStartEditor(Editor e,Int line)478 getStartEditor(Editor e, Int line)
479 { answer(getStartTextImage(e->image, line));
480 }
481 
482 
483 static Int
getViewEditor(Editor e)484 getViewEditor(Editor e)
485 { answer(getViewTextImage(e->image));
486 }
487 
488 
489 static Int
getLengthEditor(Editor e)490 getLengthEditor(Editor e)
491 { answer(toInt(e->text_buffer->size));
492 }
493 
494 		/********************************
495 		*            LABEL		*
496 		********************************/
497 
498 static status
labelEditor(Editor e,Name lbl)499 labelEditor(Editor e, Name lbl)
500 { showLabelEditor(e, ON);
501 
502   send(e->label_text, NAME_string, lbl, EAV);
503   geometryEditor(e, DEFAULT, DEFAULT, DEFAULT, DEFAULT);
504 
505   succeed;
506 }
507 
508 
509 static status
showLabelEditor(Editor e,BoolObj val)510 showLabelEditor(Editor e, BoolObj val)
511 { if ( isNil(e->label_text) )
512   { if ( val == ON )
513     { assign(e, label_text,
514 	     newObject(ClassText, GetLabelNameName(e->name), NAME_left,
515 		       getClassVariableValueObject(e, NAME_labelFont), EAV));
516       marginText(e->label_text, e->area->w, NAME_clip);
517       displayDevice(e, e->label_text, DEFAULT);
518       return geometryEditor(e, DEFAULT, DEFAULT, DEFAULT, DEFAULT);
519     } else
520       succeed;
521   }
522 
523   if ( e->label_text->displayed != val )
524   { DisplayedGraphical(e->label_text, val);
525     return geometryEditor(e, DEFAULT, DEFAULT, DEFAULT, DEFAULT);
526   }
527 
528   succeed;
529 }
530 
531 
532 static BoolObj
getShowLabelEditor(Editor e)533 getShowLabelEditor(Editor e)
534 { if ( notNil(e->label_text) )
535     answer(e->label_text->displayed);
536 
537   answer(OFF);
538 }
539 
540 
541 		/********************************
542 		*             MARGIN		*
543 		********************************/
544 
545 static status
marginWidthEditor(Editor e,Int width)546 marginWidthEditor(Editor e, Int width)
547 { if ( getMarginWidthEditor(e) != width )
548   { if ( isNil(e->margin) )
549     { assign(e, margin, newObject(ClassTextMargin, e, width, e->area->h, EAV));
550       displayDevice(e, e->margin, DEFAULT);
551     } else
552       setGraphical(e->margin, DEFAULT, DEFAULT, width, DEFAULT);
553 
554     geometryEditor(e, DEFAULT, DEFAULT, DEFAULT, DEFAULT);
555   }
556 
557   succeed;
558 }
559 
560 
561 static Int
getMarginWidthEditor(Editor e)562 getMarginWidthEditor(Editor e)
563 { if ( notNil(e->margin) )
564     answer(e->margin->area->w);
565 
566   answer(ZERO);
567 }
568 
569 
570 static status
selectedFragmentEditor(Editor e,Fragment fr)571 selectedFragmentEditor(Editor e, Fragment fr)
572 { if ( e->selected_fragment != fr )
573   { if ( notNil(e->selected_fragment) )
574     { Fragment f = e->selected_fragment;
575 
576       ChangedRegionEditor(e, toInt(f->start), toInt(f->start + f->length));
577     }
578     assign(e, selected_fragment, fr);
579     if ( notNil(fr) )
580       ChangedRegionEditor(e, toInt(fr->start), toInt(fr->start + fr->length));
581   }
582 
583   succeed;
584 }
585 
586 
587 static status
selectedFragmentStyleEditor(Editor e,Style style)588 selectedFragmentStyleEditor(Editor e, Style style)
589 { if ( e->selected_fragment_style != style )
590   { assign(e, selected_fragment_style, style);
591     if ( notNil(e->selected_fragment) )
592     { Fragment f = e->selected_fragment;
593 
594       ChangedRegionEditor(e, toInt(f->start), toInt(f->start + f->length));
595     }
596   }
597 
598   succeed;
599 }
600 
601 
602 		/********************************
603 		*            GEOMETRY		*
604 		********************************/
605 
606 static status
geometryEditor(Editor e,Int x,Int y,Int w,Int h)607 geometryEditor(Editor e, Int x, Int y, Int w, Int h)
608 { int ix, iy, iw, ih, mx, mw, sw;
609   int pen = valInt(e->pen);
610   Area a = e->area;
611   Any sbobj = e->image;
612   int fh = valInt(getHeightFont(e->font));
613 
614   if ( e->badBoundingBox == ON && (isDefault(w) || isDefault(h)) )
615   { Cell cell;
616     clearArea(a);
617 
618 				/* simplyfied computeBoundingBoxDevice() */
619 				/* we should consider non-displayed grs */
620 				/* too ... See label and scrollbar hiding */
621     for_cell(cell, e->graphicals)
622     { Graphical gr = cell->value;
623 
624       unionNormalisedArea(a, gr->area);
625     }
626 
627     relativeMoveArea(a, e->offset);
628     assign(e, badBoundingBox, OFF);
629   }
630 
631   if ( isDefault(x) ) x = a->x;
632   if ( isDefault(y) ) y = a->y;
633   if ( isDefault(w) ) w = a->w;
634   if ( isDefault(h) ) h = a->h;
635 
636   if ( valInt(w) < 50 ) w = toInt(50);
637 
638   DEBUG(NAME_editor, Cprintf("geometryEditor(%s, %d, %d, %d, %d)\n",
639 			     pp(e),
640 			     valInt(x), valInt(y),
641 			     valInt(w), valInt(h)));
642 
643   if ( notNil(e->label_text) && e->label_text->displayed == ON )
644   { marginText(e->label_text, w, NAME_clip);
645     ComputeGraphical(e->label_text);
646     send(e->label_text, NAME_set, ZERO, ZERO, DEFAULT, DEFAULT, EAV);
647     iy = valInt(e->label_text->area->h);
648   } else
649   { iy = 0;
650   }
651 
652 					/* make sure at least line fits! */
653   if ( valInt(h) - iy - fh - 2*TXT_Y_MARGIN < 0 )
654     h = toInt(iy+fh+2*TXT_Y_MARGIN);
655   ih = valInt(h);
656 
657   sw = isNil(e->scroll_bar) ? 0 : valInt(getMarginScrollBar(e->scroll_bar));
658   mw = notNil(e->margin) ? valInt(e->margin->area->w) : 0;
659   iw = valInt(w) - abs(sw) - mw;
660 
661   DEBUG(NAME_editor, Cprintf("sw = %d, mw = %d, iw = %d\n",
662 			     sw, mw, iw));
663 
664   assign(e->size, w, div(toInt(iw), getExFont(e->font)));
665   assign(e->size, h, div(h,  getHeightFont(e->font)));
666 
667   ix = (sw < 0 ? -sw : 0);
668   mx = ix + iw - pen;
669 
670   if ( notNil(e->margin) )
671   { if ( getClassVariableValueObject(e->margin, NAME_placement) == NAME_left )
672     { mx = ix;
673       ix += mw;
674     } else
675       sbobj = e->margin;
676   }
677 
678   send(e->image, NAME_set, toInt(ix), toInt(iy), toInt(iw), toInt(ih-iy), EAV);
679   if ( notNil(e->margin) )
680     send(e->margin, NAME_set, toInt(mx), toInt(iy), DEFAULT, toInt(ih-iy), EAV);
681   if ( notNil(e->scroll_bar) )
682     placeScrollBar(e->scroll_bar, sbobj);
683 
684   return geometryDevice((Device) e, x, y, DEFAULT, DEFAULT);
685 }
686 
687 
688 static status
requestGeometryEditor(Editor e,Int x,Int y,Int w,Int h)689 requestGeometryEditor(Editor e, Int x, Int y, Int w, Int h)
690 { Any v;
691 
692   if ( notDefault(w) )
693     w = mul(w, getExFont(e->font));
694   else if ( notNil(e->request_compute) )
695     w = mul(e->size->w, getExFont(e->font));
696 
697   if ( notDefault(h) )
698     h = mul(h, getHeightFont(e->font));
699   else if ( notNil(e->request_compute) )
700     h = mul(e->size->h, getHeightFont(e->font));
701 
702   if ( instanceOfObject(v = Receiver(e), ClassWindow) )
703     requestGeometryWindow(v, x, y, w, h);
704   else
705     requestGeometryGraphical(e, x, y, w, h);
706 
707   succeed;
708 }
709 
710 
711 static status
SizeEditor(Editor e,Size size)712 SizeEditor(Editor e, Size size)
713 { return doSetGraphical(e, DEFAULT, DEFAULT, size->w, size->h);
714 }
715 
716 
717 static Size
getSizeEditor(Editor e)718 getSizeEditor(Editor e)
719 { answer(e->size);
720 }
721 
722 
723 static Int
getWidthEditor(Editor e)724 getWidthEditor(Editor e)
725 { answer(e->size->w);
726 }
727 
728 
729 static Int
getHeightEditor(Editor e)730 getHeightEditor(Editor e)
731 { answer(e->size->h);
732 }
733 
734 
735 		/********************************
736 		*            STYLES		*
737 		********************************/
738 
739 static status
styleEditor(Editor e,Name name,Style style)740 styleEditor(Editor e, Name name, Style style)
741 { if ( isNil(style) )
742     deleteSheet(e->styles, name);
743   else
744     valueSheet(e->styles, name, style);
745 
746   ChangedEditor(e);
747 
748   succeed;
749 }
750 
751 static status
stylesEditor(Editor e,Sheet styles)752 stylesEditor(Editor e, Sheet styles)
753 { assign(e, styles, styles);
754   ChangedEditor(e);
755 
756   succeed;
757 }
758 
759 
760 		/********************************
761 		*            FETCH		*
762 		********************************/
763 
764 typedef struct fragment_cell  *FragmentCell;
765 
766 struct fragment_cell
767 { Fragment	fragment;		/* Fragment in the cell */
768   Style		style;			/* Style that belongs to it */
769   FragmentCell	next;			/* next in chain */
770 };
771 
772 
773 struct fragment_cache
774 { FragmentCell	active;			/* list of active fragments */
775   Fragment	current;		/* current fragment */
776   long		index;			/* current index */
777   unsigned long		attributes;		/* Current (fragment) attributes */
778   FontObj	font;			/* current (fragment) font */
779   Colour	colour;			/* current (fragment) colour */
780   Any		background;		/* curremt (fragment) background */
781   int		left_margin;		/* current left margin */
782   int		right_margin;		/* current right margin */
783   int		initial_state;		/* state after reset */
784 };
785 
786 
787 static FragmentCache
newFragmentCache(Editor e)788 newFragmentCache(Editor e)
789 { FragmentCache fc = alloc(sizeof(struct fragment_cache));
790 
791   fc->active = NULL;
792   fc->initial_state = FALSE;
793   resetFragmentCache(fc, e->text_buffer);
794 
795   return fc;
796 }
797 
798 
799 static void
freeFragmentCache(FragmentCache fc)800 freeFragmentCache(FragmentCache fc)
801 { resetFragmentCache(fc, NIL);
802 
803   unalloc(sizeof(struct fragment_cache), fc);
804 }
805 
806 
807 static void
resetFragmentCache(FragmentCache fc,TextBuffer tb)808 resetFragmentCache(FragmentCache fc, TextBuffer tb)
809 { if ( !fc->initial_state )
810   { FragmentCell c, c2;
811 
812     for(c=fc->active; c; c = c2)
813     { c2 = c->next;
814       unalloc(sizeof(struct fragment_cell), c);
815     }
816 
817     fc->active        = NULL;
818     fc->index         = -1;
819     fc->attributes    = 0;
820     fc->font	      = DEFAULT;
821     fc->colour	      = DEFAULT;
822     fc->background    = DEFAULT;
823     fc->left_margin   = 0;
824     fc->right_margin  = 0;
825     fc->initial_state = TRUE;
826   }
827 
828   fc->current         = (isNil(tb) ? NIL : tb->first_fragment);
829 }
830 
831 
832 static void
indexFragmentCache(FragmentCache fc,Editor e,long int i)833 indexFragmentCache(FragmentCache fc, Editor e, long int i)
834 { int changed = 0;
835   FragmentCell *C, c;
836   Fragment fr;
837 
838   if ( i < fc->index )			/* No incremental index when back */
839     resetFragmentCache(fc, e->text_buffer);
840 
841 					/* Delete those we passed */
842   for(C = &fc->active; (c = *C); )
843   { if ( i >= c->fragment->start + c->fragment->length )
844     { *C = c->next;
845       DEBUG(NAME_fragment, Cprintf("Passed %s fragment (%ld, %ld)\n",
846 				   pp(c->fragment->style),
847 				   c->fragment->start, c->fragment->length));
848       unalloc(sizeof(struct fragment_cell), c);
849       changed++;
850     } else
851       C = &c->next;
852   }
853 					/* Add new ones entered */
854   while( notNil(fr = fc->current) && i >= fr->start )
855   { Style s;
856 
857     if ( i < fr->start + fr->length &&
858 	 (s = getValueSheet(e->styles, fr->style)) )
859     { FragmentCell c = alloc(sizeof(struct fragment_cell));
860 
861       DEBUG(NAME_fragment,
862 	    Cprintf("Enter %s fragment (%ld, %ld) (style = %s)\n",
863 		    pp(fr->style),
864 		    fr->start, fr->length,
865 		    pp(s)));
866       c->fragment = fr;
867       c->style    = s;
868       c->next     = fc->active;
869       fc->active  = c;
870 
871       changed++;
872     }
873 
874     fc->current = fr->next;
875   }
876 
877   if ( changed )
878   { FragmentCell cell;
879     FontObj f = DEFAULT;
880     Any bg    = DEFAULT;
881     Colour c  = DEFAULT;
882     long fl   = 0;			/* keep compiler happy */
883     long bgl  = 0;
884     long cl   = 0;
885     int lm    = 0;
886     int rm    = 0;			/* margins */
887     unsigned long attributes = 0L;
888 
889     for( cell = fc->active; cell; cell = cell->next )
890     { Style s = cell->style;
891 
892       lm += valInt(s->left_margin);
893       rm += valInt(s->right_margin);
894 
895       if ( s->attributes & TXT_HIDDEN )
896       { Fragment fr = cell->fragment;
897 
898 	indexFragmentCache(fc, e, fr->start + fr->length);
899 	return;
900       }
901 
902       attributes |= s->attributes;
903 
904       if ( notDefault(s->font) )
905       { if ( isDefault(f) || cell->fragment->length < fl )
906 	{ f = s->font;
907 	  fl = cell->fragment->length;
908 	}
909       }
910       if ( notDefault(s->colour) )
911       { if ( isDefault(c) || cell->fragment->length < cl )
912 	{ c = s->colour;
913 	  cl = cell->fragment->length;
914 	}
915       }
916       if ( notDefault(s->background) )
917       { if ( isDefault(bg) || cell->fragment->length < bgl )
918 	{ bg = s->background;
919 	  bgl = cell->fragment->length;
920 	}
921       }
922     }
923 
924     fc->font	     = f;
925     fc->colour       = c;
926     fc->background   = bg;
927     fc->attributes   = attributes;
928     fc->right_margin = rm;
929     fc->left_margin  = lm;
930 
931     DEBUG(NAME_fragment, Cprintf("---> Font: %s; attributes: 0x%lx\n",
932 				 pp(f), attributes));
933   }
934 
935   fc->initial_state = FALSE;
936   fc->index = i;
937 }
938 
939 
940 static ISearchCache
newISearchCache(Editor e)941 newISearchCache(Editor e)
942 { ISearchCache ic = alloc(sizeof(struct isearch_cache));
943 
944   memset(ic, 0, sizeof(*ic));
945 
946   return ic;
947 }
948 
949 
950 static void
freeISearchCache(ISearchCache ic)951 freeISearchCache(ISearchCache ic)
952 { unalloc(sizeof(struct isearch_cache), ic);
953 }
954 
955 
956 static void
seek_editor(Any obj,long int index)957 seek_editor(Any obj, long int index)
958 { Editor e = obj;
959 
960   indexFragmentCache(e->fragment_cache, e, index);
961 }
962 
963 
964 static long
scan_editor(Any obj,long int index,int dir,int how,int category,int * eof)965 scan_editor(Any obj, long int index, int dir, int how, int category, int *eof)
966 { Editor e = obj;
967   TextBuffer tb = e->text_buffer;
968   SyntaxTable s = tb->syntax;
969   int size = tb->size;
970 
971   *eof = FALSE;
972 
973   if ( how == TEXT_SCAN_FOR )
974   { if ( dir > 0 )
975     { for(; index < size; index++)
976       { if ( tischtype(s, fetch_textbuffer(tb, index), category) )
977 	  goto out;
978       }
979       goto out_eof;
980     } else				/* dir < 0 */
981     { for(; index >= 0; index--)
982       { if ( tischtype(s, fetch_textbuffer(tb, index), category) )
983 	  goto out;
984       }
985       goto out_eof;
986     }
987   } else				/* TEXT_SKIP_OVER */
988   { if ( dir > 0 )
989     { for(; index < size; index++)
990       { if ( !tischtype(s, fetch_textbuffer(tb, index), category) )
991 	  goto out;
992       }
993       goto out_eof;
994     } else				/* dir < 0 */
995     { for(; index >= 0; index--)
996       { if ( !tischtype(s, fetch_textbuffer(tb, index), category) )
997 	  goto out;
998       }
999       goto out_eof;
1000     }
1001   }
1002 
1003 out_eof:
1004   *eof = TRUE;
1005 out:
1006   if ( index < 0 )
1007     index = 0;
1008   else if ( index > size )
1009     index = size;
1010 
1011   return index;
1012 }
1013 
1014 
1015 #define GRAPHICS_START 01		/* ^A */
1016 
1017 static long
fetch_editor(Any obj,TextChar tc)1018 fetch_editor(Any obj, TextChar tc)
1019 { Editor e = obj;
1020   FragmentCache fc = e->fragment_cache;
1021   long index = fc->index;
1022 
1023   tc->value.c      = Fetch(e, index);
1024   tc->type	   = CHAR_ASCII;
1025   tc->font         = fc->font;
1026   tc->colour       = fc->colour;
1027   tc->background   = fc->background;
1028   tc->attributes   = fc->attributes;
1029   tc->index	   = index;
1030 
1031   if ( tc->value.c == GRAPHICS_START &&
1032        Fetch(e, index+2) == GRAPHICS_START &&
1033        hasGetMethodObject(e, NAME_diagram) )
1034   { int grindex = Fetch(e, index+1);
1035     Graphical gr = get(e, NAME_diagram, toInt(grindex), EAV);
1036 
1037     if ( gr )
1038     { tc->value.graphical = gr;
1039       tc->type	         = CHAR_GRAPHICAL;
1040 
1041       indexFragmentCache(e->fragment_cache, e, index+3);
1042       return fc->index;
1043     }
1044   }
1045 
1046   if ( e->focus_function == NAME_Isearch )	/* actively searching */
1047   { ISearchCache ic = e->isearch_cache;
1048 
1049     if ( !ic->style )
1050     { Style s = getClassVariableValueObject(e, NAME_isearchOtherStyle);
1051 
1052       if ( !s ) s = NIL;
1053       ic->style = s;
1054     }
1055 
1056     if ( notNil(ic->style) )
1057     { Style s = ic->style;
1058     again:
1059 
1060       if ( index >= ic->hit_start && index < ic->hit_end )
1061       { if ( tc->value.c != '\n' )
1062 	{ tc->attributes |= s->attributes;
1063 	  if ( notDefault(s->font) )
1064 	    tc->font = s->font;
1065 	  if ( notDefault(s->colour) )
1066 	    tc->colour = s->colour;
1067 	  if ( notDefault(s->background) )
1068 	    tc->background = s->background;
1069 	}
1070       } else if ( notNil(e->search_string) )
1071       { int len = valInt(getSizeCharArray(e->search_string));
1072 	TextBuffer tb = e->text_buffer;
1073 
1074 	if ( len > 0 &&
1075 	     match_textbuffer(tb, index, &e->search_string->data,
1076 			      e->exact_case == ON, FALSE) )
1077 	{ ic->hit_start = index;
1078 	  ic->hit_end = index+len;
1079 
1080 	  goto again;
1081 	}
1082       }
1083     }
1084   }
1085 
1086   if ( e->mark_status != NAME_inactive &&
1087        InRegion(index, valInt(e->mark), valInt(e->caret)) )
1088   { Style s = (isisearchingEditor(e)
1089 	       ? getClassVariableValueObject(e, NAME_isearchStyle)
1090 	       : e->selection_style);
1091 
1092     if ( !s || isDefault(s) )
1093     { tc->attributes ^= TXT_HIGHLIGHTED;
1094     } else
1095     { tc->attributes |= s->attributes;
1096       if ( notDefault(s->font) )
1097 	tc->font = s->font;
1098       if ( notDefault(s->colour) )
1099 	tc->colour = s->colour;
1100       if ( notDefault(s->background) )
1101 	tc->background = s->background;
1102     }
1103   }
1104 
1105   if ( notNil(e->selected_fragment) )
1106   { Fragment fr = e->selected_fragment;
1107     Style s = e->selected_fragment_style;
1108 
1109     if ( index >= fr->start && index < fr->start + fr->length )
1110     { tc->attributes |= s->attributes;
1111       if ( notDefault(s->font) )
1112 	tc->font = s->font;
1113       if ( notDefault(s->colour) )
1114 	tc->colour = s->colour;
1115       if ( notDefault(s->background) )
1116 	tc->background = s->background;
1117     }
1118   }
1119 
1120   if ( isDefault(tc->font) )
1121     tc->font = e->font;
1122 
1123   indexFragmentCache(e->fragment_cache, e, ++index);
1124 
1125   return fc->index;
1126 }
1127 
1128 
1129 static void
margin_editor(Any obj,int * left,int * right)1130 margin_editor(Any obj, int *left, int *right)
1131 { Editor e = obj;
1132   FragmentCache fc = e->fragment_cache;
1133 
1134   *left  = fc->left_margin;
1135   *right = fc->right_margin;
1136 }
1137 
1138 
1139 static SeekFunction
getSeekFunctionEditor(Editor e)1140 getSeekFunctionEditor(Editor e)
1141 { answer(seek_editor);
1142 }
1143 
1144 
1145 static ScanFunction
getScanFunctionEditor(Editor e)1146 getScanFunctionEditor(Editor e)
1147 { answer(scan_editor);
1148 }
1149 
1150 
1151 static FetchFunction
getFetchFunctionEditor(Editor e)1152 getFetchFunctionEditor(Editor e)
1153 { answer(fetch_editor);
1154 }
1155 
1156 
1157 static MarginFunction
getMarginFunctionEditor(Editor e)1158 getMarginFunctionEditor(Editor e)
1159 { answer(margin_editor);
1160 }
1161 
1162 
1163 static Int
getFetchEditor(Editor e,Int where)1164 getFetchEditor(Editor e, Int where)
1165 { answer(toInt(Fetch(e, valInt(where))));
1166 }
1167 
1168 
1169 static RewindFunction
getRewindFunctionEditor(Editor e)1170 getRewindFunctionEditor(Editor e)
1171 { answer((RewindFunction) NULL);
1172 }
1173 
1174 
1175 
1176 
1177 		/********************************
1178 		*            REDRAW		*
1179 		********************************/
1180 
1181 static status
computeEditor(Editor e)1182 computeEditor(Editor e)
1183 { if ( notNil(e->request_compute) )
1184   { computeTextImage(e->image);
1185     ensureVisibleEditor(e, DEFAULT, DEFAULT);
1186     if ( e->request_compute != NAME_showCaretAt )
1187       updateCursorEditor(e);
1188     if ( notNil(e->margin) )
1189       changedEntireImageGraphical(e->margin);
1190 
1191     computeDevice(e);
1192   }
1193 
1194   succeed;
1195 }
1196 
1197 
1198 		/********************************
1199 		*            WINDOW		*
1200 		********************************/
1201 
1202 static Int
normalise_index(Editor e,Int index)1203 normalise_index(Editor e, Int index)
1204 { if ( valInt(index) < 0 )
1205     return ZERO;
1206   if ( valInt(index) > e->text_buffer->size )
1207     return toInt(e->text_buffer->size);
1208 
1209   return index;
1210 }
1211 
1212 
1213 static Name
where_editor(Editor e,Int index)1214 where_editor(Editor e, Int index)
1215 { int i = valInt(index);
1216 
1217   if ( i < valInt(getStartTextImage(e->image, ONE)) )
1218     return NAME_above;			/* above window */
1219 
1220   ComputeGraphical(e->image);
1221   if ( i < valInt(e->image->end) )
1222     return NAME_inside;			/* In the window */
1223 
1224   if ( i == e->text_buffer->size &&	/* standing on EOF that is in window */
1225        e->image->eof_in_window == ON )
1226     return NAME_inside;
1227 
1228   return NAME_below;
1229 }
1230 
1231 
1232 static status
ensureVisibleEditor(Editor e,Int from,Int to)1233 ensureVisibleEditor(Editor e, Int from, Int to)
1234 { TextImage ti = e->image;
1235 
1236   from = (isDefault(from) ? e->caret : normalise_index(e, from));
1237   to   = (isDefault(to) ? from : normalise_index(e, to));
1238 
1239   if ( !(from == to && ensureVisibleTextImage(ti, from)) )
1240   { Before(from, to);
1241 
1242     if ( where_editor(e, to) == NAME_below )
1243     { DEBUG(NAME_scroll, Cprintf("Caret below window\n"));
1244       startTextImage(ti, getScanTextBuffer(e->text_buffer,
1245 					   getStartTextImage(ti,ONE),
1246 					   NAME_line, ONE,
1247 					   NAME_start),
1248 		     ZERO);
1249 
1250       if ( where_editor(e, to) == NAME_below )
1251       { DEBUG(NAME_scroll, Cprintf("More than one line: centering\n"));
1252 	centerWindowEditor(e, to);
1253 	ComputeGraphical(ti);
1254       }
1255     } else if ( valInt(to) < valInt(getStartTextImage(ti, ONE)) )
1256     { startTextImage(ti, getScanTextBuffer(e->text_buffer,
1257 					   getStartTextImage(ti,ONE),
1258 					   NAME_line, toInt(-1),
1259 					   NAME_start),
1260 		     ZERO);
1261       ComputeGraphical(ti);
1262       if ( valInt(to) < valInt(getStartTextImage(ti, ONE)) )
1263       { centerWindowEditor(e, to);
1264 	ComputeGraphical(ti);
1265       }
1266     }
1267 
1268     if ( valInt(from) < valInt(getStartTextImage(ti, ONE)) )
1269     { while( valInt(from) < valInt(getStartTextImage(ti, ONE)) )
1270       { startTextImage(ti, getScanTextBuffer(e->text_buffer,
1271 					     getStartTextImage(ti,ONE),
1272 					     NAME_line, toInt(-1),
1273 					     NAME_start),
1274 		       ZERO);
1275 	ComputeGraphical(ti);
1276       }
1277     }
1278   }
1279 
1280   ensureCaretInWindowEditor(e);		/* play save */
1281 
1282   succeed;
1283 }
1284 
1285 
1286 status
normaliseEditor(Editor e,Int start,Int end)1287 normaliseEditor(Editor e, Int start, Int end)
1288 { return ensureVisibleEditor(e, start, end); /* TBD: delete */
1289 }
1290 
1291 
1292 static status
ensureCaretInWindowEditor(Editor e)1293 ensureCaretInWindowEditor(Editor e)
1294 { Int start;
1295 
1296   ComputeGraphical(e->image);
1297 
1298   if ( valInt(e->caret) < valInt(start = getStartTextImage(e->image, ONE)) )
1299     CaretEditor(e, start);
1300   else
1301   { if ( valInt(e->caret) >= valInt(e->image->end) )
1302     { if ( e->image->eof_in_window == ON )
1303 	CaretEditor(e, e->image->end);
1304       else
1305       { long ie = max(0, valInt(e->image->end) - 1);
1306 
1307 	CaretEditor(e, toInt(ie));
1308       }
1309     }
1310   }
1311 
1312   return requestComputeGraphical(e->scroll_bar, DEFAULT);
1313 }
1314 
1315 
1316 static Int
getFirstEditor(Editor e)1317 getFirstEditor(Editor e)
1318 { ComputeGraphical(e->image);
1319 
1320   answer(getLineNumberEditor(e, getStartTextImage(e->image, ONE)));
1321 }
1322 
1323 
1324 static Int
countLinesEditor(Editor e,Int from,Int to)1325 countLinesEditor(Editor e, Int from, Int to)
1326 { answer(toInt(count_lines_textbuffer(e->text_buffer,
1327 				      valInt(from), valInt(to))));
1328 }
1329 
1330 
1331 static Point
getLinesVisibleEditor(Editor e)1332 getLinesVisibleEditor(Editor e)
1333 { Int first = getFirstEditor(e);
1334   Int last;
1335 
1336   last = add(countLinesEditor(e, getStartTextImage(e->image, ONE),
1337 			      e->image->end), first);
1338 
1339   answer(answerObject(ClassPoint, first, sub(last, ONE), EAV));
1340 }
1341 
1342 		/********************************
1343 		*            FEEDBACK		*
1344 		********************************/
1345 
1346 Any
ReceiverOfEditor(Editor e)1347 ReceiverOfEditor(Editor e)
1348 { if ( isObject(e->device) && instanceOfObject(e->device, ClassView) )
1349     return e->device;
1350 
1351   return e;
1352 }
1353 
1354 
1355 static status
reportEditor(Editor e,Name kind,CharArray fm,int argc,Any * argv)1356 reportEditor(Editor e, Name kind, CharArray fm, int argc, Any *argv)
1357 { if ( notNil(e->error_message) )
1358   { string msg;
1359     StringObj str;
1360 
1361     if ( isDefault(fm) )
1362       fm = (CharArray) (kind == NAME_done ? NAME_done : CtoName(""));
1363 
1364     str_writefv(&msg, fm, argc, argv);
1365     str = StringToTempString(&msg);
1366 
1367     forwardReceiverCode(e->error_message, Receiver(e),
1368 			e, kind, str, EAV);
1369     considerPreserveObject(str);
1370     str_unalloc(&msg);
1371 
1372     succeed;
1373   }
1374 
1375   return reportVisual((VisualObj)e, kind, fm, argc, argv);
1376 }
1377 
1378 
1379 status
forwardModifiedEditor(Editor e,BoolObj val)1380 forwardModifiedEditor(Editor e, BoolObj val)
1381 { abortIsearchEditor(e, OFF);
1382 
1383   if ( notNil(e->modified_message) )
1384     forwardReceiverCode(e->modified_message, Receiver(e), val, EAV);
1385 
1386   succeed;
1387 }
1388 
1389 
1390 		/********************************
1391 		*        FUNCTION MAPPING	*
1392 		********************************/
1393 
1394 
1395 static Any
getKeyBindingEditor(Editor e,Name key)1396 getKeyBindingEditor(Editor e, Name key)
1397 { return getFunctionKeyBinding(e->bindings, key);
1398 }
1399 
1400 
1401 static status
keyBindingEditor(Editor e,Name key,Any function)1402 keyBindingEditor(Editor e, Name key, Any function)
1403 { return functionKeyBinding(e->bindings, key, function);
1404 }
1405 
1406 
1407 		/********************************
1408 		*            TYPING		*
1409 		********************************/
1410 
1411 static status
typedEditor(Editor e,EventId id)1412 typedEditor(Editor e, EventId id)
1413 { if ( notNil(e->focus_function) )
1414   { if ( send(e, e->focus_function, id, EAV) )
1415       succeed;
1416     else
1417       assign(e, focus_function, NIL);
1418   }
1419 
1420   return typedKeyBinding(e->bindings, id, Receiver(e));
1421 }
1422 
1423 
1424 
1425 static status
event_editor(Editor e,EventObj ev)1426 event_editor(Editor e, EventObj ev)
1427 { if ( isAEvent(ev, NAME_focus) )
1428   { if ( isAEvent(ev, NAME_activateKeyboardFocus) )
1429       send(e->text_cursor, NAME_active, ON, EAV);
1430     else if ( isAEvent(ev, NAME_deactivateKeyboardFocus) )
1431       send(e->text_cursor, NAME_active, OFF, EAV);
1432 
1433     succeed;
1434   }
1435 
1436   if ( eventDevice(e, ev) )
1437     succeed;
1438 
1439   if ( isAEvent(ev, NAME_keyboard) )
1440     return send(e, NAME_typed, ev, EAV);
1441 
1442 					/* delete mode on button down */
1443   if ( isDownEvent(ev) )
1444   { PceWindow sw = getWindowGraphical((Graphical)e);
1445 
1446     if ( sw && notNil(sw) && sw->keyboard_focus != (Graphical)e )
1447       send(e, NAME_keyboardFocus, ON, EAV);
1448 
1449     endIsearchEditor(e, OFF);
1450     assign(e, focus_function, NIL);
1451   }
1452 
1453   if ( mapWheelMouseEvent(ev, e) )
1454     succeed;
1455 
1456 					/* @editor_recogniser is a hook */
1457 					/* to allow for host-language */
1458 					/* level redefinition */
1459 
1460   { Any recogniser = getObjectFromReferencePce(PCE, NAME_editorRecogniser);
1461 
1462     if ( recogniser && instanceOfObject(recogniser, ClassRecogniser) )
1463       return send(recogniser, NAME_event, ev, EAV);
1464   }
1465 					/* Built-in version */
1466 
1467   if ( isAEvent(ev, NAME_button) )
1468   { Int where = getIndexTextImage(e->image, ev);
1469     Modifier select_modifier = getClassVariableValueObject(e, NAME_selectModifier);
1470     Modifier caret_modifier = getClassVariableValueObject(e, NAME_caretModifier);
1471 
1472     if ( !where )
1473       fail;
1474 
1475     if ( isDownEvent(ev) )
1476     { status rval = FAIL;
1477 
1478       focusGraphical((Graphical) e, DEFAULT, DEFAULT, DEFAULT);
1479 
1480       if ( isAEvent(ev, NAME_msLeftDown) )
1481       { if ( hasModifierEvent(ev, select_modifier) )
1482 	{ if ( getMulticlickEvent(ev) == NAME_double )
1483 	    assign(e, selection_unit, NAME_word);
1484 	  else if ( getMulticlickEvent(ev) == NAME_triple )
1485 	    assign(e, selection_unit, NAME_line);
1486 	  else
1487 	    assign(e, selection_unit, NAME_character);
1488 
1489 	  rval = selectionOriginEditor(e, where);
1490 	}
1491 
1492 	if ( hasModifierEvent(ev, caret_modifier) &&
1493 	     getMulticlickEvent(ev) == NAME_single )
1494 	  rval = CaretEditor(e, where);
1495 
1496 	return rval;
1497       }
1498 
1499       if ( isAEvent(ev, NAME_msRightDown) &&
1500 	   hasModifierEvent(ev, select_modifier) )
1501 	return selectionExtendEditor(e, where);
1502     } else
1503     { if ( isAEvent(ev, NAME_msMiddleUp) &&
1504 	   hasModifierEvent(ev, select_modifier) )
1505       { send(e, NAME_paste, NAME_primary, EAV);
1506 	succeed;
1507       } else if ( hasModifierEvent(ev, select_modifier) )
1508       { selectionExtendEditor(e, where);
1509 	selectionToCutBufferEditor(e, DEFAULT);
1510       }
1511     }
1512 
1513     if ( hasModifierEvent(ev, select_modifier) &&
1514 	 (isAEvent(ev, NAME_msLeftDrag) || isAEvent(ev, NAME_msRightDrag)) )
1515       return selectionExtendEditor(e, where);
1516   }
1517 
1518   fail;
1519 }
1520 
1521 
1522 static status
eventEditor(Editor e,EventObj ev)1523 eventEditor(Editor e, EventObj ev)
1524 { status rval = event_editor(e, ev);
1525 
1526   if ( rval && !isFreedObj(e) )
1527   { if ( (isAEvent(ev, NAME_keyboard) || isAEvent(ev, NAME_button) ) &&
1528 	 e->bindings->prefix == NAME_ )
1529       markUndoTextBuffer(e->text_buffer);
1530 
1531     if ( notNil(e->text_buffer) && notNil(e->request_compute) )
1532     { assign(e, caret, normalise_index(e, e->caret));
1533       ensureVisibleEditor(e, e->caret, e->caret);
1534     }
1535   }
1536 
1537   return rval;
1538 }
1539 
1540 
1541 static status
cuaKeyAsPrefixEditor(Editor e,EventObj ev)1542 cuaKeyAsPrefixEditor(Editor e, EventObj ev)
1543 { if ( instanceOfObject(ev, ClassEvent) )
1544   { if ( (valInt(ev->buttons) & BUTTON_shift) )
1545       succeed;
1546   }
1547 
1548   if ( !HasSelection(e) )
1549     succeed;
1550 
1551   if ( ws_wait_for_key(250) )
1552     succeed;
1553 
1554   fail;
1555 }
1556 
1557 
1558 		/********************************
1559 		*         EDIT FUNCTIONS	*
1560 		********************************/
1561 
1562 #define UArg(arg)	  (isDefault(arg) ? 1 : valInt(arg))
1563 #define MustBeEditable(e) TRY( verify_editable_editor(e) )
1564 
1565 
1566 static status
verify_editable_editor(Editor e)1567 verify_editable_editor(Editor e)
1568 { if ( e->editable == OFF )
1569   { send(e, NAME_report, NAME_warning, CtoName("Text is read-only"), EAV);
1570     fail;
1571   }
1572 
1573   succeed;
1574 }
1575 
1576 
1577 static status
insert_editor(Editor e,Int times,Int chr,int fill)1578 insert_editor(Editor e, Int times, Int chr, int fill)
1579 { wint_t c;
1580   LocalString(s, TRUE, 1);		/* wide-character string! */
1581 
1582   MustBeEditable(e);
1583   if ( HasSelection(e) &&
1584        getClassVariableValueObject(e, NAME_insertDeletesSelection) == ON )
1585     deleteSelectionEditor(e);
1586 
1587   if ( fill && e->fill_mode == ON )
1588     return insertSelfFillEditor(e, times, chr);
1589 
1590   if ( isDefault(times) )
1591     times = ONE;
1592 
1593   if ( isDefault(chr) )
1594   { EventObj ev = EVENT->value;
1595 
1596     if ( instanceOfObject(ev, ClassEvent) && isAEvent(ev, NAME_printable) )
1597       c = valInt(getIdEvent(ev));
1598     else
1599       return errorPce(e, NAME_noCharacter);
1600   } else
1601     c = valInt(chr);
1602 
1603   str_store(s, 0, c);
1604   s->s_size = 1;
1605   insert_textbuffer(e->text_buffer, Caret(e), valInt(times), s);
1606 
1607   if ( tisclosebrace(e->text_buffer->syntax, c) &&
1608        getClassVariableValueObject(e, NAME_showOpenBracket) == ON )
1609     showMatchingBracketEditor(e, sub(e->caret, ONE));
1610 
1611   succeed;
1612 }
1613 
1614 
1615 static status
insertSelfEditor(Editor e,Int times,Int chr)1616 insertSelfEditor(Editor e, Int times, Int chr)
1617 { return insert_editor(e, times, chr, TRUE);
1618 }
1619 
1620 
1621 static status
insertQuotedEditor(Editor e,Int times,Int chr)1622 insertQuotedEditor(Editor e, Int times, Int chr)
1623 { return insert_editor(e, times, chr, FALSE);
1624 }
1625 
1626 
1627 static status
showMatchingBracketEditor(Editor e,Int arg)1628 showMatchingBracketEditor(Editor e, Int arg)
1629 { Int here = (isDefault(arg) ? e->caret : arg);
1630   Int there_pos, here_bracket, there_bracket;
1631   TextBuffer tb = e->text_buffer;
1632 
1633   if ( !tischtype(tb->syntax, valInt(getFetchEditor(e, here)), OB|CB) )
1634   { here = sub(here, ONE);
1635     if ( !tisclosebrace(tb->syntax, valInt(getFetchEditor(e, here))) )
1636       fail;
1637   }
1638 
1639   here_bracket = getFetchEditor(e, here);
1640   if ( (there_pos = getMatchingBracketTextBuffer(tb, here, DEFAULT)) &&
1641        (there_bracket = getFetchEditor(e, there_pos)) &&
1642        tismatching(tb->syntax, valInt(there_bracket), valInt(here_bracket)) )
1643   { if ( !electricCaretEditor(e, there_pos, DEFAULT) )
1644     { Int sol = getScanTextBuffer(e->text_buffer, there_pos, NAME_line,
1645 				  ZERO, NAME_start);
1646       Int eol = getScanTextBuffer(e->text_buffer, sol, NAME_line,
1647 				  ZERO, NAME_end);
1648       Int len = toInt(valInt(eol) - valInt(sol));
1649       StringObj line = getContentsTextBuffer(e->text_buffer, sol, len);
1650       send(e, NAME_report, NAME_status, CtoName("Matches %s"), line, EAV);
1651     }
1652   } else
1653     return errorPce(e, NAME_noMatchingBracket);
1654 
1655   succeed;
1656 }
1657 
1658 
1659 static status
newlineEditor(Editor e,Int arg)1660 newlineEditor(Editor e, Int arg)
1661 { MustBeEditable(e);
1662   return insert_textbuffer(e->text_buffer, Caret(e), UArg(arg),
1663 			   str_nl(&e->text_buffer->buffer));
1664 }
1665 
1666 
1667 static status
openLineEditor(Editor e,Int arg)1668 openLineEditor(Editor e, Int arg)
1669 { Int caret = e->caret;
1670 
1671   MustBeEditable(e);
1672   insert_textbuffer(e->text_buffer, Caret(e), UArg(arg),
1673 		    str_nl(&e->text_buffer->buffer));
1674   return CaretEditor(e, caret);		/* do not move the caret */
1675 }
1676 
1677 
1678 static status
caretEditor(Editor e,Int c)1679 caretEditor(Editor e, Int c)
1680 { if ( isDefault(c) )
1681     c = toInt(e->text_buffer->size);
1682 
1683   selection_editor(e, DEFAULT, c, DEFAULT);
1684   return requestComputeGraphical(e, DEFAULT);
1685 }
1686 
1687 
1688 static status
CaretEditor(Editor e,Int c)1689 CaretEditor(Editor e, Int c)
1690 { if ( e->caret != c )
1691     return qadSendv(e, NAME_caret, 1, (Any *)&c);
1692 
1693   succeed;
1694 }
1695 
1696 
1697 static status
pushMarkEditor(Editor e,Int mark)1698 pushMarkEditor(Editor e, Int mark)
1699 { Vector ring = e->mark_ring;
1700   Int high = getHighIndexVector(ring);
1701 
1702   if ( valInt(high) < 16 )		/* TBD: parameter */
1703     elementVector(ring, add(high, ONE), NIL);
1704 
1705   shiftVector(ring, ONE);
1706   elementVector(ring, ONE, mark);
1707 
1708   succeed;
1709 }
1710 
1711 
1712 static status
markEditor(Editor e,Int mark,Name status)1713 markEditor(Editor e, Int mark, Name status)
1714 { if ( isDefault(mark) )
1715     mark = e->caret;
1716 
1717   pushMarkEditor(e, mark);
1718   selection_editor(e, mark, DEFAULT, status);
1719   return requestComputeGraphical(e, DEFAULT);
1720 }
1721 
1722 
1723 static status
markStatusEditor(Editor e,Name status)1724 markStatusEditor(Editor e, Name status)
1725 { if ( e->mark_status != status )
1726     selection_editor(e, DEFAULT, DEFAULT, status);
1727 
1728   succeed;
1729 }
1730 
1731 
1732 static status
forwardCharEditor(Editor e,Int arg)1733 forwardCharEditor(Editor e, Int arg)
1734 { return CaretEditor(e, toInt(Caret(e) + UArg(arg)));
1735 }
1736 
1737 
1738 static status
backwardCharEditor(Editor e,Int arg)1739 backwardCharEditor(Editor e, Int arg)
1740 { return CaretEditor(e, toInt(Caret(e) - UArg(arg)));
1741 }
1742 
1743 
1744 static status
forwardWordEditor(Editor e,Int arg)1745 forwardWordEditor(Editor e, Int arg)
1746 { return CaretEditor(e,
1747 		     getScanTextBuffer(e->text_buffer,
1748 				       e->caret, NAME_word, toInt(UArg(arg)-1),
1749 				       NAME_end));
1750 }
1751 
1752 
1753 static status
backwardWordEditor(Editor e,Int arg)1754 backwardWordEditor(Editor e, Int arg)
1755 { backwardCharEditor(e, ONE);
1756   return CaretEditor(e,
1757 		     getScanTextBuffer(e->text_buffer,
1758 				       e->caret, NAME_word, toInt(1-UArg(arg)),
1759 				       NAME_start));
1760 }
1761 
1762 
1763 static status
beginningOfLineEditor(Editor e,Int arg)1764 beginningOfLineEditor(Editor e, Int arg)
1765 { Int caret;
1766 
1767   if ( e->image->wrap == NAME_word &&
1768        isDefault(arg) &&
1769        (caret = getBeginningOfLineCursorTextImage(e->image, e->caret)) )
1770   {
1771   } else
1772   { caret = getScanTextBuffer(e->text_buffer,
1773 			      e->caret, NAME_line, toInt(1-UArg(arg)),
1774 			      NAME_start);
1775   }
1776 
1777   return CaretEditor(e, caret);
1778 }
1779 
1780 
1781 static status
endOfLineEditor(Editor e,Int arg)1782 endOfLineEditor(Editor e, Int arg)
1783 { Int caret;
1784 
1785   if ( e->image->wrap == NAME_word &&
1786        isDefault(arg) &&
1787        (caret = getEndOfLineCursorTextImage(e->image, e->caret)) )
1788   {
1789   } else
1790     caret = getScanTextBuffer(e->text_buffer,
1791 			      e->caret, NAME_line, toInt(UArg(arg)-1),
1792 			      NAME_end);
1793 
1794   return CaretEditor(e, caret);
1795 }
1796 
1797 
1798 static status
forwardSentenceEditor(Editor e,Int arg)1799 forwardSentenceEditor(Editor e, Int arg)
1800 { return CaretEditor(e, getScanTextBuffer(e->text_buffer,
1801 					  e->caret,
1802 					  NAME_sentence,
1803 					  toInt(UArg(arg)-1),
1804 					  NAME_end));
1805 }
1806 
1807 
1808 static status
backwardSentenceEditor(Editor e,Int arg)1809 backwardSentenceEditor(Editor e, Int arg)
1810 { return CaretEditor(e, getScanTextBuffer(e->text_buffer,
1811 					  e->caret,
1812 					  NAME_sentence,
1813 					  toInt(1-UArg(arg)),
1814 					  NAME_start));
1815 }
1816 
1817 
1818 static status
forwardParagraphEditor(Editor e,Int arg)1819 forwardParagraphEditor(Editor e, Int arg)
1820 { return CaretEditor(e, getScanTextBuffer(e->text_buffer,
1821 					  e->caret,
1822 					  NAME_paragraph,
1823 					  toInt(UArg(arg)-1),
1824 					  NAME_end));
1825 }
1826 
1827 
1828 static status
backwardParagraphEditor(Editor e,Int arg)1829 backwardParagraphEditor(Editor e, Int arg)
1830 { return CaretEditor(e, getScanTextBuffer(e->text_buffer,
1831 					  e->caret,
1832 					  NAME_paragraph,
1833 					  toInt(1-UArg(arg)),
1834 					  NAME_start));
1835 }
1836 
1837 
1838 static status
forwardTermEditor(Editor e,Int arg)1839 forwardTermEditor(Editor e, Int arg)
1840 { return CaretEditor(e, getScanTextBuffer(e->text_buffer,
1841 					  e->caret,
1842 					  NAME_term,
1843 					  toInt(UArg(arg)),
1844 					  NAME_end));
1845 }
1846 
1847 
1848 static status
backwardTermEditor(Editor e,Int arg)1849 backwardTermEditor(Editor e, Int arg)
1850 { return CaretEditor(e, getScanTextBuffer(e->text_buffer,
1851 					  e->caret,
1852 					  NAME_term,
1853 					  toInt(-UArg(arg)),
1854 					  NAME_start));
1855 }
1856 
1857 
1858 static status
skipBlanksEditor(Editor e,Int arg)1859 skipBlanksEditor(Editor e, Int arg)
1860 { TextBuffer tb  = e->text_buffer;
1861   Name direction = (UArg(arg) >= 0 ? NAME_forward : NAME_backward);
1862   BoolObj skipnl    = (UArg(arg) >= 4 || UArg(arg) <= -4 ? ON : OFF);
1863 
1864   return CaretEditor(e, getSkipBlanksTextBuffer(tb, e->caret,
1865 						direction, skipnl));
1866 }
1867 
1868 
1869 static status
pointToTopOfFileEditor(Editor e,Int arg)1870 pointToTopOfFileEditor(Editor e, Int arg)
1871 { return lineNumberEditor(e, toInt(UArg(arg)));
1872 }
1873 
1874 
1875 static status
pointToBottomOfFileEditor(Editor e,Int arg)1876 pointToBottomOfFileEditor(Editor e, Int arg)
1877 { return CaretEditor(e, getScanTextBuffer(e->text_buffer,
1878 					  toInt(e->text_buffer->size),
1879 					  NAME_line, toInt(1-UArg(arg)),
1880 					  NAME_end));
1881 }
1882 
1883 
1884 static status
pointToTopOfWindowEditor(Editor e,Int arg)1885 pointToTopOfWindowEditor(Editor e, Int arg)
1886 { return CaretEditor(e, getStartTextImage(e->image, arg));
1887 }
1888 
1889 
1890 static status
pointToBottomOfWindowEditor(Editor e,Int arg)1891 pointToBottomOfWindowEditor(Editor e, Int arg)
1892 { if ( isDefault(arg) )
1893     arg = ONE;
1894 
1895   return CaretEditor(e, getStartTextImage(e->image, neg(arg)));
1896 }
1897 
1898 
1899 static status
nextLineEditor(Editor e,Int arg,Int column)1900 nextLineEditor(Editor e, Int arg, Int column)
1901 { Int caret;
1902   TextBuffer tb = e->text_buffer;
1903   int n = UArg(arg);
1904 
1905   if ( isDefault(column) )
1906     column = getColumnEditor(e, e->caret);
1907 
1908   caret = getScanTextBuffer(tb, e->caret, NAME_line, toInt(n), NAME_start);
1909 
1910   if ( valInt(caret) ==	tb->size &&
1911        ( caret == e->caret || Fetch(e, tb->size-1) != '\n' ) &&
1912        n == 1 &&
1913        e->editable == ON )
1914   { endOfLineEditor(e, DEFAULT);
1915 
1916     return send(e, NAME_newline, ONE, EAV);
1917   }
1918 
1919   return CaretEditor(e, getColumnLocationEditor(e, column, caret));
1920 }
1921 
1922 
1923 static status
previousLineEditor(Editor e,Int arg,Int column)1924 previousLineEditor(Editor e, Int arg, Int column)
1925 { return nextLineEditor(e, toInt(-UArg(arg)), column);
1926 }
1927 
1928 
1929 static status
deleteCharEditor(Editor e,Int arg)1930 deleteCharEditor(Editor e, Int arg)
1931 { MustBeEditable(e);
1932 
1933   return delete_textbuffer(e->text_buffer, Caret(e), UArg(arg));
1934 }
1935 
1936 
1937 static status
backwardDeleteCharEditor(Editor e,Int arg)1938 backwardDeleteCharEditor(Editor e, Int arg)
1939 { MustBeEditable(e);
1940   return delete_textbuffer(e->text_buffer, Caret(e), -UArg(arg));
1941 }
1942 
1943 
1944 static status
cutOrDeleteCharEditor(Editor e,Int arg)1945 cutOrDeleteCharEditor(Editor e, Int arg)
1946 { MustBeEditable(e);
1947 
1948   if ( isDefault(arg) && HasSelection(e) )
1949     return send(e, NAME_cut, EAV);
1950   else
1951     return send(e, NAME_deleteChar, arg, EAV);
1952 }
1953 
1954 
1955 static status
cutOrBackwardDeleteCharEditor(Editor e,Int arg)1956 cutOrBackwardDeleteCharEditor(Editor e, Int arg)
1957 { MustBeEditable(e);
1958 
1959   if ( isDefault(arg) && HasSelection(e) )
1960     return send(e, NAME_cut, EAV);
1961   else
1962     return send(e, NAME_backwardDeleteChar, arg, EAV);
1963 }
1964 
1965 
1966 static status
copyEditor(Editor e)1967 copyEditor(Editor e)
1968 { StringObj s = getSelectedEditor(e);
1969   DisplayObj d = getDisplayGraphical((Graphical)e);
1970 
1971   if ( s && d )
1972     return send(d, NAME_copy, s, EAV);
1973 
1974   fail;
1975 }
1976 
1977 
1978 static status
cutEditor(Editor e)1979 cutEditor(Editor e)
1980 { MustBeEditable(e);
1981 
1982   if ( send(e, NAME_copy, EAV) )
1983     return deleteSelectionEditor(e);
1984 
1985   fail;
1986 }
1987 
1988 
1989 static status
pasteEditor(Editor e,Name which)1990 pasteEditor(Editor e, Name which)
1991 { DisplayObj d = getDisplayGraphical((Graphical)e);
1992   CharArray str;
1993   Any selection;
1994 
1995   MustBeEditable(e);
1996 
1997   if ( d &&
1998        (selection=get(d, NAME_paste, which, EAV)) &&
1999        (str=checkType(selection, TypeCharArray, NIL)) )
2000   { if ( HasSelection(e) &&
2001 	 getClassVariableValueObject(e, NAME_insertDeletesSelection) == ON )
2002       deleteSelectionEditor(e);
2003 
2004     return insertEditor(e, str);
2005   }
2006 
2007   fail;
2008 }
2009 
2010 		 /*******************************
2011 		 *	    CURSOR KEYS		*
2012 		 *******************************/
2013 
2014 static int
buttons()2015 buttons()
2016 { if ( instanceOfObject(EVENT->value, ClassEvent) )
2017   { EventObj ev = EVENT->value;
2018 
2019     return valInt(ev->buttons);
2020   }
2021 
2022   return 0;
2023 }
2024 
2025 
2026 static status
caretMoveExtendSelectionEditor(Editor e,Int oldcaret)2027 caretMoveExtendSelectionEditor(Editor e, Int oldcaret)
2028 { if ( e->mark_status != NAME_active )
2029   { assign(e, selection_unit, NAME_character);
2030     assign(e, selection_origin, oldcaret);
2031   }
2032 
2033   selectionExtendEditor(e, e->caret);
2034   if ( getClassVariableValueObject(e, NAME_autoCopy) == ON )
2035     copyEditor(e);
2036 
2037   succeed;
2038 }
2039 
2040 
2041 static Int
getUpDownColumnEditor(Editor e)2042 getUpDownColumnEditor(Editor e)
2043 { if ( e->image->wrap == NAME_word )
2044     return getUpDownColumnTextImage(e->image, e->caret);
2045   else
2046     return getColumnEditor(e, e->caret);
2047 }
2048 
2049 
2050 static status
cursorUpEditor(Editor e,Int arg,Int column)2051 cursorUpEditor(Editor e, Int arg, Int column)
2052 { int bts = buttons();
2053   Int caret = e->caret;
2054 
2055   if ( isDefault(arg) )
2056     arg = ONE;
2057 
2058   if ( !(bts & BUTTON_shift) )
2059     markStatusEditor(e, NAME_inactive);
2060 
2061   if ( bts & BUTTON_control )
2062     backwardParagraphEditor(e, arg);
2063   else if ( e->image->wrap == NAME_word &&
2064 	    (caret = getUpDownCursorTextImage(e->image, caret,
2065 					      neg(arg), column)) )
2066     return CaretEditor(e, caret);
2067   else if ( e->text_cursor->displayed == OFF && !isisearchingEditor(e) )
2068     return scrollDownEditor(e, ONE);
2069   else
2070     previousLineEditor(e, arg, column);
2071 
2072   if ( bts & BUTTON_shift )
2073     caretMoveExtendSelectionEditor(e, caret);
2074 
2075   succeed;
2076 }
2077 
2078 
2079 static status
cursorDownEditor(Editor e,Int arg,Int column)2080 cursorDownEditor(Editor e, Int arg, Int column)
2081 { int bts = buttons();
2082   Int caret = e->caret;
2083 
2084   if ( isDefault(arg) )
2085     arg = ONE;
2086 
2087   if ( !(bts & BUTTON_shift) )
2088     markStatusEditor(e, NAME_inactive);
2089 
2090   if ( bts & BUTTON_control )
2091     forwardParagraphEditor(e, arg);
2092   else if ( e->image->wrap == NAME_word &&
2093 	    (caret = getUpDownCursorTextImage(e->image, caret, arg, column)) )
2094     return CaretEditor(e, caret);
2095   else if ( e->text_cursor->displayed == OFF && !isisearchingEditor(e) )
2096     return scrollUpEditor(e, ONE);
2097   else
2098     nextLineEditor(e, arg, column);
2099 
2100   if ( bts & BUTTON_shift )
2101     caretMoveExtendSelectionEditor(e, caret);
2102 
2103   succeed;
2104 }
2105 
2106 
2107 static status
cursorLeftEditor(Editor e,Int arg)2108 cursorLeftEditor(Editor e, Int arg)
2109 { int bts = buttons();
2110   Int caret = e->caret;
2111 
2112   if ( !(bts & BUTTON_shift) )
2113     markStatusEditor(e, NAME_inactive);
2114 
2115   if ( bts & BUTTON_control )
2116     backwardWordEditor(e, arg);
2117   else
2118     backwardCharEditor(e, arg);
2119 
2120   if ( bts & BUTTON_shift )
2121     caretMoveExtendSelectionEditor(e, caret);
2122 
2123   succeed;
2124 }
2125 
2126 
2127 static status
cursorRightEditor(Editor e,Int arg)2128 cursorRightEditor(Editor e, Int arg)
2129 { int bts = buttons();
2130   Int caret = e->caret;
2131 
2132   if ( !(bts & BUTTON_shift) )
2133     markStatusEditor(e, NAME_inactive);
2134 
2135   if ( bts & BUTTON_control )
2136     forwardWordEditor(e, arg);
2137   else
2138     forwardCharEditor(e, arg);
2139 
2140   if ( bts & BUTTON_shift )
2141     caretMoveExtendSelectionEditor(e, caret);
2142 
2143   succeed;
2144 }
2145 
2146 
2147 static status
cursorEndEditor(Editor e,Int arg)2148 cursorEndEditor(Editor e, Int arg)
2149 { int bts = buttons();
2150   Int caret = e->caret;
2151 
2152   if ( !(bts & BUTTON_shift) )
2153     markStatusEditor(e, NAME_inactive);
2154 
2155   if ( bts & BUTTON_control )
2156     pointToBottomOfFileEditor(e, arg);
2157   else
2158     endOfLineEditor(e, arg);
2159 
2160   if ( bts & BUTTON_shift )
2161     caretMoveExtendSelectionEditor(e, caret);
2162 
2163   succeed;
2164 }
2165 
2166 
2167 static status
cursorHomeEditor(Editor e,Int arg)2168 cursorHomeEditor(Editor e, Int arg)
2169 { int bts = buttons();
2170   Int caret = e->caret;
2171 
2172   if ( !(bts & BUTTON_shift) )
2173     markStatusEditor(e, NAME_inactive);
2174 
2175   if ( bts & BUTTON_control )
2176     pointToTopOfFileEditor(e, arg);
2177   else
2178     beginningOfLineEditor(e, arg);
2179 
2180   if ( bts & BUTTON_shift )
2181     caretMoveExtendSelectionEditor(e, caret);
2182 
2183   succeed;
2184 }
2185 
2186 
2187 static status
cursorPageUpEditor(Editor e,Int arg)2188 cursorPageUpEditor(Editor e, Int arg)
2189 { int bts = buttons();
2190   Int caret = e->caret;
2191 
2192   if ( !(bts & BUTTON_shift) )
2193     markStatusEditor(e, NAME_inactive);
2194 
2195   scrollDownEditor(e, arg);
2196 
2197   if ( bts & BUTTON_shift )
2198     caretMoveExtendSelectionEditor(e, caret);
2199 
2200   succeed;
2201 }
2202 
2203 
2204 static status
cursorPageDownEditor(Editor e,Int arg)2205 cursorPageDownEditor(Editor e, Int arg)
2206 { int bts = buttons();
2207   Int caret = e->caret;
2208 
2209   if ( !(bts & BUTTON_shift) )
2210     markStatusEditor(e, NAME_inactive);
2211 
2212   scrollUpEditor(e, arg);
2213 
2214   if ( bts & BUTTON_shift )
2215     caretMoveExtendSelectionEditor(e, caret);
2216 
2217   succeed;
2218 }
2219 
2220 		/********************************
2221 		*        KILLING/YANKING	*
2222 		********************************/
2223 
2224 static status
yankEditor(Editor e,Int times)2225 yankEditor(Editor e, Int times)
2226 { CharArray s = killRegister(ZERO);
2227 
2228   times = toInt(labs(UArg(times)));
2229   MustBeEditable(e);
2230 
2231   if ( s )
2232   { Int mark = e->caret;		/* otherwise moves at the insert */
2233 
2234     insertTextBuffer(e->text_buffer, e->caret, s, times);
2235     assign(e, mark, mark);
2236 
2237     succeed;
2238   }
2239 
2240   fail;
2241 }
2242 
2243 
2244 static status
killEditor(Editor e,Int from,Int to)2245 killEditor(Editor e, Int from, Int to)
2246 { Int length;
2247   CharArray text;
2248 
2249   MustBeEditable(e);
2250 
2251   Before(from, to);
2252   length = sub(to, from);
2253   text = (CharArray)getContentsTextBuffer(e->text_buffer, from, length);
2254 
2255   if ( from == e->kill_location )
2256     appendKill(text);
2257   else if ( to == e->kill_location )
2258     prependKill(text);
2259   else
2260     newKill(text);
2261 
2262   deleteTextBuffer(e->text_buffer, from, length);
2263   assign(e, kill_location, from);
2264 
2265   succeed;
2266 }
2267 
2268 
2269 static status
grabEditor(Editor e,Int from,Int to)2270 grabEditor(Editor e, Int from, Int to)
2271 { Int length;
2272 
2273   Before(from, to);
2274   length = sub(to, from);
2275 
2276   newKill((CharArray) getContentsTextBuffer(e->text_buffer, from, length));
2277   send(e, NAME_report, NAME_status, CtoName("Grabbed"), EAV);
2278   assign(e, kill_location, NIL);
2279 
2280   succeed;
2281 }
2282 
2283 
2284 static status
killWordEditor(Editor e,Int arg)2285 killWordEditor(Editor e, Int arg)
2286 { Int end = getScanTextBuffer(e->text_buffer, e->caret,
2287 			      NAME_word, toInt(UArg(arg)-1), NAME_end);
2288 
2289   MustBeEditable(e);
2290   return killEditor(e, e->caret, end);
2291 }
2292 
2293 
2294 static status
backwardKillWordEditor(Editor e,Int arg)2295 backwardKillWordEditor(Editor e, Int arg)
2296 { Int start = getScanTextBuffer(e->text_buffer, sub(e->caret, ONE),
2297 				NAME_word, toInt(1-UArg(arg)), NAME_start);
2298 
2299   MustBeEditable(e);
2300   return killEditor(e, start, e->caret);
2301 }
2302 
2303 
2304 static status
killLineEditor(Editor e,Int arg)2305 killLineEditor(Editor e, Int arg)
2306 { Int end;
2307   Int lines;
2308 
2309   MustBeEditable(e);
2310   if ( notDefault(arg) )
2311     lines = arg;
2312   else
2313   { if ( tisendsline(e->text_buffer->syntax, Fetch(e, valInt(e->caret))) )
2314       return killEditor(e, e->caret, add(e->caret, ONE));
2315 
2316     if ( e->image->wrap == NAME_word &&
2317 	 (end = getEndOfLineCursorTextImage(e->image, e->caret)) )
2318     { int i = valInt(end);
2319       TextBuffer tb = e->text_buffer;
2320 
2321       while(i<tb->size && Fetch(e, i) == ' ')
2322 	i++;
2323       return killEditor(e, e->caret, toInt(i));
2324     } else
2325       lines = ZERO;
2326   }
2327 
2328   end = getScanTextBuffer(e->text_buffer, e->caret,
2329 			  NAME_line, lines, NAME_end);
2330 
2331   return killEditor(e, e->caret, end);
2332 }
2333 
2334 
2335 static status
killSentenceEditor(Editor e,Int arg)2336 killSentenceEditor(Editor e, Int arg)
2337 { Int end = getScanTextBuffer(e->text_buffer,
2338 			      e->caret,
2339 			      NAME_sentence,
2340 			      toInt(UArg(arg)-1),
2341 			      NAME_end);
2342   MustBeEditable(e);
2343   return killEditor(e, e->caret, end);
2344 }
2345 
2346 
2347 static status
killParagraphEditor(Editor e,Int arg)2348 killParagraphEditor(Editor e, Int arg)
2349 { Int end = getScanTextBuffer(e->text_buffer,
2350 			      e->caret,
2351 			      NAME_paragraph,
2352 			      toInt(UArg(arg)-1),
2353 			      NAME_end);
2354   MustBeEditable(e);
2355   return killEditor(e, e->caret, end);
2356 }
2357 
2358 
2359 static status
killTermEditor(Editor e,Int arg)2360 killTermEditor(Editor e, Int arg)
2361 { Int end = getScanTextBuffer(e->text_buffer,
2362 			      e->caret,
2363 			      NAME_term,
2364 			      toInt(UArg(arg)),
2365 			      NAME_end);
2366   MustBeEditable(e);
2367   return killEditor(e, e->caret, end);
2368 }
2369 
2370 
2371 static status
killOrGrabRegionEditor(Editor e,Int arg)2372 killOrGrabRegionEditor(Editor e, Int arg)
2373 { status rval;
2374 
2375   if ( !HasSelection(e) )
2376   { send(e, NAME_report, NAME_warning, CtoName("No mark"), EAV);
2377     succeed;
2378   }
2379 
2380   if ( isDefault(arg) )
2381     rval = killEditor(e, e->caret, e->mark);
2382   else
2383     rval = grabEditor(e, e->caret, e->mark);
2384 
2385   if ( rval )
2386     markStatusEditor(e, NAME_inactive);
2387 
2388   return rval;
2389 }
2390 
2391 		/********************************
2392 		*          MISCELENEOUS		*
2393 		********************************/
2394 
2395 static status
undefinedEditor(Editor e)2396 undefinedEditor(Editor e)
2397 { send(e, NAME_report, NAME_warning, CtoName("Undefined"), EAV);
2398 
2399   succeed;
2400 }
2401 
2402 
2403 static status
keyboardQuitEditor(Editor e,Int arg)2404 keyboardQuitEditor(Editor e, Int arg)
2405 { assign(e, focus_function, NIL);
2406   abortIsearchEditor(e, OFF);
2407   markStatusEditor(e, NAME_inactive);
2408   send(e, NAME_report, NAME_warning, CtoName("Quit"), EAV);
2409 
2410   succeed;
2411 }
2412 
2413 
2414 static status
undoEditor(Editor e)2415 undoEditor(Editor e)
2416 { Int caret;
2417 
2418   if ( (caret = getUndoTextBuffer(e->text_buffer)) )
2419   { return CaretEditor(e, caret);
2420   } else
2421   { send(e, NAME_report, NAME_warning,
2422 	 CtoName("No (further) undo information"), EAV);
2423     fail;
2424   }
2425 }
2426 
2427 
2428 static status
setMarkEditor(Editor e,Int arg)2429 setMarkEditor(Editor e, Int arg)
2430 { if ( isDefault(arg) )
2431   { markEditor(e, arg, NAME_active);
2432 
2433     send(e, NAME_report, NAME_status, CtoName("Mark set"), EAV);
2434   } else				/* rotate through mark-ring */
2435   { Int to = getElementVector(e->mark_ring, ONE);
2436 
2437     if ( notNil(to) )
2438     { shiftVector(e->mark_ring, toInt(-1));
2439       elementVector(e->mark_ring,
2440 		    getHighIndexVector(e->mark_ring),
2441 		    to);
2442       return CaretEditor(e, to);
2443     } else
2444       send(e, NAME_report, NAME_warning, CtoName("No marks"), EAV);
2445   }
2446 
2447   succeed;
2448 }
2449 
2450 
2451 static status
switchCaseModeEditor(Editor e,Int arg)2452 switchCaseModeEditor(Editor e, Int arg)
2453 { if ( isDefault(arg) )
2454     assign(e, exact_case, e->exact_case == ON ? OFF : ON);
2455   else
2456     assign(e, exact_case, UArg(arg) > 0 ? OFF : ON);
2457 
2458   send(e, NAME_report, NAME_status, CtoName("%s case"),
2459        e->exact_case == ON ? CtoName("Exact") : CtoName("Either"), EAV);
2460 
2461   succeed;
2462 }
2463 
2464 
2465 static status
pointToMarkEditor(Editor e)2466 pointToMarkEditor(Editor e)
2467 { return CaretEditor(e, e->mark);
2468 }
2469 
2470 
2471 static status
exchangePointAndMarkEditor(Editor e)2472 exchangePointAndMarkEditor(Editor e)
2473 { if ( notNil(e->mark) )
2474     return selection_editor(e, e->caret, e->mark, NAME_active);
2475 
2476   send(e, NAME_report, NAME_warning, CtoName("No mark"), EAV);
2477   fail;
2478 }
2479 
2480 
2481 static status
markWholeBufferEditor(Editor e)2482 markWholeBufferEditor(Editor e)
2483 { TextBuffer tb = e->text_buffer;
2484 
2485   return ( CaretEditor(e, toInt(0)) &&
2486 	   markEditor(e, toInt(tb->size), NAME_active) &&
2487 	   copyEditor(e) );
2488 }
2489 
2490 
2491 static status
transposeWordEditor(Editor e)2492 transposeWordEditor(Editor e)
2493 { Int f1, t1, f2, t2;
2494   Int caret = e->caret;
2495 
2496   MustBeEditable(e);
2497   backwardWordEditor(e, ONE);	f1 = e->caret;
2498   forwardWordEditor(e, ONE);	t1 = e->caret;
2499   forwardWordEditor(e, ONE);	t2 = e->caret;
2500   backwardWordEditor(e, ONE);	f2 = e->caret;
2501   if ( transposeTextBuffer(e->text_buffer, f1, t1, f2, t2) )
2502     CaretEditor(e, add(caret, sub(sub(t2, f2), sub(t1, f1))));
2503 
2504   succeed;
2505 }
2506 
2507 
2508 static status
transposeLinesEditor(Editor e)2509 transposeLinesEditor(Editor e)
2510 { Int f1, t1, f2, t2;
2511   TextBuffer tb = e->text_buffer;
2512 
2513   MustBeEditable(e);
2514 
2515   t2 = getScanTextBuffer(tb, e->caret, NAME_line, ZERO, NAME_end);
2516   f2 = getScanTextBuffer(tb, e->caret, NAME_line, ZERO, NAME_start);
2517   t1 = sub(f2, ONE);
2518   f1 = getScanTextBuffer(tb, t1,       NAME_line, ZERO, NAME_start);
2519 
2520   if ( transposeTextBuffer(tb, f1, t1, f2, t2) )
2521     forwardCharEditor(e, sub(f1, f2));
2522 
2523   succeed;
2524 }
2525 
2526 
2527 static status
transposeTermsEditor(Editor e)2528 transposeTermsEditor(Editor e)
2529 { Int f1, t1, f2, t2;
2530   TextBuffer tb = e->text_buffer;
2531   int caret = valInt(e->caret);
2532 
2533   MustBeEditable(e);
2534 
2535   if ( !tisblank(tb->syntax, fetch_textbuffer(tb, caret)) &&
2536         tisblank(tb->syntax, fetch_textbuffer(tb, caret-1)) )
2537     caret--;
2538 
2539   f2 = getScanTextBuffer(tb, e->caret, NAME_term, ONE,       NAME_start);
2540   t2 = getScanTextBuffer(tb, f2,       NAME_term, ONE,       NAME_end);
2541   t1 = getScanTextBuffer(tb, e->caret, NAME_term, toInt(-1), NAME_end);
2542   f1 = getScanTextBuffer(tb, t1,       NAME_term, toInt(-1), NAME_start);
2543 
2544   if ( transposeTextBuffer(tb, f1, t1, f2, t2) )
2545     CaretEditor(e, add(e->caret, sub(sub(t2,f2), sub(t1, f1))));
2546 
2547   succeed;
2548 }
2549 
2550 
2551 static status
deleteHorizontalSpaceEditor(Editor e,Int arg)2552 deleteHorizontalSpaceEditor(Editor e, Int arg)
2553 { int f, t;
2554   int spaces = (isDefault(arg) ? 0 : valInt(arg));
2555   SyntaxTable syntax = e->text_buffer->syntax;
2556   TextBuffer tb = e->text_buffer;
2557 
2558   MustBeEditable(e);
2559   f = t = valInt(e->caret);
2560   if ( f > 0 &&
2561        !tisblank(syntax, Fetch(e, f)) && tisblank(syntax, Fetch(e, f-1)) )
2562     f--, t--;
2563   for( ; f > 0 && tisblank(syntax, Fetch(e, f-1)); f-- )
2564     ;
2565   for( ; t < tb->size && tisblank(syntax, Fetch(e, t)); t++ )
2566     ;
2567   delete_textbuffer(tb, f, t-f);
2568   insert_textbuffer(tb, f, spaces, str_spc(&tb->buffer));
2569 
2570   return CaretEditor(e, toInt(f+spaces));
2571 }
2572 
2573 
2574 static status
justOneSpaceEditor(Editor e)2575 justOneSpaceEditor(Editor e)
2576 { return deleteHorizontalSpaceEditor(e, ONE);
2577 }
2578 
2579 
2580 /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
2581 GNU-Emacs:
2582 On blank line, delete all surrounding blank lines, leaving just one.
2583 On isolated blank line, delete that one.
2584 On nonblank line, delete any immediately following blank lines.
2585 - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
2586 
2587 static status
isBlankLine(Editor e,Int sol)2588 isBlankLine(Editor e, Int sol)
2589 { TextBuffer tb = e->text_buffer;
2590   Int eol = getSkipBlanksTextBuffer(tb, sol, NAME_forward, OFF);
2591 
2592   if ( Fetch(e, valInt(eol)) == '\n' )
2593   { Cprintf("blank at %s\n", pp(sol));
2594     succeed;
2595   }
2596 
2597   fail;
2598 }
2599 
2600 
2601 static status
deleteBlankLinesEditor(Editor e)2602 deleteBlankLinesEditor(Editor e)
2603 { TextBuffer tb = e->text_buffer;
2604   Int to = ZERO, from = ZERO;
2605   Int sol;
2606   Int caret = NIL;
2607 
2608   MustBeEditable(e);
2609 
2610   sol = getScanTextBuffer(tb, e->caret, NAME_line, ZERO, NAME_start);
2611 
2612   if ( !isBlankLine(e, sol) )
2613   { sol = getScanTextBuffer(tb, e->caret, NAME_line, ONE, NAME_start);
2614     if ( isBlankLine(e, sol) )
2615     { from = sol;
2616       to   = getSkipBlanksTextBuffer(tb, from, NAME_forward, ON);
2617     }
2618   } else
2619   { from = getSkipBlanksTextBuffer(tb, e->caret, NAME_backward, ON);
2620     to   = getSkipBlanksTextBuffer(tb, e->caret, NAME_forward, ON);
2621 
2622     if ( valInt(to) > valInt(from) )
2623     { int open = valInt(countLinesEditor(e, from, to)) > 2;
2624 
2625       characterTextBuffer(tb, from, toInt('\n'));
2626       from = add(from, ONE);
2627       caret = from;
2628       if ( open )
2629       { characterTextBuffer(tb, from, toInt('\n'));
2630 	from = add(from, ONE);
2631       }
2632     }
2633   }
2634 
2635   if ( valInt(to) > valInt(from) )
2636   { deleteTextBuffer(tb, from, sub(to, from));
2637     if ( notNil(caret) )
2638       CaretEditor(e, caret);
2639   }
2640 
2641   succeed;
2642 }
2643 
2644 
2645 static status
gosmacsTransposeEditor(Editor e)2646 gosmacsTransposeEditor(Editor e)
2647 { long caret = valInt(e->caret);
2648 
2649   MustBeEditable(e);
2650   if ( caret >= 2 )
2651   { char c1, c2;
2652 
2653     c1 = Fetch(e, caret-2);
2654     c2 = Fetch(e, caret-1);
2655     characterTextBuffer(e->text_buffer, toInt(caret-2), toInt(c2));
2656     characterTextBuffer(e->text_buffer, toInt(caret-1), toInt(c1));
2657 
2658     succeed;
2659   }
2660 
2661   fail;
2662 }
2663 
2664 
2665 static status
transposeCharsEditor(Editor e)2666 transposeCharsEditor(Editor e)
2667 { long caret = valInt(e->caret);
2668 
2669   MustBeEditable(e);
2670   if ( caret >= 1 && caret < e->text_buffer->size )
2671   { wint_t c1, c2;
2672 
2673     c1 = Fetch(e, caret-1);
2674     c2 = Fetch(e, caret);
2675     characterTextBuffer(e->text_buffer, toInt(caret-1), toInt(c2));
2676     characterTextBuffer(e->text_buffer, toInt(caret), toInt(c1));
2677 
2678     succeed;
2679   }
2680 
2681   fail;
2682 }
2683 
2684 		/********************************
2685 		*            FILES		*
2686 		********************************/
2687 
2688 static status
saveBufferEditor(Editor e,Int arg)2689 saveBufferEditor(Editor e, Int arg)
2690 { status rval = SUCCEED;
2691 
2692   if ( e->text_buffer->modified == ON && isDefault(arg) )
2693   { if ( notNil(e->file) )
2694     { if ( saveEditor(e, DEFAULT) )
2695       { CmodifiedTextBuffer(e->text_buffer, OFF);
2696 	send(e, NAME_report, NAME_status,
2697 	     CtoName("Buffer saved in %N"), e->file, EAV);
2698       } else
2699       { send(e, NAME_report, NAME_error,
2700 	     CtoName("Failed to save buffer into %N"), e->file, EAV);
2701 	rval = FAIL;
2702       }
2703     } else
2704     { send(e, NAME_report, NAME_error, CtoName("No current file"), EAV);
2705       rval = FAIL;
2706     }
2707   } else
2708   { send(e, NAME_report, NAME_status, CtoName("No changes need saving"), EAV);
2709   }
2710 
2711   return rval;
2712 }
2713 
2714 
2715 		/********************************
2716 		*        CHARACTER CASE		*
2717 		********************************/
2718 
2719 static status
downcaseRegionEditor(Editor e)2720 downcaseRegionEditor(Editor e)
2721 { Int from = e->mark;
2722   Int to   = e->caret;
2723 
2724   MustBeEditable(e);
2725   if ( isDefault(from) )
2726     fail;
2727 
2728   Before(from, to);
2729   return downcaseTextBuffer(e->text_buffer, from, sub(to, from));
2730 }
2731 
2732 
2733 static status
upcaseRegionEditor(Editor e)2734 upcaseRegionEditor(Editor e)
2735 { Int from = e->mark;
2736   Int to   = e->caret;
2737 
2738   MustBeEditable(e);
2739   if ( isDefault(from) )
2740     fail;
2741 
2742   Before(from, to);
2743   return upcaseTextBuffer(e->text_buffer, from, sub(to, from));
2744 }
2745 
2746 
2747 static status
capitaliseRegionEditor(Editor e)2748 capitaliseRegionEditor(Editor e)
2749 { Int from = e->mark;
2750   Int to   = e->caret;
2751 
2752   MustBeEditable(e);
2753   if ( isDefault(from) )
2754     fail;
2755 
2756   Before(from, to);
2757   return capitaliseTextBuffer(e->text_buffer, from, sub(to, from));
2758 }
2759 
2760 
2761 static status
downcasePreviousWordEditor(Editor e,Int arg)2762 downcasePreviousWordEditor(Editor e, Int arg)
2763 { Int f = getScanTextBuffer(e->text_buffer,
2764 			    sub(e->caret, ONE), NAME_word, toInt(1-UArg(arg)),
2765 			    NAME_start);
2766   MustBeEditable(e);
2767   return downcaseTextBuffer(e->text_buffer, f, sub(e->caret, f));
2768 }
2769 
2770 
2771 static status
upcasePreviousWordEditor(Editor e,Int arg)2772 upcasePreviousWordEditor(Editor e, Int arg)
2773 { Int f = getScanTextBuffer(e->text_buffer,
2774 			    sub(e->caret, ONE), NAME_word, toInt(1-UArg(arg)),
2775 			    NAME_start);
2776   MustBeEditable(e);
2777   return upcaseTextBuffer(e->text_buffer, f, sub(e->caret, f));
2778 }
2779 
2780 
2781 static status
capitalisePreviousWordEditor(Editor e,Int arg)2782 capitalisePreviousWordEditor(Editor e, Int arg)
2783 { Int f = getScanTextBuffer(e->text_buffer,
2784 			    sub(e->caret, ONE), NAME_word, toInt(1-UArg(arg)),
2785 			    NAME_start);
2786   MustBeEditable(e);
2787   return capitaliseTextBuffer(e->text_buffer, f, sub(e->caret, f));
2788 }
2789 
2790 
2791 static status
downcaseWordEditor(Editor e,Int arg)2792 downcaseWordEditor(Editor e, Int arg)
2793 { Int to = getScanTextBuffer(e->text_buffer,
2794 			     e->caret, NAME_word, toInt(UArg(arg)-1),
2795 			     NAME_end);
2796   MustBeEditable(e);
2797   downcaseTextBuffer(e->text_buffer, e->caret, sub(to, e->caret));
2798   return CaretEditor(e, to);
2799 }
2800 
2801 
2802 static status
upcaseWordEditor(Editor e,Int arg)2803 upcaseWordEditor(Editor e, Int arg)
2804 { Int to = getScanTextBuffer(e->text_buffer,
2805 			     e->caret, NAME_word, toInt(UArg(arg)-1),
2806 			     NAME_end);
2807   MustBeEditable(e);
2808   upcaseTextBuffer(e->text_buffer, e->caret, sub(to, e->caret));
2809   return CaretEditor(e, to);
2810 }
2811 
2812 
2813 static status
capitaliseWordEditor(Editor e,Int arg)2814 capitaliseWordEditor(Editor e, Int arg)
2815 { Int to = getScanTextBuffer(e->text_buffer,
2816 			     e->caret, NAME_word, toInt(UArg(arg)-1),
2817 			     NAME_end);
2818   MustBeEditable(e);
2819   capitaliseTextBuffer(e->text_buffer, e->caret, sub(to, e->caret));
2820   return CaretEditor(e, to);
2821 }
2822 
2823 
2824 static status
toggleCharCaseEditor(Editor e)2825 toggleCharCaseEditor(Editor e)
2826 { long caret = valInt(e->caret);
2827 
2828   MustBeEditable(e);
2829   if ( caret >= 1 )
2830   { char c;
2831 
2832     c = Fetch(e, caret-1);
2833     if ( iswupper(c) )
2834       c = towlower(c);
2835     else if ( iswlower(c) )
2836       c = towupper(c);
2837     else
2838       succeed;
2839 
2840     return characterTextBuffer(e->text_buffer, toInt(caret-1), toInt(c));
2841   }
2842 
2843   fail;
2844 
2845 }
2846 
2847 
2848 		/********************************
2849 		*          INDENT/UNDENT        *
2850 		*********************************/
2851 
2852 static long
start_of_line(Editor e,Int where)2853 start_of_line(Editor e, Int where)
2854 { TextBuffer tb = e->text_buffer;
2855 
2856   if ( isDefault(where) )
2857     where = e->caret;
2858   where = normalise_index(e, where);
2859 
2860   return valInt(getScanTextBuffer(tb, where, NAME_line, ZERO, NAME_start));
2861 }
2862 
2863 
2864 static long
end_of_line(Editor e,Int where)2865 end_of_line(Editor e, Int where)
2866 { TextBuffer tb = e->text_buffer;
2867 
2868   if ( isDefault(where) )
2869     where = e->caret;
2870   where = normalise_index(e, where);
2871 
2872   return valInt(getScanTextBuffer(tb, where, NAME_line, ZERO, NAME_end));
2873 }
2874 
2875 
2876 static void
get_region_editor(Editor e,Int * from,Int * to)2877 get_region_editor(Editor e, Int *from, Int *to)
2878 { *from = normalise_index(e, e->mark);
2879   *to   = normalise_index(e, e->caret);
2880   Before(*from, *to);
2881 }
2882 
2883 
2884 static status
blankLineEditor(Editor e,Int where)2885 blankLineEditor(Editor e, Int where)
2886 { TextBuffer tb = e->text_buffer;
2887   long sol = start_of_line(e, where);
2888 
2889   for( ; ; sol++)
2890   { char c = fetch_textbuffer(tb, sol);
2891 
2892     if ( tisblank(tb->syntax, c) )
2893       continue;
2894     if ( tisendsline(tb->syntax, c) )
2895       succeed;
2896     fail;
2897   }
2898 }
2899 
2900 
2901 static Int
getIndentationEditor(Editor e,Int where,Regex re)2902 getIndentationEditor(Editor e, Int where, Regex re)
2903 { TextBuffer tb = e->text_buffer;
2904   int col;
2905   Int n;
2906   long sol = start_of_line(e, where);
2907   long eoi;
2908 
2909   if ( isDefault(re) )
2910   { eoi = valInt(getSkipBlanksTextBuffer(tb, toInt(sol), NAME_forward, OFF));
2911   } else
2912   { long eol = end_of_line(e, where);
2913     eoi = ((n=getMatchRegex(re, tb, toInt(sol), toInt(eol))) ? sol+valInt(n)
2914 							     : sol);
2915   }
2916 
2917   for(col = 0; sol < eoi; sol++)
2918   { switch( fetch_textbuffer(tb, sol) )
2919     { case '\t':
2920 	col++;
2921 	col = Round(col, valInt(e->tab_distance));
2922 	continue;
2923       case '\b':
2924 	col--;
2925 	continue;
2926       default:
2927         col++;
2928         continue;
2929     }
2930   }
2931 
2932   answer(toInt(col));
2933 }
2934 
2935 
2936 static status
alignEditor(Editor e,Int column,Int where)2937 alignEditor(Editor e, Int column, Int where)
2938 { TextBuffer tb = e->text_buffer;
2939   long here = valInt(normalise_index(e, notDefault(where) ? where : e->caret));
2940   long txt;
2941   int txtcol, tabs, spaces;
2942   int col = valInt(column);
2943   int tabd = valInt(e->tab_distance);
2944 
2945 					/* find text before `here' */
2946   for( txt = here-1;
2947        txt >= 0 && tisblank(tb->syntax, fetch_textbuffer(tb, txt));
2948        txt--)
2949     ;
2950   txt++;
2951   txtcol = valInt(getColumnEditor(e, toInt(txt)));
2952   DEBUG(NAME_align, Cprintf("col = %d; txt = %ld; txtcol = %d\n",
2953 			    col, txt, txtcol));
2954 
2955   if ( col <= txtcol )
2956   { tabs = 0;
2957     if ( txt == 1 || tisendsline(tb->syntax, fetch_textbuffer(tb, txt-1)) )
2958       spaces = 0;
2959     else
2960       spaces = 1;
2961   } else
2962   { if ( tb->indent_tabs == OFF )
2963       tabs = 0;
2964     else
2965       tabs = col / tabd - txtcol / tabd;
2966     spaces = (tabs == 0 ? col - txtcol : col % tabd);
2967   }
2968   DEBUG(NAME_align, Cprintf("tabs = %d; spaces = %d\n", tabs, spaces));
2969 
2970 					/* delete old indent */
2971   delete_textbuffer(tb, txt, here-txt);
2972   insert_textbuffer(tb, txt, tabs, str_tab(&tb->buffer));
2973   insert_textbuffer(tb, txt+tabs, spaces, str_spc(&tb->buffer));
2974 
2975   succeed;
2976 }
2977 
2978 
2979 /*  Set the indentation of a line to be `column'
2980 */
2981 
2982 static status
alignOneLineEditor(Editor e,Int where,Int column)2983 alignOneLineEditor(Editor e, Int where, Int column)
2984 { TextBuffer tb = e->text_buffer;
2985   long sol = start_of_line(e, where);
2986   long sot;
2987   int tabs, spaces;
2988   int col;
2989 
2990   if ( isDefault(column) )
2991     column = e->left_margin;
2992   col = valInt(column);
2993   if ( col < 0 )
2994     col = 0;
2995 
2996   for(sot = sol;
2997       sot < tb->size && tisblank(tb->syntax, fetch_textbuffer(tb, sot));
2998       sot++)
2999     ;
3000 					/* delete old indent */
3001   delete_textbuffer(tb, sol, sot-sol);
3002   if ( tb->indent_tabs == OFF )
3003     tabs = 0;
3004   else
3005     tabs = col / valInt(e->tab_distance);
3006   spaces = (tabs == 0 ? col : col % valInt(e->tab_distance));
3007   insert_textbuffer(tb, sol, tabs, str_tab(&tb->buffer));
3008   insert_textbuffer(tb, sol+tabs, spaces, str_spc(&tb->buffer));
3009 
3010   succeed;
3011 }
3012 
3013 
3014 static status
alignLineEditor(Editor e,Int arg)3015 alignLineEditor(Editor e, Int arg)	/* align line on indentation arg */
3016 { MustBeEditable(e);
3017   return alignOneLineEditor(e, e->caret, arg);
3018 }
3019 
3020 
3021 static status
alignRegionEditor(Editor e,Int arg)3022 alignRegionEditor(Editor e, Int arg)
3023 { Int from, to;
3024   TextBuffer tb = e->text_buffer;
3025 
3026   MustBeEditable(e);
3027   get_region_editor(e, &from, &to);
3028   e->internal_mark = valInt(to);
3029   while( valInt(from) < e->internal_mark )
3030   { alignOneLineEditor(e, from, arg);
3031     from = getScanTextBuffer(tb, from, NAME_line, ONE, NAME_start);
3032   }
3033 
3034   succeed;
3035 }
3036 
3037 
3038 static status
indentOneLineEditor(Editor e,Int where,Int arg)3039 indentOneLineEditor(Editor e, Int where, Int arg)
3040 { int col = valInt(getIndentationEditor(e, where, DEFAULT)) +
3041 	    UArg(arg) * valInt(e->indent_increment);
3042 
3043   return alignOneLineEditor(e, where, toInt(col));
3044 }
3045 
3046 
3047 static status
indentLineEditor(Editor e,Int arg)3048 indentLineEditor(Editor e, Int arg)
3049 { MustBeEditable(e);
3050   beginningOfLineEditor(e, DEFAULT);
3051   indentOneLineEditor(e, e->caret, arg);
3052   return skipBlanksEditor(e, DEFAULT);
3053 }
3054 
3055 
3056 static status
undentLineEditor(Editor e,Int arg)3057 undentLineEditor(Editor e, Int arg)
3058 { return indentLineEditor(e, toInt(-UArg(arg)));
3059 }
3060 
3061 
3062 static status
indentRegionEditor(Editor e,Int arg)3063 indentRegionEditor(Editor e, Int arg)
3064 { Int from, to;
3065   TextBuffer tb = e->text_buffer;
3066 
3067   MustBeEditable(e);
3068   SelectionRegion(e, from, to);
3069   e->internal_mark = valInt(to);
3070   while( valInt(from) < e->internal_mark )
3071   { indentOneLineEditor(e, from, arg);
3072     from = getScanTextBuffer(tb, from, NAME_line, ONE, NAME_start);
3073   }
3074 
3075   succeed;
3076 }
3077 
3078 
3079 static status
undentRegionEditor(Editor e,Int arg)3080 undentRegionEditor(Editor e, Int arg)
3081 { return indentRegionEditor(e, toInt(-UArg(arg)));
3082 }
3083 
3084 /* Insert a newline and copy the indentation of the last non-blank line.
3085 */
3086 
3087 static status
newlineAndIndentEditor(Editor e,Int arg)3088 newlineAndIndentEditor(Editor e, Int arg)
3089 { Int index;
3090   TextBuffer tb = e->text_buffer;
3091 
3092   MustBeEditable(e);
3093   endOfLineEditor(e, DEFAULT);
3094   newlineEditor(e, arg);
3095   index = e->caret;
3096   do
3097   { index = getScanTextBuffer(tb, index, NAME_line, toInt(-1), NAME_start);
3098     if ( !blankLineEditor(e, index) )
3099     { alignLineEditor(e, getIndentationEditor(e, index, DEFAULT));
3100       endOfLineEditor(e, DEFAULT);
3101       break;
3102     }
3103   } while( index != ZERO );
3104 
3105   succeed;
3106 }
3107 
3108 		/********************************
3109 		*         FILL/JUSTIFY		*
3110 		********************************/
3111 
3112 static status
autoFillModeEditor(Editor e,Int arg)3113 autoFillModeEditor(Editor e, Int arg)
3114 { BoolObj val;
3115   if ( isDefault(arg) )
3116     val = (e->fill_mode == ON ? OFF : ON);
3117   else
3118     val = (UArg(arg) > 0 ? ON : OFF);
3119   assign(e, fill_mode, val);
3120   send(e, NAME_report, NAME_status,
3121        CtoName("%sAuto Fill"), val == ON ? CtoName("") : CtoName("No "), EAV);
3122   succeed;
3123 }
3124 
3125 
3126 static status
setFillColumnEditor(Editor e,Int arg)3127 setFillColumnEditor(Editor e, Int arg)
3128 { if ( isDefault(arg) )
3129     send(e, NAME_report, NAME_inform,
3130 	 CtoName("Left margin: %d, Right margin: %d"),
3131 	 e->left_margin, e->right_margin, EAV);
3132   else if ( UArg(arg) > 0 )
3133     assign(e, right_margin, arg);
3134   else
3135     assign(e, left_margin, toInt(-UArg(arg)));
3136 
3137   succeed;
3138 }
3139 
3140 
3141 static status
fillEditor(Editor e,Int from,Int to,Int left_margin,Int right_margin,BoolObj justify)3142 fillEditor(Editor e,
3143 	   Int from, Int to,
3144 	   Int left_margin, Int right_margin,
3145 	   BoolObj justify)
3146 { TextBuffer tb = e->text_buffer;
3147   int rm  = valInt(isDefault(right_margin) ? e->right_margin : right_margin);
3148   int lm  = valInt(isDefault(left_margin)  ? e->left_margin  : left_margin);
3149   int pos = start_of_line(e, normalise_index(e, from));
3150   int end;
3151   int ep;				/* end of paragraph */
3152   int col;
3153   int p;
3154 
3155   MustBeEditable(e);
3156 
3157   end = valInt(normalise_index(e, to));
3158   if ( end > 0 && tisendsline(tb->syntax, fetch_textbuffer(tb, end-1)) )
3159     end--;
3160 
3161   while( pos < end )
3162   { int p0 = pos;
3163 
3164     DEBUG(NAME_fill, Cprintf("fill: region = %d ... %d\n", pos, end));
3165 
3166 					/* skip the separator */
3167     while( pos < end && parsep_line_textbuffer(tb, pos) )
3168     { pos = scan_textbuffer(tb, p=pos, NAME_line, 1, 'a');
3169       if ( pos <= p )			/* end of file? */
3170 	break;
3171     }
3172 
3173     ep = scan_textbuffer(tb, pos, NAME_paragraph, 0, 'z');
3174     if ( fetch_textbuffer(tb, ep-1) == '\n' )
3175       ep--;
3176     ep = min(ep, end);
3177     e->internal_mark = ep;
3178 
3179     col = 0;				/* Do the first line: keep indent */
3180     while( pos < e->internal_mark &&
3181 	   tisblank(tb->syntax, fetch_textbuffer(tb, pos)) )
3182     { if ( fetch_textbuffer(tb, pos) == '\t' )
3183         col = Round(col+1, valInt(e->tab_distance));
3184       else
3185 	col++;
3186       pos++;
3187     }
3188     DEBUG(NAME_fill, Cprintf("Filling first paragraph line from %d\n", pos));
3189     pos = fill_line_textbuffer(tb, pos, e->internal_mark,
3190 			       col, rm, justify == ON);
3191 
3192 					/* do the lines of the paragraph */
3193     while( pos < e->internal_mark && !parsep_line_textbuffer(tb, pos) )
3194     { alignOneLineEditor(e, toInt(pos), toInt(lm));
3195       pos = valInt(getSkipBlanksTextBuffer(tb, toInt(pos), NAME_forward, OFF));
3196       DEBUG(NAME_fill, Cprintf("Next paragraph line from %d\n", pos));
3197       pos = fill_line_textbuffer(tb, pos, e->internal_mark,
3198 				 lm, rm, justify == ON);
3199     }
3200     DEBUG(NAME_fill,
3201 	  Cprintf("%s end\n",
3202 		  pos < e->internal_mark ? "Paragraph" : "Region"));
3203 
3204 					/* correct end for inserts/deletes */
3205     end += e->internal_mark - ep;
3206     pos = max(pos, p0+1);		/* ensure progress */
3207   }
3208   changedTextBuffer(tb);		/* Not a neat place! */
3209 
3210   succeed;
3211 }
3212 
3213 
3214 static status
fillRegionEditor(Editor e)3215 fillRegionEditor(Editor e)
3216 { Int from, to;
3217   TextBuffer tb = e->text_buffer;
3218 
3219   MustBeEditable(e);
3220   SelectionRegion(e, from, to);
3221   from = getScanTextBuffer(tb, from, NAME_line, ZERO, NAME_start);
3222 
3223   return fillEditor(e, from, to, DEFAULT, DEFAULT, OFF);
3224 }
3225 
3226 
3227 static status
fillParagraphEditor(Editor e,Int arg)3228 fillParagraphEditor(Editor e, Int arg)
3229 { TextBuffer tb = e->text_buffer;
3230   Int from = getScanTextBuffer(tb, add(e->caret, ONE), NAME_paragraph,
3231 			       ZERO, NAME_start);
3232   Int to   = getScanTextBuffer(tb, sub(e->caret, ONE), NAME_paragraph,
3233 			       ZERO, NAME_end);
3234   BoolObj justify = (isDefault(arg) ? OFF : ON);
3235 
3236   return fillEditor(e, from, to, DEFAULT, DEFAULT, justify);
3237 }
3238 
3239 
3240 static status
justifyParagraphEditor(Editor e)3241 justifyParagraphEditor(Editor e)
3242 { TextBuffer tb = e->text_buffer;
3243   Int from = getScanTextBuffer(tb, add(e->caret, ONE), NAME_paragraph,
3244 			       ZERO, NAME_start);
3245   Int to   = getScanTextBuffer(tb, sub(e->caret, ONE), NAME_paragraph,
3246 			       ZERO, NAME_end);
3247 
3248   return fillEditor(e, from, to, DEFAULT, DEFAULT, ON);
3249 }
3250 
3251 
3252 static status
justifyRegionEditor(Editor e)3253 justifyRegionEditor(Editor e)
3254 { TextBuffer tb = e->text_buffer;
3255   Int from = e->mark;
3256   Int to   = e->caret;
3257 
3258   from = getScanTextBuffer(tb, from, NAME_line, ZERO, NAME_start);
3259 
3260   Before(from, to);
3261   return fillEditor(e, from, to, DEFAULT, DEFAULT, ON);
3262 }
3263 
3264 
3265 static status
insertSelfFillEditor(Editor e,Int times,Int chr)3266 insertSelfFillEditor(Editor e, Int times, Int chr)
3267 { TextBuffer tb = e->text_buffer;
3268   LocalString(s, TRUE, 1);
3269   wint_t c;
3270   Int le;
3271 
3272   MustBeEditable(e);
3273 
3274   if ( isDefault(times) )
3275     times = ONE;
3276 
3277   if ( isDefault(chr) )
3278   { EventObj ev = EVENT->value;
3279 
3280     if ( instanceOfObject(ev, ClassEvent) && isAEvent(ev, NAME_printable) )
3281       c = valInt(getIdEvent(ev));
3282     else
3283       return errorPce(e, NAME_noCharacter);
3284   } else
3285     c = valInt(chr);
3286 
3287   str_store(s, 0, c);
3288   s->s_size = 1;
3289   insert_textbuffer(e->text_buffer, Caret(e), valInt(times), s);
3290   le = getScanTextBuffer(tb, e->caret, NAME_line, ZERO, NAME_end);
3291 
3292   if ( valInt(getColumnEditor(e, le)) > valInt(e->right_margin) )
3293   { Regex re = getClassVariableValueObject(e, NAME_autoFillRegex);
3294 
3295     if ( !instanceOfObject(re, ClassRegex) )
3296       re = DEFAULT;
3297 
3298     send(e, NAME_autoFill, e->caret, re, EAV);
3299   }
3300 
3301   if ( tisclosebrace(e->text_buffer->syntax, c) &&
3302        getClassVariableValueObject(e, NAME_showOpenBracket) == ON )
3303     showMatchingBracketEditor(e, sub(e->caret, ONE));
3304 
3305   succeed;
3306 }
3307 
3308 
3309 static status
autoFillEditor(Editor e,Int caret,Regex re)3310 autoFillEditor(Editor e, Int caret, Regex re)
3311 { TextBuffer tb = e->text_buffer;
3312   Int from, to, lm;
3313 
3314   if ( isDefault(caret) )
3315     caret = e->caret;
3316   from = getScanTextBuffer(tb, e->caret, NAME_line, ZERO, NAME_start);
3317   to = getScanTextBuffer(tb, sub(e->caret, ONE), NAME_paragraph,
3318 			 ZERO, NAME_end);
3319 
3320   if ( isDefault(re) )
3321   { lm = getIndentationEditor(e, from, DEFAULT);
3322   } else
3323   { TextBuffer tb = e->text_buffer;
3324     long eol = end_of_line(e, from);
3325     Int n = getMatchRegex(re, tb, from, toInt(eol));
3326 
3327     if ( n )
3328     { from = add(from, n);
3329       lm = getColumnEditor(e, from);
3330 
3331       DEBUG(NAME_fill,
3332 	    Cprintf("autofill: n=%d, from=%d, lm=%d\n",
3333 		    valInt(n), valInt(from), valInt(lm)));
3334     } else
3335     { DEBUG(NAME_fill,
3336 	    Cprintf("autofill regex %p did not match\n", re));
3337 
3338       lm = getIndentationEditor(e, from, DEFAULT);
3339     }
3340   }
3341 
3342   fillEditor(e, from, to, lm, DEFAULT, OFF);
3343 
3344   succeed;
3345 }
3346 
3347 
3348 		/********************************
3349 		*           SEARCHING		*
3350 		********************************/
3351 
3352 static status
findCutBufferEditor(Editor e,Int arg)3353 findCutBufferEditor(Editor e, Int arg)
3354 { StringObj str;
3355   Int start = normalise_index(e, e->caret);
3356   int hit_start;
3357   int ign = (e->exact_case == OFF);
3358   int buffer = UArg(arg) - 1;
3359 
3360   if ( buffer < 0 || buffer > 7 )
3361   { send(e, NAME_report, NAME_error,
3362 	 CtoName("Illegal cut buffer: %d"), toInt(buffer+1));
3363     fail;
3364   }
3365 
3366   if ( (str = get(getDisplayGraphical((Graphical) e),
3367 		  NAME_cutBuffer, toInt(buffer), EAV)) == FAIL )
3368   { send(e, NAME_report, NAME_warning,
3369 	 CtoName("Failed to get cut buffer %d"), toInt(buffer+1));
3370     fail;
3371   }
3372 
3373   hit_start = find_textbuffer(e->text_buffer,
3374 			      valInt(start),
3375 			      &str->data,
3376 			      1, 'a', !ign, FALSE);
3377   if ( hit_start < 0 )
3378   { send(e, NAME_report, NAME_warning, CtoName("Failed search: %s"), str, EAV);
3379     fail;
3380   }
3381 
3382   selection_editor(e,
3383 		   toInt(hit_start),
3384 		   toInt(hit_start + str->data.s_size),
3385 		   NAME_highlight);
3386   ensureVisibleEditor(e, toInt(hit_start), toInt(hit_start + str->data.s_size));
3387   succeed;
3388 }
3389 
3390 
3391 static status
isisearchingEditor(Editor e)3392 isisearchingEditor(Editor e)
3393 { if ( e->focus_function == NAME_Isearch ||
3394        e->focus_function == NAME_StartIsearch )
3395     succeed;
3396 
3397   fail;
3398 }
3399 
3400 
3401 static status
StartIsearchEditor(Editor e,EventId id)3402 StartIsearchEditor(Editor e, EventId id)
3403 { Name cmd = getKeyBindingEditor(e, characterName(id));
3404 
3405   if ( cmd != NAME_isearchForward &&
3406        cmd != NAME_isearchBackward )
3407     assign(e, search_string, NIL);
3408 
3409   assign(e, focus_function, NAME_Isearch);
3410   return IsearchEditor(e, id);
3411 }
3412 
3413 
3414 static status
beginIsearchEditor(Editor e,Name direction)3415 beginIsearchEditor(Editor e, Name direction)
3416 { assign(e, search_direction,      direction);
3417   assign(e, search_wrapped,        NIL);
3418   assign(e, search_wrapped_warned, OFF);
3419   assign(e, search_base,           e->caret);
3420   assign(e, search_origin,         e->caret);
3421   assign(e, focus_function,        NAME_StartIsearch);
3422   selection_editor(e, e->caret, e->caret, NAME_highlight);
3423   send(e, NAME_report, NAME_status,
3424        CtoName("ISearch %s (type to search)"), direction, EAV);
3425 
3426   succeed;
3427 }
3428 
3429 
3430 static status
abortIsearchEditor(Editor e,BoolObj save_mark)3431 abortIsearchEditor(Editor e, BoolObj save_mark)
3432 { if ( isisearchingEditor(e) )
3433   { assign(e, focus_function, NIL);
3434     changedHitsEditor(e);
3435     if ( save_mark == ON )
3436       selection_editor(e, e->search_origin, DEFAULT, NAME_inactive);
3437     else
3438       selection_editor(e, DEFAULT, DEFAULT, NAME_inactive);
3439   }
3440 
3441   succeed;
3442 }
3443 
3444 
3445 static status
endIsearchEditor(Editor e,BoolObj save_mark)3446 endIsearchEditor(Editor e, BoolObj save_mark)
3447 { if ( isisearchingEditor(e) )
3448   { Name msg;
3449 
3450     abortIsearchEditor(e, save_mark);
3451     if ( save_mark )
3452       msg = CtoName("Mark saved where search started");
3453     else
3454       msg = NAME_;
3455 
3456     send(e, NAME_report, NAME_status, msg, EAV);
3457   }
3458 
3459   succeed;
3460 }
3461 
3462 
3463 static status
isearchForwardEditor(Editor e)3464 isearchForwardEditor(Editor e)
3465 { return beginIsearchEditor(e, NAME_forward);
3466 }
3467 
3468 
3469 static status
isearchBackwardEditor(Editor e)3470 isearchBackwardEditor(Editor e)
3471 { return beginIsearchEditor(e, NAME_backward);
3472 }
3473 
3474 
3475 static status
changedHitsEditor(Editor e)3476 changedHitsEditor(Editor e)
3477 { intptr_t len;
3478 
3479   if ( notNil(e->search_string) &&
3480        (len = valInt(getSizeCharArray(e->search_string))) > 0 )
3481   { intptr_t start = valInt(e->image->start);
3482     intptr_t end   = valInt(e->image->end);
3483     TextBuffer tb = e->text_buffer;
3484     PceString s  = &e->search_string->data;
3485     int ec = (e->exact_case == ON);
3486 
3487     while(start<end)
3488     { if ( match_textbuffer(tb, start, s, ec, FALSE) )
3489       { ChangedRegionEditor(e, toInt(start), toInt(start+len));
3490 	start += len;
3491       }
3492       start++;
3493     }
3494 
3495   }
3496 
3497   succeed;
3498 }
3499 
3500 
3501 static status
showIsearchHitEditor(Editor ed,Int start,Int end)3502 showIsearchHitEditor(Editor ed, Int start, Int end)
3503 { int s = valInt(start);
3504   int e = valInt(end);
3505   int wrapped;
3506   Int mark, caret;
3507   const char *fmt;
3508 
3509   if ( ed->search_direction == NAME_forward )
3510   { caret = toInt(max(s,e));
3511     mark  = toInt(min(s,e));
3512     wrapped = valInt(caret) < valInt(ed->search_origin);
3513   } else
3514   { caret = toInt(min(s,e));
3515     mark  = toInt(max(s,e));
3516     wrapped = valInt(caret) > valInt(ed->search_origin);
3517   }
3518 
3519   changedHitsEditor(ed);
3520   selection_editor(ed, mark, caret, NAME_highlight);
3521   ensureVisibleEditor(ed, mark, caret);
3522 
3523   if ( wrapped )
3524   { if ( isNil(ed->search_wrapped) )
3525       assign(ed, search_wrapped, NAME_wrapped);
3526   } else
3527   { if ( ed->search_wrapped == NAME_wrapped )
3528       assign(ed, search_wrapped, NAME_overWrapped);
3529   }
3530 
3531   if ( isNil(ed->search_wrapped) )
3532     fmt = "Isearch %s %I%s";
3533   else
3534     fmt = "Isearch %s (%s) %s";
3535 
3536   send(ed, NAME_report, NAME_status, CtoName(fmt),
3537        ed->search_direction, ed->search_wrapped, ed->search_string,
3538        EAV);
3539 
3540   succeed;
3541 }
3542 
3543 
3544 static status
extendSearchStringToWordEditor(Editor e)3545 extendSearchStringToWordEditor(Editor e)
3546 { TextBuffer tb = e->text_buffer;
3547   Int size = isNil(e->search_string) ? ZERO : getSizeCharArray(e->search_string);
3548   Int start, end;
3549 
3550   if ( e->search_direction == NAME_forward )
3551   { end = e->caret;
3552     start = sub(end, size);
3553   } else
3554   { start = e->caret;
3555     end   = add(start, size);
3556   }
3557 
3558   end = getScanTextBuffer(tb, end, NAME_word, ZERO, NAME_end);
3559   changedHitsEditor(e);
3560   assign(e, search_string, getContentsTextBuffer(tb, start, sub(end, start)));
3561   return showIsearchHitEditor(e, start, end);
3562 }
3563 
3564 
3565 static status
backwardDeleteCharSearchStringEditor(Editor e)3566 backwardDeleteCharSearchStringEditor(Editor e)
3567 { if ( notNil(e->search_string) )
3568   { Int size = getSizeCharArray(e->search_string);
3569 
3570     if ( size == ONE )
3571       assign(e, search_string, NIL);
3572     else
3573       deleteString(e->search_string, sub(size, ONE), DEFAULT);
3574   }
3575 
3576   succeed;
3577 }
3578 
3579 
3580 static status
executeSearchEditor(Editor e,Int chr,Int from)3581 executeSearchEditor(Editor e, Int chr, Int from)
3582 { int l, hit_start, hit_end;
3583   int times, start;
3584   int fwd = (e->search_direction == NAME_forward);
3585   int ign = (e->exact_case == OFF);
3586 
3587   if ( notDefault(chr) )
3588   { if ( isNil(e->search_string) )
3589       assign(e, search_string, newObject(ClassString, EAV));
3590     else
3591       changedHitsEditor(e);
3592 
3593     insertCharacterString(e->search_string, chr, DEFAULT, DEFAULT);
3594   }
3595 
3596   if ( isNil(e->search_string) ||
3597        (l=valInt(getSizeCharArray(e->search_string))) == 0 )
3598   { send(e, NAME_report, NAME_warning, CtoName("No search string"), EAV);
3599     abortIsearchEditor(e, OFF);
3600     succeed;
3601   }
3602 
3603   if ( fwd )
3604   { times = 1;
3605     start = valInt(e->mark);
3606   } else
3607   { times = -1;
3608     start = valInt(e->caret);
3609   }
3610   if ( notDefault(from) )
3611     start = valInt(from);
3612 
3613   if ( isDefault(chr) && e->mark != e->caret )
3614     start += times;
3615 
3616   hit_start = find_textbuffer(e->text_buffer,
3617 			      start,
3618 			      &e->search_string->data,
3619 			      times, 'a', !ign, FALSE);
3620   if ( hit_start < 0 )
3621   { if ( e->search_wrapped_warned == ON )
3622     { hit_start = find_textbuffer(e->text_buffer,
3623 				  fwd ? 0 : e->text_buffer->size,
3624 				  &e->search_string->data,
3625 				  times, 'a', !ign, FALSE);
3626       assign(e, search_wrapped_warned, OFF);
3627     }
3628   }
3629 
3630   if ( hit_start < 0 )
3631   { send(e, NAME_report, NAME_warning,
3632 	 CtoName("Failing ISearch: %s"), e->search_string, EAV);
3633     if ( e->search_wrapped_warned == OFF )
3634       assign(e, search_wrapped_warned, ON);
3635 
3636     succeed;
3637   }
3638   hit_end = hit_start + l;
3639 
3640   if ( isDefault(chr) && isDefault(from) )
3641     assign(e, search_base, toInt(fwd ? hit_start : hit_end-1));
3642 
3643   return showIsearchHitEditor(e, toInt(hit_start), toInt(hit_end));
3644 }
3645 
3646 
3647 static status
searchDirectionEditor(Editor e,Name dir)3648 searchDirectionEditor(Editor e, Name dir)
3649 { if ( dir != e->search_direction )
3650   { assign(e, search_direction, dir);
3651 
3652     if ( dir == NAME_forward )
3653     { if ( valInt(e->caret) < valInt(e->mark) )
3654 	selection_editor(e, e->caret, e->mark, DEFAULT);
3655       assign(e, search_base, e->mark);
3656     } else
3657     { if ( valInt(e->mark) < valInt(e->caret) )
3658 	selection_editor(e, e->caret, e->mark, DEFAULT);
3659       assign(e, search_base, e->mark);
3660     }
3661   }
3662 
3663   succeed;
3664 }
3665 
3666 
3667 static status
IsearchEditor(Editor e,EventId id)3668 IsearchEditor(Editor e, EventId id)
3669 { Int chr = id;				/* TBD: test for character */
3670   Name cnm = characterName(id);
3671   Name cmd = getKeyBindingEditor(e, cnm);
3672 
3673   if ( cmd == NAME_keyboardQuit )	/* abort the search */
3674   { selection_editor(e, e->search_origin, e->search_origin, NAME_inactive);
3675     endIsearchEditor(e, OFF);
3676 
3677     fail;
3678   }
3679   if ( cmd == NAME_isearchForward )
3680   { searchDirectionEditor(e, NAME_forward);
3681     return executeSearchEditor(e, DEFAULT, DEFAULT);
3682   }
3683   if ( cmd == NAME_isearchBackward )
3684   { searchDirectionEditor(e, NAME_backward);
3685     return executeSearchEditor(e, DEFAULT, DEFAULT);
3686   }
3687   if ( cmd == NAME_backwardDeleteChar ||
3688        cmd == NAME_cutOrBackwardDeleteChar ||
3689        cnm == NAME_backspace )		/* also if re-bound */
3690   { changedHitsEditor(e);
3691     backwardDeleteCharSearchStringEditor(e);
3692     if ( notNil(e->search_string) )
3693     { executeSearchEditor(e, DEFAULT, e->search_base);
3694     } else
3695     { e->caret = e->search_origin;		/* re-start */
3696       beginIsearchEditor(e, e->search_direction);
3697     }
3698 
3699     succeed;
3700   }
3701 
3702   if ( !isInteger(id) )
3703   { endIsearchEditor(e, ON);
3704     fail;
3705   }
3706 
3707   switch( valInt(chr) )
3708   { case ESC:
3709       endIsearchEditor(e, ON);
3710       succeed;
3711     case Control('W'):
3712       extendSearchStringToWordEditor(e);
3713       succeed;
3714     case Control('M'):
3715       chr = toInt(Control('J'));
3716     case Control('J'):
3717     case Control('I'):
3718       return executeSearchEditor(e, chr, DEFAULT);
3719     case Control('L'):
3720     case Control('@'):
3721       endIsearchEditor(e, ON);
3722       fail;
3723   }
3724 
3725   if ( valInt(chr) < Meta(0) &&
3726        tisprint(e->text_buffer->syntax, valInt(chr)) )
3727     return executeSearchEditor(e, chr, DEFAULT);
3728 
3729   endIsearchEditor(e, ON);
3730   fail;
3731 }
3732 
3733 		/********************************
3734 		*            DABBREV		*
3735 		********************************/
3736 
3737 static Name
get_dabbrev_target(Editor e)3738 get_dabbrev_target(Editor e)
3739 { Int caret = e->caret;
3740   TextBuffer tb = e->text_buffer;
3741   Int sow = getScanTextBuffer(tb, caret, NAME_word, 0, NAME_start);
3742   int n;
3743   string s;
3744 
3745   for(n=valInt(sow); n < valInt(caret); n++)
3746   { if ( !tisalnum(tb->syntax, fetch_textbuffer(tb, n)) )
3747     { send(e, NAME_report, NAME_warning, CtoName("Not at end of word"), EAV);
3748       fail;
3749     }
3750   }
3751 
3752   assign(e, dabbrev_origin, sow);
3753   str_sub_text_buffer(tb, &s, valInt(sow), valInt(caret) - valInt(sow));
3754   answer(StringToName(&s));
3755 }
3756 
3757 
3758 static status
dabbrevExpandEditor(Editor e)3759 dabbrevExpandEditor(Editor e)
3760 { Name target;
3761 
3762   MustBeEditable(e);
3763 
3764   TRY( target = get_dabbrev_target(e) );
3765   assign(e, dabbrev_target, target);
3766   assign(e, dabbrev_mode, NAME_backwards);
3767   assign(e, dabbrev_candidates, NIL);
3768   DEBUG(NAME_editor, Cprintf("dabbrev target = %s\n", pp(target)));
3769 
3770   if ( notNil(e->dabbrev_reject) )
3771     clearChain(e->dabbrev_reject);
3772   else
3773     assign(e, dabbrev_reject, newObject(ClassChain, EAV));
3774   appendChain(e->dabbrev_reject, target);
3775 
3776   assign(e, dabbrev_pos, sub(e->caret, toInt(target->data.s_size+1)));
3777   assign(e, focus_function, NAME_DabbrevExpand);
3778 
3779   DEBUG(NAME_editor, Cprintf("starting DabbrevExpand\n"));
3780 
3781   return DabbrevExpandEditor(e, DEFAULT);
3782 }
3783 
3784 
3785 static Name
get_dabbrev_hit_editor(Editor e,int start)3786 get_dabbrev_hit_editor(Editor e, int start)
3787 { TextBuffer tb = e->text_buffer;
3788   int size = tb->size;
3789   int end;
3790   string s;
3791 
3792   for(end = start; end < size; end++)
3793   { wint_t c = fetch_textbuffer(tb, end);
3794     if ( !tisalnum(tb->syntax, c) )
3795       break;
3796   }
3797   str_sub_text_buffer(tb, &s, start, end-start);
3798   answer(StringToName(&s));
3799 }
3800 
3801 
3802 static Name
get_case_pattern(SyntaxTable syntax,PceString s)3803 get_case_pattern(SyntaxTable syntax, PceString s)
3804 { int i, size = s->s_size;
3805 
3806   if ( tisupper(syntax, str_fetch(s, 0)) )
3807   { for( i=1; i < size; i++)
3808     { if ( tislower(syntax, str_fetch(s, i)) )
3809 	return NAME_capitalised;
3810     }
3811     return NAME_upper;
3812   }
3813 
3814   return NAME_lower;
3815 }
3816 
3817 
3818 static void
fix_case_and_insert(TextBuffer tb,int where,PceString insert,Name pattern,int ec)3819 fix_case_and_insert(TextBuffer tb, int where, PceString insert,
3820 		    Name pattern, int ec)
3821 { if ( insert->s_size == 0 )
3822     return;
3823 
3824   if ( ec )
3825   { insert_textbuffer(tb, where, 1, insert);
3826   } else
3827   { int size = insert->s_size;
3828     LocalString(copy, insert->s_iswide, insert->s_size);
3829 
3830     str_cpy(copy, insert);
3831     if ( equalName(pattern, NAME_upper) )
3832       str_upcase(copy, 0, size);
3833     else if ( equalName(pattern, NAME_capitalised) )
3834     { str_upcase(copy, 0, 1);
3835       str_downcase(copy, 1, size);
3836     } else
3837       str_downcase(copy, 0, size);
3838 
3839     insert_textbuffer(tb, where, 1, copy);
3840   }
3841 }
3842 
3843 
3844 static Name
nextDabbrevMode(Editor e)3845 nextDabbrevMode(Editor e)
3846 { if ( e->dabbrev_mode == NAME_forwards )
3847     assign(e, dabbrev_mode, NAME_user1);
3848   else if ( e->dabbrev_mode == NAME_user1 )
3849     assign(e, dabbrev_mode, NAME_user2);
3850   else if ( e->dabbrev_mode == NAME_user2 )
3851     assign(e, dabbrev_mode, NAME_user3);
3852   else
3853     fail;
3854 
3855   return e->dabbrev_mode;
3856 }
3857 
3858 
3859 static status
DabbrevExpandEditor(Editor e,EventId id)3860 DabbrevExpandEditor(Editor e, EventId id)
3861 { int pos = valInt(e->dabbrev_pos);
3862   int caret = valInt(e->caret);
3863   PceString target = &e->dabbrev_target->data;
3864   int ec = (e->exact_case == ON);
3865   TextBuffer tb = e->text_buffer;
3866   int dir = (pos < caret ? -1 : 1);
3867   int hit_pos;
3868   Name hit;
3869 
3870   if ( notDefault(id) )
3871   { Name cmd = getKeyBindingEditor(e, characterName(id));
3872 
3873     if ( equalName(cmd, NAME_keyboardQuit) )
3874     { Int start = add(e->dabbrev_origin, toInt(target->s_size));
3875 
3876       deleteTextBuffer(tb, start, sub(e->caret, start));
3877       keyboardQuitEditor(e, DEFAULT);
3878       assign(e, focus_function, NIL);
3879 
3880       succeed;
3881     }
3882 
3883     if ( !equalName(cmd, NAME_dabbrevExpand) )
3884       fail;
3885   }
3886 
3887   for(;;)
3888   { Cell cell;
3889 
3890     DEBUG(NAME_editor, Cprintf("Starting search\n"));
3891     if ( equalName(e->dabbrev_mode, NAME_backwards) ||
3892 	 equalName(e->dabbrev_mode, NAME_forwards) )
3893     { hit_pos = find_textbuffer(tb, pos, target, dir, 'a', ec, FALSE);
3894 
3895       if ( hit_pos < 0 )
3896       { if ( dir < 0 )			/* no more backwards; revert */
3897 	{ dir = -dir;
3898 	  pos = caret;
3899 	  assign(e, dabbrev_mode, NAME_forwards);
3900 	  continue;
3901 	}
3902 
3903 	goto user;
3904       }
3905 
3906       if ( hit_pos != 0 &&
3907 	   tisalnum(tb->syntax, fetch_textbuffer(tb, hit_pos-1)) )
3908       { pos = hit_pos + dir;		/* hit is no start of word */
3909 	continue;
3910       }
3911 
3912       DEBUG(NAME_editor, Cprintf("hit at %d\n", hit_pos));
3913 
3914       hit = get_dabbrev_hit_editor(e, hit_pos);
3915       DEBUG(NAME_editor, Cprintf("hit = %s\n", pp(hit)));
3916       pos = (dir < 0 ? hit_pos - 1 : hit_pos + target->s_size);
3917     } else
3918     { user:
3919       while ( !(notNil(e->dabbrev_candidates) &&
3920 		(hit = getDeleteHeadChain(e->dabbrev_candidates))) )
3921       { Name mode = nextDabbrevMode(e);
3922 
3923 	if ( mode )
3924 	{ Chain ch;
3925 
3926 	  ch = get(e, NAME_dabbrevCandidates, mode, e->dabbrev_target, EAV);
3927 
3928 	  if ( !instanceOfObject(ch, ClassChain) )
3929 	    ch = NIL;
3930 	  assign(e, dabbrev_candidates, ch);
3931 	} else
3932 	{ send(e, NAME_report, NAME_warning, CtoName("No more hits"), EAV);
3933 	  assign(e, focus_function, NIL);
3934 	  succeed;
3935 	}
3936       }
3937     }
3938 
3939     for_cell(cell, e->dabbrev_reject)
3940     { Name reject = cell->value;
3941 
3942       if ( ec && reject == hit )
3943 	goto next;
3944       if ( !ec && str_icase_eq(&hit->data, &reject->data) )
3945 	goto next;
3946     }
3947 
3948     if ( memberChain(e->dabbrev_reject, hit) == SUCCEED )
3949       continue;
3950     appendChain(e->dabbrev_reject, hit);
3951     assign(e, dabbrev_pos, toInt(pos));
3952 
3953     DEBUG(NAME_editor, Cprintf("deleting\n"));
3954     deleteTextBuffer(tb, e->dabbrev_origin, sub(e->caret, e->dabbrev_origin));
3955     DEBUG(NAME_editor, Cprintf("inserting\n"));
3956     fix_case_and_insert(tb,
3957 			valInt(e->dabbrev_origin),
3958 			&hit->data,
3959 			get_case_pattern(tb->syntax, target),
3960 			str_prefix(&hit->data, target) ? TRUE : ec);
3961     DEBUG(NAME_editor, Cprintf("ok\n"));
3962     succeed;
3963 
3964     next:;
3965   }
3966 }
3967 
3968 
3969 static Chain
getDabbrevCandidatesEditor(Editor e,Name mode,CharArray target)3970 getDabbrevCandidatesEditor(Editor e, Name mode, CharArray target)
3971 { return NIL;
3972 }
3973 
3974 
3975 		/********************************
3976 		*           SCROLLING		*
3977 		********************************/
3978 
3979 status
scrollToEditor(Editor e,Int pos,Int screenline)3980 scrollToEditor(Editor e, Int pos, Int screenline)
3981 { if ( isDefault(pos) )
3982     pos = toInt(e->text_buffer->size);
3983 
3984   centerTextImage(e->image, pos, screenline);
3985   return ensureCaretInWindowEditor(e);
3986 }
3987 
3988 
3989 static status
centerWindowEditor(Editor e,Int pos)3990 centerWindowEditor(Editor e, Int pos)
3991 { centerTextImage(e->image, normalise_index(e, pos), DEFAULT);
3992   ComputeGraphical(e->image);
3993   updateCursorEditor(e);
3994 
3995   succeed;
3996 }
3997 
3998 
3999 static status
scrollDownEditor(Editor e,Int arg)4000 scrollDownEditor(Editor e, Int arg)
4001 { Name unit = NAME_line;
4002 
4003   if ( isDefault(arg) )
4004   { arg = toInt(SCROLL_PAGE_PROM);
4005     unit = NAME_page;
4006   }
4007 
4008   return send(e, NAME_scrollVertical, NAME_backwards, unit, arg, EAV);
4009 }
4010 
4011 
4012 static status
scrollUpEditor(Editor e,Int arg)4013 scrollUpEditor(Editor e, Int arg)
4014 { Name unit = NAME_line;
4015 
4016   if ( isDefault(arg) )
4017   { arg = toInt(SCROLL_PAGE_PROM);
4018     unit = NAME_page;
4019   }
4020 
4021   return send(e, NAME_scrollVertical, NAME_forwards, unit, arg, EAV);
4022 }
4023 
4024 
4025 static status
scrollOneLineUpEditor(Editor e,Int arg)4026 scrollOneLineUpEditor(Editor e, Int arg)
4027 { return scrollUpEditor(e, toInt(UArg(arg)));
4028 }
4029 
4030 
4031 static status
scrollOneLineDownEditor(Editor e,Int arg)4032 scrollOneLineDownEditor(Editor e, Int arg)
4033 { return scrollDownEditor(e, toInt(UArg(arg)));
4034 }
4035 
4036 
4037 static status
lineToTopOfWindowEditor(Editor e,Int arg)4038 lineToTopOfWindowEditor(Editor e, Int arg)
4039 { centerTextImage(e->image, normalise_index(e, e->caret),
4040 		  toInt(UArg(arg) - 1));
4041 
4042   return ensureCaretInWindowEditor(e);
4043 }
4044 
4045 
4046 static status
recenterEditor(Editor e,Int arg)4047 recenterEditor(Editor e, Int arg)
4048 { centerTextImage(e->image, normalise_index(e, e->caret), arg);
4049   updateCursorEditor(e);
4050 
4051   succeed;
4052 }
4053 
4054 
4055 status
scrollVerticalEditor(Editor e,Name dir,Name unit,Int amount)4056 scrollVerticalEditor(Editor e, Name dir, Name unit, Int amount)
4057 { TextBuffer tb = e->text_buffer;
4058   Int start;
4059 
4060   endIsearchEditor(e, OFF);
4061   markStatusEditor(e, NAME_inactive);
4062 
4063   if ( unit == NAME_file )
4064   { if ( dir == NAME_goto )
4065     { if ( tb->size < MAXPRECISESCROLLING &&
4066 	   (start = getScrollStartTextImage(e->image, dir, unit, amount)) )
4067       { startTextImage(e->image, start, ZERO);
4068 
4069 	return ensureCaretInWindowEditor(e);
4070       } else if ( tb->size < MAXLINEBASEDSCROLLING )
4071       { int size = valInt(countLinesEditor(e, ZERO, toInt(tb->size)));
4072 	int view = valInt(getLinesTextImage(e->image));
4073 	int target = ((size-view)*valInt(amount))/1000;
4074 	int cp;				/* character-position */
4075 
4076 	if ( target < 0 )
4077 	  target = 0;
4078 
4079 	cp = start_of_line_n_textbuffer(tb, target+1);
4080 	centerTextImage(e->image, toInt(cp), ONE);
4081 	ensureCaretInWindowEditor(e);
4082       } else
4083       { long h = (long)(((double)tb->size * (double)valInt(amount)) / 1000.0);
4084 					/* avoid integer arithmetic overflow */
4085 
4086 	scrollToEditor(e, toInt(h), DEFAULT);
4087       }
4088     }
4089   } else
4090   { if ( (start = getScrollStartTextImage(e->image, dir, unit, amount)) )
4091     { startTextImage(e->image, start, ZERO);
4092 
4093       return ensureCaretInWindowEditor(e);
4094     }
4095   }
4096 
4097   succeed;
4098 }
4099 
4100 
4101 static status
showScrollBarEditor(Editor e,BoolObj show,ScrollBar sb)4102 showScrollBarEditor(Editor e, BoolObj show, ScrollBar sb)
4103 { if ( isDefault(sb) || sb == e->scroll_bar )
4104   { computeBoundingBoxDevice((Device)e);
4105     DisplayedGraphical(e->scroll_bar, show);
4106     geometryEditor(e, DEFAULT, DEFAULT, e->area->w, e->area->h);
4107   }
4108 
4109   succeed;
4110 }
4111 
4112 		/********************************
4113 		*     SELECTION/REGION/MARK	*
4114 		********************************/
4115 
4116 static status
internalMarkEditor(Editor e,Int mark)4117 internalMarkEditor(Editor e, Int mark)
4118 { if ( isDefault(mark) )
4119     mark = e->caret;
4120 
4121   e->internal_mark = valInt(normalise_index(e, mark));
4122 
4123   succeed;
4124 }
4125 
4126 
4127 static Int
getInternalMarkEditor(Editor e)4128 getInternalMarkEditor(Editor e)
4129 { return toInt(e->internal_mark);
4130 }
4131 
4132 
4133 
4134 static status
selectionOriginEditor(Editor e,Int where)4135 selectionOriginEditor(Editor e, Int where)
4136 { endIsearchEditor(e, OFF);
4137   assign(e, selection_origin, where);
4138 
4139   return selectionExtendEditor(e, where);
4140 }
4141 
4142 
4143 static status
selectionExtendEditor(Editor e,Int where)4144 selectionExtendEditor(Editor e, Int where)
4145 { int from = valInt(e->selection_origin);
4146   int to   = valInt(where);
4147   SyntaxTable syntax = e->text_buffer->syntax;
4148 
4149 #define WordKind(c) (tisalnum(syntax, c) ? 1 : 0)
4150 #define LineKind(c) (tisendsline(syntax, c) ? 1 : 0)
4151 
4152   if ( to < from )
4153   { int tmp = to;
4154     to = from + 1;
4155     from = tmp;
4156   }
4157 
4158   if ( equalName(e->selection_unit, NAME_word) )
4159   { for( ; from > 0 && WordKind(Fetch(e, from-1)) ; from-- )
4160       ;
4161 
4162     for( ; to < e->text_buffer->size && WordKind(Fetch(e, to)); to++)
4163       ;
4164   } else if ( equalName(e->selection_unit, NAME_line) )
4165   { for( ; from > 0 && !LineKind(Fetch(e, from-1)); from-- )
4166       ;
4167     if ( !LineKind(Fetch(e, to)) )
4168       for( ; to < e->text_buffer->size && !LineKind(Fetch(e, to)); to++ )
4169 	;
4170     to++;
4171   }
4172 
4173 #undef WordKind
4174 #undef LineKind
4175 
4176   if ( valInt(where) < valInt(e->selection_origin) ) /* swap */
4177   { int tmp = from;
4178     from = to;
4179     to = tmp;
4180   }
4181   return selection_editor(e, toInt(from), toInt(to), NAME_active);
4182 }
4183 
4184 
4185 static status
selection_editor(Editor e,Int from,Int to,Name status)4186 selection_editor(Editor e, Int from, Int to, Name status)
4187 { if ( isDefault(from) )   from   = e->mark;
4188   if ( isDefault(to) )     to     = e->caret;
4189   if ( isDefault(status) )
4190   { if ( e->mark_status == NAME_highlight )
4191       status = NAME_inactive;
4192     else
4193       status = e->mark_status;
4194   }
4195 
4196   from = normalise_index(e, from);
4197   to   = normalise_index(e, to);
4198 
4199   if ( from != e->mark || to != e->caret || status != e->mark_status )
4200   { if ( e->caret != e->mark )
4201       ChangedRegionEditor(e, e->mark, e->caret);
4202 
4203     assign(e, mark, from);
4204     assign(e, caret, to);	/* TBD: allow redefinition of ->caret */
4205     assign(e, mark_status, status);
4206 
4207     if ( from != to )
4208       ChangedRegionEditor(e, from, to);
4209   }
4210 
4211   succeed;
4212 }
4213 
4214 
4215 static status
selectLineEditor(Editor e,Int line,BoolObj newline)4216 selectLineEditor(Editor e, Int line, BoolObj newline)
4217 { Int from, to;
4218   TextBuffer tb = e->text_buffer;
4219 
4220   if ( notDefault(line) )
4221     from = toInt(start_of_line_n_textbuffer(tb, valInt(line)));
4222   else
4223     from = getScanTextBuffer(tb, e->caret, NAME_line, ZERO, NAME_start);
4224 
4225   to = getScanTextBuffer(tb, from, NAME_line, ZERO, NAME_end);
4226   if ( newline == ON )
4227     to = add(to, ONE);
4228 
4229   selection_editor(e, to, from, NAME_highlight); /* put caret at start */
4230   return ensureVisibleEditor(e, from, to);
4231 }
4232 
4233 
4234 status
selectionEditor(Editor e,Int from,Int to,Name status)4235 selectionEditor(Editor e, Int from, Int to, Name status)
4236 { selection_editor(e, from, to, status);
4237   if ( e->mark != e->caret )
4238     normaliseEditor(e, e->mark, e->caret);
4239 
4240   succeed;
4241 }
4242 
4243 
4244 Point
getSelectionEditor(Editor e)4245 getSelectionEditor(Editor e)
4246 { Int f = e->mark;
4247   Int t = e->caret;
4248 
4249   if ( f != t )
4250   { Before(f, t);
4251     answer(answerObject(ClassPoint, f, t, EAV));
4252   }
4253 
4254   fail;
4255 }
4256 
4257 
4258 static Int
getSelectionStartEditor(Editor e)4259 getSelectionStartEditor(Editor e)
4260 { if ( e->mark != e->caret )
4261     answer(e->mark);
4262 
4263   fail;
4264 }
4265 
4266 
4267 static Int
getSelectionEndEditor(Editor e)4268 getSelectionEndEditor(Editor e)
4269 { if ( e->mark != e->caret )
4270     answer(e->caret);
4271 
4272   fail;
4273 }
4274 
4275 
4276 StringObj
getSelectedEditor(Editor e)4277 getSelectedEditor(Editor e)
4278 { Int f = e->mark;
4279   Int t = e->caret;
4280 
4281   if ( f != t )
4282   { Before(f, t);
4283     answer(getContentsTextBuffer(e->text_buffer, f, sub(t, f)));
4284   }
4285 
4286   fail;
4287 }
4288 
4289 		/********************************
4290 		*        SELECTION EDITS	*
4291 		********************************/
4292 
4293 static status
deleteSelectionEditor(Editor e)4294 deleteSelectionEditor(Editor e)
4295 { Int from, to;
4296   status rval;
4297 
4298   MustBeEditable(e);
4299   SelectionRegion(e, from, to);
4300   if ( (rval = deleteTextBuffer(e->text_buffer, from, sub(to, from))) )
4301     selection_editor(e, from, from, NAME_inactive);
4302 
4303   return rval;
4304 }
4305 
4306 
4307 		/********************************
4308 		*         X CUT BUFFERS		*
4309 		********************************/
4310 
4311 static status
selectionToCutBufferEditor(Editor e,Int arg)4312 selectionToCutBufferEditor(Editor e, Int arg)
4313 { int buffer = UArg(arg) - 1;
4314 
4315   if ( buffer < 0 || buffer > 7 )
4316   { send(e, NAME_report, NAME_error,
4317 	 CtoName("Illegal cut buffer: %d"), toInt(buffer+1), EAV);
4318     fail;
4319   }
4320 
4321   if ( !HasSelection(e) )
4322     fail;				/* no selection */
4323 
4324   return send(getDisplayGraphical((Graphical) e), NAME_cutBuffer,
4325 	      toInt(buffer), getSelectedEditor(e), EAV);
4326 }
4327 
4328 
4329 static status
insertCutBufferEditor(Editor e,Int arg)4330 insertCutBufferEditor(Editor e, Int arg)
4331 { StringObj str;
4332   int buffer = UArg(arg) - 1;
4333 
4334   MustBeEditable(e);
4335 
4336   if ( buffer < 0 || buffer > 7 )
4337   { send(e, NAME_report, NAME_error,
4338 	 CtoName("Illegal cut buffer: %d"), toInt(buffer+1), EAV);
4339     fail;
4340   }
4341 
4342   if ( (str = get(getDisplayGraphical((Graphical) e),
4343 		  NAME_cutBuffer, toInt(buffer), EAV)) == FAIL )
4344   { send(e, NAME_report, NAME_warning,
4345 	 CtoName("Failed to get cut buffer %d"), toInt(buffer+1), EAV);
4346     fail;
4347   }
4348 
4349   return insertEditor(e, (CharArray) str);
4350 }
4351 
4352 
4353 		/********************************
4354 		*         PROGRAM EDITS		*
4355 		********************************/
4356 
4357 static status
appendEditor(Editor e,CharArray str)4358 appendEditor(Editor e, CharArray str)
4359 { if ( e->left_margin != ZERO )
4360     alignOneLineEditor(e, getLengthEditor(e), e->left_margin);
4361   appendTextBuffer(e->text_buffer, str, ONE);
4362   if ( e->auto_newline == ON )
4363     newlineEditor(e, ONE);
4364   return CaretEditor(e, DEFAULT);
4365 
4366   succeed;
4367 }
4368 
4369 
4370 static status
insertEditor(Editor e,CharArray str)4371 insertEditor(Editor e, CharArray str)
4372 { return insertTextBuffer(e->text_buffer, e->caret, str, ONE);
4373 }
4374 
4375 
4376 status
formatEditor(Editor e,CharArray fmt,int argc,Any * argv)4377 formatEditor(Editor e, CharArray fmt, int argc, Any *argv)
4378 { string s;
4379 
4380   TRY(str_writefv(&s, fmt, argc, argv));
4381   insert_textbuffer(e->text_buffer, Caret(e), 1, &s);
4382   str_unalloc(&s);
4383 
4384   succeed;
4385 }
4386 
4387 
4388 static status
appendfEditor(Editor e,CharArray fmt,int argc,Any * argv)4389 appendfEditor(Editor e, CharArray fmt, int argc, Any *argv)
4390 { string s;
4391 
4392   TRY(str_writefv(&s, fmt, argc, argv));
4393   insert_textbuffer(e->text_buffer, e->text_buffer->size, 1, &s);
4394   str_unalloc(&s);
4395 
4396   succeed;
4397 }
4398 
4399 
4400 
4401 static status
printEditor(Editor e,CharArray str)4402 printEditor(Editor e, CharArray str)
4403 { insertEditor(e, str);
4404   if ( e->auto_newline == ON )
4405     newlineEditor(e, ONE);
4406 
4407   succeed;
4408 }
4409 
4410 
4411 status
clearEditor(Editor e)4412 clearEditor(Editor e)
4413 { clearTextBuffer(e->text_buffer);
4414   selection_editor(e, ZERO, ZERO, NAME_inactive);
4415   assign(e, file, NIL);
4416 
4417   succeed;
4418 }
4419 
4420 
4421 static status
deleteEditor(Editor e,Int from,Int to)4422 deleteEditor(Editor e, Int from, Int to)
4423 { Before(from, to);
4424   return deleteTextBuffer(e->text_buffer, from, sub(to, from));
4425 }
4426 
4427 
4428 static status
deleteLineEditor(Editor e,Int line)4429 deleteLineEditor(Editor e, Int line)
4430 { Int from = getScanTextBuffer(e->text_buffer,
4431 			       ZERO, NAME_line, sub(line, ONE),
4432 			       NAME_start);
4433   Int to =   getScanTextBuffer(e->text_buffer,
4434 			       from, NAME_line, ZERO, NAME_end);
4435 
4436   return deleteTextBuffer(e->text_buffer, from, sub(add(to, ONE), from));
4437 }
4438 
4439 
4440 static status
replaceLineEditor(Editor e,CharArray str)4441 replaceLineEditor(Editor e, CharArray str)
4442 { Int from = getScanTextBuffer(e->text_buffer,
4443 			       e->caret, NAME_line, ZERO,
4444 			       NAME_start);
4445   Int to =   getScanTextBuffer(e->text_buffer,
4446 			       from, NAME_line, ZERO, NAME_end);
4447 
4448   deleteTextBuffer(e->text_buffer, from, sub(to, from));
4449   insertTextBuffer(e->text_buffer, from, str, ONE);
4450   return CaretEditor(e, from);
4451 }
4452 
4453 
4454 static status
sortEditor(Editor e,Int from,Int to)4455 sortEditor(Editor e, Int from, Int to)
4456 { return sortTextBuffer(e->text_buffer, from, to);
4457 }
4458 
4459 
4460 static StringObj
getWordEditor(Editor e,Int where)4461 getWordEditor(Editor e, Int where)
4462 { Int to;
4463   TextBuffer tb = e->text_buffer;
4464 
4465   if ( isDefault(where) )
4466     where = e->caret;
4467   where = normalise_index(e, where);
4468 
4469   where = getScanTextBuffer(tb, where, NAME_word, ZERO, NAME_start);
4470   to    = getScanTextBuffer(tb, where, NAME_word, ZERO, NAME_end);
4471 
4472   answer(getContentsTextBuffer(e->text_buffer, where, sub(to, where)));
4473 }
4474 
4475 
4476 static StringObj
getLineEditor(Editor e,Int where)4477 getLineEditor(Editor e, Int where)
4478 { Int to;
4479   TextBuffer tb = e->text_buffer;
4480 
4481   if ( isDefault(where) )
4482     where = e->caret;
4483   where = normalise_index(e, where);
4484 
4485   where = getScanTextBuffer(tb, where, NAME_line, ZERO, NAME_start);
4486   to    = getScanTextBuffer(tb, where, NAME_line, ZERO, NAME_end);
4487 
4488   answer(getContentsTextBuffer(e->text_buffer, where, sub(to, where)));
4489 }
4490 
4491 
4492 static StringObj
getReadLineEditor(Editor e)4493 getReadLineEditor(Editor e)
4494 { Int to;
4495   StringObj rval;
4496 
4497   if ( e->caret == getLengthEditor(e) )
4498     fail;
4499   to = getScanTextBuffer(e->text_buffer, e->caret, NAME_line, 0, NAME_end);
4500   rval = getContentsTextBuffer(e->text_buffer, e->caret, sub(to, e->caret));
4501   CaretEditor(e, add(to, ONE));
4502 
4503   answer(rval);
4504 }
4505 
4506 
4507 static StringObj
getFirstLineEditor(Editor e)4508 getFirstLineEditor(Editor e)
4509 { ComputeGraphical(e->image);
4510 
4511   answer(getLineEditor(e, getStartTextImage(e->image, ONE)));
4512 }
4513 
4514 
4515 static Int
getColumnEditor(Editor e,Int where)4516 getColumnEditor(Editor e, Int where)
4517 { TextBuffer tb = e->text_buffer;
4518   long sol;
4519   int col;
4520 
4521   if ( isDefault(where) )
4522     where = e->caret;
4523   where = normalise_index(e, where);
4524 
4525   sol = valInt(getScanTextBuffer(tb, where, NAME_line, 0, NAME_start));
4526   for(col = 0; sol < valInt(where); sol++ )
4527   { if ( fetch_textbuffer(tb, sol) == '\t' )
4528     { col++;
4529       col = Round(col, valInt(e->tab_distance));
4530     } else
4531       col++;
4532   }
4533 
4534   answer(toInt(col));
4535 }
4536 
4537 
4538 static Int
getColumnLocationEditor(Editor e,Int c,Int from)4539 getColumnLocationEditor(Editor e, Int c, Int from)
4540 { TextBuffer tb = e->text_buffer;
4541   int size = tb->size;
4542   long pos;
4543   int dcol = valInt(c);
4544   int col;
4545 
4546   if ( isDefault(from) )
4547     from = e->caret;
4548   pos = valInt(getScanTextBuffer(tb, from, NAME_line, 0, NAME_start));
4549 
4550   for(col = 0; col < dcol && pos < size; pos++)
4551   { switch( fetch_textbuffer(tb, pos) )
4552     { case '\n':
4553 	return toInt(pos);
4554       case '\t':
4555 	col++;
4556 	col = Round(col, valInt(e->tab_distance));
4557 	break;
4558       default:
4559 	col++;
4560     }
4561   }
4562 
4563   answer(toInt(pos));
4564 }
4565 
4566 
4567 static status
columnEditor(Editor e,Int c)4568 columnEditor(Editor e, Int c)
4569 { return CaretEditor(e, getColumnLocationEditor(e, c, e->caret));
4570 }
4571 
4572 
4573 static status
lineNumberEditor(Editor e,Int line)4574 lineNumberEditor(Editor e, Int line)
4575 { return CaretEditor(e, getScanTextBuffer(e->text_buffer,
4576 					  ZERO, NAME_line, sub(line, ONE),
4577 					  NAME_start));
4578 }
4579 
4580 
4581 static Int
getLineNumberEditor(Editor e,Int where)4582 getLineNumberEditor(Editor e, Int where)
4583 { if ( isDefault(where) )
4584     where = e->caret;
4585   where = normalise_index(e, where);
4586 
4587   answer(getLineNumberTextBuffer(e->text_buffer, where));
4588 }
4589 
4590 
4591 		/********************************
4592 		*             FILES		*
4593 		********************************/
4594 
4595 static status
loadEditor(Editor e,SourceSink file)4596 loadEditor(Editor e, SourceSink file)
4597 { TextBuffer tb = e->text_buffer;
4598   status rval;
4599 
4600   clearTextBuffer(tb);
4601   if ( (rval = insertFileTextBuffer(tb, ZERO, file, ONE)) )
4602   { BoolObj editable = (send(file, NAME_access, NAME_write, EAV) ? ON : OFF);
4603 
4604     assign(e, file, file);
4605     send(e, NAME_editable, editable, EAV);
4606     CaretEditor(e, ZERO);
4607     CmodifiedTextBuffer(tb, OFF);
4608     resetUndoTextBuffer(tb);
4609   }
4610 
4611   return rval;
4612 }
4613 
4614 
4615 static status
saveEditor(Editor e,SourceSink file)4616 saveEditor(Editor e, SourceSink file)
4617 { if ( isDefault(file) )
4618     file = e->file;
4619 
4620   if ( isNil(file) )
4621     fail;
4622 
4623   if ( instanceOfObject(file, ClassFile) &&
4624        existsFile((FileObj)file, DEFAULT) )
4625     TRY(send(file, NAME_backup, EAV));
4626 
4627   TRY(saveTextBuffer(e->text_buffer, file, DEFAULT, DEFAULT));
4628   assign(e, file, file);
4629 
4630   succeed;
4631 }
4632 
4633 
4634 		/********************************
4635 		*          ATTRIBUTES		*
4636 		********************************/
4637 
4638 static status
fontEditor(Editor e,FontObj font)4639 fontEditor(Editor e, FontObj font)
4640 { if ( e->font != font )
4641   { assign(e, font, font);
4642     tabDistanceTextImage(e->image, mul(e->tab_distance, getExFont(e->font)));
4643     setGraphical(e, DEFAULT, DEFAULT, e->size->w, e->size->h);
4644     updateStyleCursorEditor(e);
4645     ChangedEditor(e);
4646   }
4647 
4648   succeed;
4649 }
4650 
4651 
4652 static status
tabDistanceEditor(Editor e,Int tab)4653 tabDistanceEditor(Editor e, Int tab)
4654 { if ( e->tab_distance != tab )
4655   { assign(e, tab_distance, tab);
4656     tabDistanceTextImage(e->image, mul(tab, getExFont(e->font)));
4657     ChangedEditor(e);
4658   }
4659 
4660   succeed;
4661 }
4662 
4663 
4664 static status
tabStopsEditor(Editor e,Vector v)4665 tabStopsEditor(Editor e, Vector v)
4666 { return tabStopsTextImage(e->image, v);	/* character -> pixels? */
4667 }
4668 
4669 
4670 static Vector
getTabStopsEditor(Editor e)4671 getTabStopsEditor(Editor e)
4672 { answer(e->image->tab_stops);
4673 }
4674 
4675 
4676 static status
wrapEditor(Editor e,Name wrap)4677 wrapEditor(Editor e, Name wrap)
4678 { return send(e->image, NAME_wrap, wrap, EAV);
4679 }
4680 
4681 
4682 static Name
getWrapEditor(Editor e)4683 getWrapEditor(Editor e)
4684 { answer(e->image->wrap);
4685 }
4686 
4687 
4688 status
backgroundEditor(Editor e,Any bg)4689 backgroundEditor(Editor e, Any bg)
4690 { return backgroundTextImage(e->image, bg);
4691 }
4692 
4693 
4694 status
colourEditor(Editor e,Any c)4695 colourEditor(Editor e, Any c)
4696 { return colourGraphical((Graphical)e->image, c);
4697 }
4698 
4699 
4700 		/********************************
4701 		*      CHANGE NOTIFICATIONS	*
4702 		********************************/
4703 
4704 static inline long
update_index_on_insert(long i,long w,long a)4705 update_index_on_insert(long i, long w, long a)
4706 { if ( a > 0 )				/* insert */
4707     return i > w ? i+a : i;
4708 
4709   if ( i > w )				/* delete before i */
4710     return i > w-a ? i+a : w;
4711 
4712   return i;
4713 }
4714 
4715 
4716 static inline long
update_caret_on_insert(long i,long w,long a)4717 update_caret_on_insert(long i, long w, long a)
4718 { if ( a > 0 )				/* insert */
4719     return i >= w ? i+a : i;
4720 
4721   if ( i > w )				/* delete before i */
4722     return i > w-a ? i+a : w;
4723 
4724   return i;
4725 }
4726 
4727 
4728 static status
InsertEditor(Editor e,Int where,Int amount)4729 InsertEditor(Editor e, Int where, Int amount)
4730 { long w = valInt(where);
4731   long a = valInt(amount);
4732   int s = valInt(e->mark_ring->size);
4733   int i; Any *p;
4734 
4735   assign(e, caret, toInt(update_caret_on_insert(valInt(e->caret), w, a)));
4736   assign(e, mark,  toInt(update_index_on_insert(valInt(e->mark),  w, a)));
4737 
4738   for(i=0, p=e->mark_ring->elements; i<s; i++, p++)
4739   { if ( notNil(*p) )
4740       *p = toInt(update_caret_on_insert(valInt(*p), w, a));
4741   }
4742 
4743 #define UPDATE_C_INDEX(e, idx) \
4744   e->idx = update_index_on_insert(e->idx, w, a);
4745 
4746   UPDATE_C_INDEX(e, internal_mark);
4747 
4748 #undef UPDATE_C_INDEX
4749 
4750   InsertTextImage(e->image, where, amount);
4751   if ( notNil(e->kill_location) )
4752     assign(e, kill_location, NIL);
4753 
4754   succeed;
4755 }
4756 
4757 
4758 static status
ChangedRegionEditor(Editor e,Int from,Int to)4759 ChangedRegionEditor(Editor e, Int from, Int to)
4760 { Before(from, to);
4761   ChangedRegionTextImage(e->image, from, to);
4762   if ( notNil(e->kill_location) )
4763     assign(e, kill_location, NIL);
4764 
4765   succeed;
4766 }
4767 
4768 
4769 static status
ChangedFragmentListEditor(Editor e)4770 ChangedFragmentListEditor(Editor e)
4771 { if ( notNil(e->selected_fragment) &&
4772        isFreeingObj(e->selected_fragment) ) /* HACK ... */
4773   { assign(e, selected_fragment, NIL);
4774     requestComputeGraphical(e->image, DEFAULT);
4775   }
4776 
4777   if ( notNil(e->margin) )
4778     requestComputeGraphical(e->margin, DEFAULT);
4779 
4780   resetFragmentCache(e->fragment_cache, e->text_buffer);
4781 
4782   succeed;
4783 }
4784 
4785 
4786 static status
ChangedEditor(Editor e)4787 ChangedEditor(Editor e)
4788 { ChangedRegionEditor(e, ZERO, getLengthEditor(e));
4789 
4790   succeed;
4791 }
4792 
4793 		 /*******************************
4794 		 *	     DELEGATION		*
4795 		 *******************************/
4796 
4797 static status
referenceEditor(Editor e,Point ref)4798 referenceEditor(Editor e, Point ref)
4799 { return referenceGraphical((Graphical) e, ref);
4800 }
4801 
4802 
4803 		/********************************
4804 		*            VISUAL		*
4805 		********************************/
4806 
4807 static Chain
getContainsEditor(Editor e)4808 getContainsEditor(Editor e)
4809 { fail;
4810 }
4811 
4812 
4813 static Any
getMasterEditor(Editor e)4814 getMasterEditor(Editor e)
4815 { if ( instanceOfObject(e->device, ClassView) )
4816     answer(e->device);
4817 
4818   answer(e);
4819 }
4820 
4821 
4822 		 /*******************************
4823 		 *	 CLASS DECLARATION	*
4824 		 *******************************/
4825 
4826 /* Type declarations */
4827 
4828 static char *T_align[] =
4829         { "column=int", "index=[int]" };
4830 static char *T_scrollVertical[] =
4831         { "direction={forwards,backwards,goto}",
4832 	  "unit={file,page,line}", "amount=int" };
4833 static char *T_showScrollBar[] =
4834         { "show=[bool]", "which=[scroll_bar]" };
4835 static char *T_formatAchar_array_argumentAany_XXX[] =
4836         { "format=char_array", "argument=any ..." };
4837 static char *T_style[] =
4838         { "fragment=name", "style=style*" };
4839 static char *T_fromADintD_toADintD[] =
4840         { "from=[int]", "to=[int]" };
4841 static char *T_fromAint_toAint[] =
4842         { "from=int", "to=int" };
4843 static char *T_fill[] =
4844         { "from=int", "to=int", "left_margin=[int]",
4845 	  "right_margin=[int]", "justify=[bool]" };
4846 static char *T_indentation[] =
4847         { "index=[int]", "skip=[regex]" };
4848 static char *T_electricCaret[] =
4849         { "index=int", "seconds=[real]" };
4850 static char *T_int_int[] =
4851         { "int", "int" };
4852 static char *T_keyBinding[] =
4853         { "key=name", "action=name|code" };
4854 static char *T_selectLine[] =
4855         { "line=[int]", "newline=[bool]" };
4856 static char *T_linesADintD_columnADintD[] =
4857         { "lines=[int]", "column=[int]" };
4858 static char *T_initialise[] =
4859         { "text=[text_buffer]", "width=[int]", "height=[int]",
4860 	  "margin=[int]" };
4861 static char *T_timesADintD_characterADcharD[] =
4862         { "times=[int]", "character=[char]" };
4863 static char *T_geometry[] =
4864         { "x=[int]", "y=[int]", "width=[int]", "height=[int]" };
4865 static char *T_selection[] =
4866         { "mark=[int]", "caret=[int]",
4867 	  "status=[{active,inactive,highlight}]"
4868 	};
4869 static char *T_mark[] =
4870         { "mark=[int]", "status=[{active,inactive,highlight}]"
4871 	};
4872 static char *T_scrollTo[] =
4873 	{ "index=[int]", "screenline=[int]" };
4874 static char *T_autoFill[] =
4875         { "from=[int]", "skip=[regex]" };
4876 static char *T_dabbrevCandidates[] =
4877         { "mode={user1,user2,user3}", "target=char_array" };
4878 
4879 
4880 /* Instance Variables */
4881 
4882 static vardecl var_editor[] =
4883 { SV(NAME_textBuffer, "text_buffer", IV_GET|IV_STORE, textBufferEditor,
4884      NAME_delegate, "Underlying text"),
4885   IV(NAME_image, "text_image", IV_GET,
4886      NAME_components, "Screen/redisplay management"),
4887   IV(NAME_scrollBar, "scroll_bar", IV_GET,
4888      NAME_components, "Scrollbar for the text"),
4889   IV(NAME_margin, "text_margin*", IV_GET,
4890      NAME_components, "Margin for annotations"),
4891   IV(NAME_textCursor, "text_cursor", IV_GET,
4892      NAME_components, "The caret"),
4893   IV(NAME_labelText, "text*", IV_GET,
4894      NAME_components, "Text object that displays the label"),
4895   SV(NAME_font, "font", IV_GET|IV_STORE, fontEditor,
4896      NAME_appearance, "Default font for the text"),
4897   IV(NAME_size, "size", IV_GET,
4898      NAME_area, "Size of editor in character units"),
4899   IV(NAME_caret, "int", IV_GET,
4900      NAME_caret, "0-based caret index"),
4901   IV(NAME_mark, "int", IV_GET,
4902      NAME_caret, "0-based mark index"),
4903   SV(NAME_markStatus, "{active,inactive,highlight}", IV_GET|IV_STORE,
4904      markStatusEditor,
4905      NAME_caret, "Status of the mark/region"),
4906   IV(NAME_markRing, "vector", IV_GET,
4907      NAME_caret, "Ring of old marks"),
4908   SV(NAME_tabDistance, "characters=int", IV_GET|IV_STORE, tabDistanceEditor,
4909      NAME_appearance, "Distance between tabs"),
4910   IV(NAME_selectionStyle, "[style]", IV_GET,
4911      NAME_appearance, "Feedback for the <-selection"),
4912   SV(NAME_selectedFragment, "fragment*", IV_GET|IV_STORE,
4913      selectedFragmentEditor,
4914      NAME_selection, "The current fragment"),
4915   SV(NAME_selectedFragmentStyle, "style", IV_GET|IV_STORE,
4916      selectedFragmentStyleEditor,
4917      NAME_appearance, "Style for the current fragment"),
4918   IV(NAME_styles, "sheet", IV_GET,
4919      NAME_appearance, "Style-name to style-object mapping"),
4920   IV(NAME_bindings, "key_binding", IV_BOTH,
4921      NAME_accelerator, "key_binding table"),
4922   IV(NAME_focusFunction, "name*", IV_BOTH,
4923      NAME_editContinue, "Method in focus of keystrokes"),
4924   IV(NAME_fillMode, "bool", IV_BOTH,
4925      NAME_mode, "If @on, automatically insert newlines"),
4926   IV(NAME_exactCase, "bool", IV_BOTH,
4927      NAME_case, "Search/replace uses exact case"),
4928   IV(NAME_killLocation, "int*", IV_NONE,
4929      NAME_internal, "Status for handling kill commands"),
4930   IV(NAME_searchDirection, "{forward,backward}", IV_NONE,
4931      NAME_internal, "Current direction of search"),
4932   IV(NAME_searchString, "string*", IV_BOTH,
4933      NAME_internal, "Current target of search"),
4934   IV(NAME_searchOrigin, "int", IV_NONE,
4935      NAME_internal, "Index where search started"),
4936   IV(NAME_searchBase, "int", IV_NONE,
4937      NAME_internal, "Index where last change was done"),
4938   IV(NAME_searchWrapped, "{wrapped,over_wrapped}*", IV_NONE,
4939      NAME_internal, "Wrapped search state"),
4940   IV(NAME_searchWrappedWarned, "bool", IV_NONE,
4941      NAME_internal, "Isearch hit end of buffer"),
4942   IV(NAME_selectionUnit, "{character,word,line}", IV_BOTH,
4943      NAME_selection, "Multiclick processing for the selection"),
4944   SV(NAME_selectionOrigin, "int", IV_GET|IV_STORE, selectionOriginEditor,
4945      NAME_selection, "Where the selection started"),
4946   IV(NAME_editable, "bool", IV_BOTH,
4947      NAME_mode, "If @on, text may be changed by user"),
4948   IV(NAME_errorMessage, "code*", IV_BOTH,
4949      NAME_report, "What to do with feedback/errors"),
4950   IV(NAME_modifiedMessage, "code*", IV_BOTH,
4951      NAME_report, "Forward changes to <->modified"),
4952   IV(NAME_leftMargin, "int", IV_BOTH,
4953      NAME_fill, "Auto-indent margin width"),
4954   IV(NAME_rightMargin, "int", IV_BOTH,
4955      NAME_fill, "Auto-fill margin"),
4956   IV(NAME_indentIncrement, "int", IV_BOTH,
4957      NAME_indentation, "Indent/undent amount"),
4958   IV(NAME_autoNewline, "bool", IV_BOTH,
4959      NAME_mode, "If @on, append newline after ->append"),
4960   IV(NAME_file, "source_sink*", IV_GET,
4961      NAME_file, "Associated file"),
4962   IV(NAME_dabbrevTarget, "name*", IV_NONE,
4963      NAME_internal, "Dynamic abbreviation target"),
4964   IV(NAME_dabbrevReject, "chain*", IV_NONE,
4965      NAME_internal, "Rejected alternatives"),
4966   IV(NAME_dabbrevPos, "int*", IV_NONE,
4967      NAME_internal, "Caret index at start of dabbrev"),
4968   IV(NAME_dabbrevOrigin, "int*", IV_NONE,
4969      NAME_internal, "Caret index of start of target"),
4970   IV(NAME_dabbrevMode, "{backwards,forwards,user1,user2,user3}", IV_NONE,
4971      NAME_internal, "Current dabbrev search mode"),
4972   IV(NAME_dabbrevCandidates, "chain*", IV_NONE,
4973      NAME_internal, "Current dabbrev candidates"),
4974   IV(NAME_internalMark, "alien:int", IV_NONE,
4975      NAME_internal, "Additional mark for internal use"),
4976   IV(NAME_fragmentCache, "alien:FragmentCache", IV_NONE,
4977      NAME_cache, "Cache to compute fragment attributes"),
4978   IV(NAME_isearchCache, "alien:ISearchCache", IV_NONE,
4979      NAME_cache, "Keep track of highlighting search hits")
4980 };
4981 
4982 static senddecl send_editor[] =
4983 { SM(NAME_geometry, 4, T_geometry, geometryEditor,
4984      DEFAULT, "Resize the image"),
4985   SM(NAME_initialise, 4, T_initialise, initialiseEditor,
4986      DEFAULT, "Create from text_buffer, W, H and margin"),
4987   SM(NAME_requestGeometry, 4, T_geometry, requestGeometryEditor,
4988      DEFAULT, "Map size to character units"),
4989   SM(NAME_unlink, 0, NULL, unlinkEditor,
4990      DEFAULT, "Unlink from buffer, margin, etc."),
4991   SM(NAME_lostTextBuffer, 0, NULL, lostTextBufferEditor,
4992      DEFAULT, "<-text_buffer is being freed"),
4993   SM(NAME_keyBinding, 2, T_keyBinding, keyBindingEditor,
4994      NAME_accelerator, "Set a local key binding"),
4995   SM(NAME_style, 2, T_style, styleEditor,
4996      NAME_appearance, "Set style associated with name"),
4997   SM(NAME_styles, 1, "sheet", stylesEditor,
4998      NAME_appearance, "Associate new name --> style object map"),
4999   SM(NAME_tabStops, 1, "vector*", tabStopsEditor,
5000      NAME_appearance, "Set tab-stops (vector of pixels)"),
5001   SM(NAME_background, 1, "colour|pixmap", backgroundEditor,
5002      NAME_appearance, "Background colour or image for the text"),
5003   SM(NAME_colour, 1, "colour|pixmap", colourEditor,
5004      NAME_appearance, "Foreground colour or image for the text"),
5005   SM(NAME_wrap, 1, "{none,character,word}", wrapEditor,
5006      NAME_appearance, "Wrap mode for long lines"),
5007   SM(NAME_Size, 1, "pixels=size", SizeEditor,
5008      NAME_area, "Set size in pixels (trap window resize)"),
5009   SM(NAME_backwardChar, 1, "[int]", backwardCharEditor,
5010      NAME_caret, "Move characters backward"),
5011   SM(NAME_backwardParagraph, 1, "[int]", backwardParagraphEditor,
5012      NAME_caret, "Move paragraphs backward"),
5013   SM(NAME_backwardSentence, 1, "[int]", backwardSentenceEditor,
5014      NAME_caret, "Move sentences backward"),
5015   SM(NAME_backwardTerm, 1, "[int]", backwardTermEditor,
5016      NAME_caret, "Move Prolog terms backward"),
5017   SM(NAME_backwardWord, 1, "[int]", backwardWordEditor,
5018      NAME_caret, "Move words backward"),
5019   SM(NAME_beginningOfLine, 1, "[int]", beginningOfLineEditor,
5020      NAME_caret, "Move lines backward"),
5021   SM(NAME_caret, 1, "index=[int]", caretEditor,
5022      NAME_caret, "Put the caret at 0-based index"),
5023   SM(NAME_column, 1, "column=int", columnEditor,
5024      NAME_caret, "Move caret to column at current line"),
5025   SM(NAME_endOfLine, 1, "[int]", endOfLineEditor,
5026      NAME_caret, "Move lines forward"),
5027   SM(NAME_exchangePointAndMark, 0, NULL, exchangePointAndMarkEditor,
5028      NAME_caret, "Exchange caret with mark"),
5029   SM(NAME_forwardChar, 1, "[int]", forwardCharEditor,
5030      NAME_caret, "Move characters forward"),
5031   SM(NAME_forwardParagraph, 1, "[int]", forwardParagraphEditor,
5032      NAME_caret, "Move paragraphs forward"),
5033   SM(NAME_forwardSentence, 1, "[int]", forwardSentenceEditor,
5034      NAME_caret, "Move sentences forward"),
5035   SM(NAME_forwardTerm, 1, "[int]", forwardTermEditor,
5036      NAME_caret, "Move Prolog terms forward"),
5037   SM(NAME_forwardWord, 1, "[int]", forwardWordEditor,
5038      NAME_caret, "Move words forward"),
5039   SM(NAME_nextLine, 2, T_linesADintD_columnADintD, nextLineEditor,
5040      NAME_caret, "Move lines downward; place caret at column"),
5041   SM(NAME_pointToBottomOfFile, 1, "[int]", pointToBottomOfFileEditor,
5042      NAME_caret, "Move to end of file"),
5043   SM(NAME_pointToBottomOfWindow, 1, "[int]", pointToBottomOfWindowEditor,
5044      NAME_caret, "Scroll caret to bottom of window"),
5045   SM(NAME_pointToMark, 0, NULL, pointToMarkEditor,
5046      NAME_caret, "Move to mark"),
5047   SM(NAME_pointToTopOfFile, 1, "[int]", pointToTopOfFileEditor,
5048      NAME_caret, "Move to start of file "),
5049   SM(NAME_pointToTopOfWindow, 1, "[int]", pointToTopOfWindowEditor,
5050      NAME_caret, "Move to 1st character of window"),
5051   SM(NAME_previousLine, 2, T_linesADintD_columnADintD, previousLineEditor,
5052      NAME_caret, "Move lines upward; place caret at column"),
5053   SM(NAME_setMark, 1, "[int]", setMarkEditor,
5054      NAME_caret, "Set mark at point"),
5055   SM(NAME_capitalisePreviousWord, 1, "[int]", capitalisePreviousWordEditor,
5056      NAME_case, "Capitalise n word before caret"),
5057   SM(NAME_capitaliseRegion, 0, NULL, capitaliseRegionEditor,
5058      NAME_case, "Capitalise words in region"),
5059   SM(NAME_capitaliseWord, 1, "[int]", capitaliseWordEditor,
5060      NAME_case, "Capitalise n words from caret"),
5061   SM(NAME_downcasePreviousWord, 1, "[int]", downcasePreviousWordEditor,
5062      NAME_case, "Lower-case n words before caret"),
5063   SM(NAME_downcaseRegion, 0, NULL, downcaseRegionEditor,
5064      NAME_case, "Put region in lower case"),
5065   SM(NAME_downcaseWord, 1, "[int]", downcaseWordEditor,
5066      NAME_case, "Loser-case n words after caret"),
5067   SM(NAME_toggleCharCase, 0, NULL, toggleCharCaseEditor,
5068      NAME_case, "Toggle case of character before caret"),
5069   SM(NAME_upcasePreviousWord, 1, "[int]", upcasePreviousWordEditor,
5070      NAME_case, "Uppercase n words before caret"),
5071   SM(NAME_upcaseRegion, 0, NULL, upcaseRegionEditor,
5072      NAME_case, "Put region in uppercase"),
5073   SM(NAME_upcaseWord, 1, "[int]", upcaseWordEditor,
5074      NAME_case, "Uppercase n words after caret"),
5075   SM(NAME_dabbrevExpand, 0, NULL, dabbrevExpandEditor,
5076      NAME_complete, "Dynamically expand word"),
5077   SM(NAME_backwardDeleteChar, 1, "[int]", backwardDeleteCharEditor,
5078      NAME_delete, "Delete characters backward"),
5079   SM(NAME_backwardKillWord, 1, "[int]", backwardKillWordEditor,
5080      NAME_delete, "Kill words backward"),
5081   SM(NAME_clear, 0, NULL, clearEditor,
5082      NAME_delete, "Clear the contents"),
5083   SM(NAME_delete, 2, T_fromAint_toAint, deleteEditor,
5084      NAME_delete, "Delete range [from, to)"),
5085   SM(NAME_deleteBlankLines, 0, NULL, deleteBlankLinesEditor,
5086      NAME_delete, "Delete blank lines around point"),
5087   SM(NAME_deleteChar, 1, "[int]", deleteCharEditor,
5088      NAME_delete, "Delete characters forward"),
5089   SM(NAME_copy, 0, NULL, copyEditor,
5090      NAME_selection, "Copy selection"),
5091   SM(NAME_cut, 0, NULL, cutEditor,
5092      NAME_selection, "Copy and delete selection"),
5093   SM(NAME_paste, 1, "which=[{primary,clipboard}]", pasteEditor,
5094      NAME_selection, "Paste the selection or clipboard value"),
5095   SM(NAME_cutOrDeleteChar, 1, "[int]", cutOrDeleteCharEditor,
5096      NAME_delete, "Cut selection or delete characters forward"),
5097   SM(NAME_cutOrBackwardDeleteChar, 1, "[int]", cutOrBackwardDeleteCharEditor,
5098      NAME_delete, "Cut selection or delete characters backward"),
5099   SM(NAME_deleteHorizontalSpace, 1, "[int]", deleteHorizontalSpaceEditor,
5100      NAME_delete, "Delete blanks around caret"),
5101   SM(NAME_deleteSelection, 0, NULL, deleteSelectionEditor,
5102      NAME_delete, "Delete the selection"),
5103   SM(NAME_grab, 2, T_fromAint_toAint, grabEditor,
5104      NAME_delete, "Add text to the kill-buffer"),
5105   SM(NAME_kill, 2, T_fromAint_toAint, killEditor,
5106      NAME_delete, "Delete text and add it to the kill-buffer"),
5107   SM(NAME_killLine, 1, "[int]", killLineEditor,
5108      NAME_delete, "Kill lines forward"),
5109   SM(NAME_killOrGrabRegion, 1, "[int]", killOrGrabRegionEditor,
5110      NAME_delete, "Kill or grab (with arg) region"),
5111   SM(NAME_killParagraph, 1, "[int]", killParagraphEditor,
5112      NAME_delete, "Kill paragraphs"),
5113   SM(NAME_killSentence, 1, "[int]", killSentenceEditor,
5114      NAME_delete, "Kill sentences forward"),
5115   SM(NAME_killTerm, 1, "[int]", killTermEditor,
5116      NAME_delete, "Kill Prolog terms"),
5117   SM(NAME_killWord, 1, "[int]", killWordEditor,
5118      NAME_delete, "Kill words forward"),
5119   SM(NAME_reference, 1, "point", referenceEditor,
5120      NAME_dialogItem, "Set reference as dialog_item"),
5121   SM(NAME_DabbrevExpand, 1, "event_id", DabbrevExpandEditor,
5122      NAME_editContinue, "Focus function"),
5123   SM(NAME_Isearch, 1, "event_id", IsearchEditor,
5124      NAME_editContinue, "Focus function"),
5125   SM(NAME_StartIsearch, 1, "event_id", StartIsearchEditor,
5126      NAME_editContinue, "Focus function"),
5127   SM(NAME_WantsKeyboardFocus, 0, NULL, succeedObject,
5128      NAME_event, "Test if ready to accept input (true)"),
5129   SM(NAME_cuaKeyAsPrefix, 1, "event|event_id", cuaKeyAsPrefixEditor,
5130      NAME_event, "Test whether to use as prefix or cut/copy command"),
5131   SM(NAME_event, 1, "event", eventEditor,
5132      NAME_event, "Handle a general event"),
5133   SM(NAME_label, 1, "name", labelEditor,
5134      NAME_label, "Set the name of the label"),
5135   SM(NAME_load, 1, "file=source_sink", loadEditor,
5136      NAME_file, "Clear editor and load a file"),
5137   SM(NAME_save, 1, "file=[file]", saveEditor,
5138      NAME_file, "Save to current or given file"),
5139   SM(NAME_saveBuffer, 1, "always=[int]", saveBufferEditor,
5140      NAME_file, "Save to current <-file"),
5141   SM(NAME_fill, 5, T_fill, fillEditor,
5142      NAME_fill, "Fill (from, to) using left- and rightmargin [justify]"),
5143   SM(NAME_fillParagraph, 1, "justify=[int]", fillParagraphEditor,
5144      NAME_fill, "Fill paragraph around point"),
5145   SM(NAME_fillRegion, 0, NULL, fillRegionEditor,
5146      NAME_fill, "Fill paragraphs in region"),
5147   SM(NAME_fillSelection, 0, NULL, fillRegionEditor,
5148      NAME_fill, "Compat: ->fill_region"),
5149   SM(NAME_justifyParagraph, 0, NULL, justifyParagraphEditor,
5150      NAME_fill, "Justify paragraph around point"),
5151   SM(NAME_justifyRegion, 0, NULL, justifyRegionEditor,
5152      NAME_fill, "Justify region"),
5153   SM(NAME_setFillColumn, 1, "[int]", setFillColumnEditor,
5154      NAME_fill, "Set fill column to argument"),
5155   SM(NAME_appendf, 2, T_formatAchar_array_argumentAany_XXX, appendfEditor,
5156      NAME_format, "Formatted append (see `string ->format')"),
5157   SM(NAME_format, 2, T_formatAchar_array_argumentAany_XXX, formatEditor,
5158      NAME_format, "Formatted insert (see `string ->format')"),
5159   SM(NAME_align, 2, T_align, alignEditor,
5160      NAME_indentation, "Align here [caret] to indicated column"),
5161   SM(NAME_alignLine, 1, "column=[int]", alignLineEditor,
5162      NAME_indentation, "Align line to argument"),
5163   SM(NAME_alignRegion, 1, "column=[int]", alignRegionEditor,
5164      NAME_indentation, "Align region to argument"),
5165   SM(NAME_indentLine, 1, "[int]", indentLineEditor,
5166      NAME_indentation, "Indent line by <-indent_increment"),
5167   SM(NAME_indentRegion, 1, "[int]", indentRegionEditor,
5168      NAME_indentation, "Indent lines in region by <-indent_increment"),
5169   SM(NAME_indentSelection, 1, "[int]", indentRegionEditor,
5170      NAME_indentation, "Compat: ->indent_region"),
5171   SM(NAME_newlineAndIndent, 1, "[int]", newlineAndIndentEditor,
5172      NAME_indentation, "Start a newline and indent"),
5173   SM(NAME_undentLine, 1, "[int]", undentLineEditor,
5174      NAME_indentation, "Unindent line by <-indent_increment"),
5175   SM(NAME_undentRegion, 1, "[int]", undentRegionEditor,
5176      NAME_indentation, "Unindent lines in region by <-indent_increment"),
5177   SM(NAME_undentSelection, 1, "[int]", undentRegionEditor,
5178      NAME_indentation, "Compat: ->undent_region"),
5179   SM(NAME_append, 1, "text=char_array", appendEditor,
5180      NAME_insert, "Append text (left_margin, auto_newline)"),
5181   SM(NAME_insert, 1, "text=char_array", insertEditor,
5182      NAME_insert, "Insert text at caret (moves caret)"),
5183   SM(NAME_insertCutBuffer, 1, "[int]", insertCutBufferEditor,
5184      NAME_insert, "Insert value of X cut-buffer"),
5185   SM(NAME_insertQuoted, 2, T_timesADintD_characterADcharD, insertQuotedEditor,
5186      NAME_insert, "Insert typed character n times (no fill)"),
5187   SM(NAME_insertSelf, 2, T_timesADintD_characterADcharD, insertSelfEditor,
5188      NAME_insert, "Insert typed character n times"),
5189   SM(NAME_insertSelfFill, 2, T_timesADintD_characterADcharD, insertSelfEditor,
5190      NAME_insert, "Insert char n times; adjust margins"),
5191   SM(NAME_autoFill, 2, T_autoFill, autoFillEditor,
5192      NAME_insert, "Fill after ->insert_self_fill detected a long line"),
5193   SM(NAME_newline, 1, "[int]", newlineEditor,
5194      NAME_insert, "Insert newlines"),
5195   SM(NAME_openLine, 1, "[int]", openLineEditor,
5196      NAME_insert, "Insert newlines after caret"),
5197   SM(NAME_print, 1, "text=string", printEditor,
5198      NAME_insert, "Insert text at caret (auto_newline)"),
5199   SM(NAME_typed, 1, "event|event_id", typedEditor,
5200      NAME_insert, "Process a keystroke"),
5201   SM(NAME_showLabel, 1, "show=bool", showLabelEditor,
5202      NAME_appearance, "Show/unshow the label"),
5203   SM(NAME_yank, 1, "[int]", yankEditor,
5204      NAME_insert, "Yank current kill-buffer"),
5205   SM(NAME_justOneSpace, 0, NULL, justOneSpaceEditor,
5206      NAME_layout, "Replace blanks with a single space"),
5207   SM(NAME_deleteLine, 1, "line=int", deleteLineEditor,
5208      NAME_line, "Delete given line number"),
5209   SM(NAME_lineNumber, 1, "line=int", lineNumberEditor,
5210      NAME_line, "Move caret to start of line"),
5211   SM(NAME_replaceLine, 1, "text=char_array", replaceLineEditor,
5212      NAME_line, "Replace given line number by string"),
5213   SM(NAME_autoFillMode, 1, "[int]", autoFillModeEditor,
5214      NAME_mode, "Toggle auto_fill mode"),
5215   SM(NAME_switchCaseMode, 1, "[int]", switchCaseModeEditor,
5216      NAME_mode, "Toggle exact/either case search"),
5217   SM(NAME_ChangedFragmentList, 0, NULL, ChangedFragmentListEditor,
5218      NAME_repaint, "Notify change in text_buffers fragment list"),
5219   SM(NAME_ChangedRegion, 2, T_int_int, ChangedRegionEditor,
5220      NAME_repaint, "Notify change (start, length)"),
5221   SM(NAME_InsertEditor, 2, T_int_int, InsertEditor,
5222      NAME_repaint, "Notify insert (start, length)"),
5223   SM(NAME_compute, 0, NULL, computeEditor,
5224      NAME_repaint, "Recompute the editor"),
5225   SM(NAME_electricCaret, 2, T_electricCaret, electricCaretEditor,
5226      NAME_report, "Temporary display caret at location"),
5227   SM(NAME_report, 3, T_report, reportEditor,
5228      NAME_report, "Report message (using <-error_message)"),
5229   SM(NAME_showCaretAt, 1, "index=[int]", showCaretAtEditor,
5230      NAME_report, "Display caret at indicated position"),
5231   SM(NAME_showCaret, 1, "show=bool", showCaretEditor,
5232      NAME_caret, "Show/hide the caret"),
5233   SM(NAME_showMatchingBracket, 1, "index=[int]", showMatchingBracketEditor,
5234      NAME_report, "->electric_caret on matching bracket"),
5235   SM(NAME_undefined, 0, NULL, undefinedEditor,
5236      NAME_report, "Warn binding is not defined"),
5237   SM(NAME_keyboardQuit, 0, NULL, keyboardQuitEditor,
5238      NAME_reset, "Cancel current operation"),
5239   SM(NAME_lineToTopOfWindow, 1, "[int]", lineToTopOfWindowEditor,
5240      NAME_scroll, "Scroll caret to top of window"),
5241   SM(NAME_normalise, 2, T_fromADintD_toADintD, normaliseEditor,
5242      NAME_scroll, "Try to make range visible"),
5243   SM(NAME_recenter, 1, "[int]", recenterEditor,
5244      NAME_scroll, "Scroll caret to center of window"),
5245   SM(NAME_scrollDown, 1, "[int]", scrollDownEditor,
5246      NAME_scroll, "Scroll lines (1 screen) downward"),
5247   SM(NAME_scrollOneLineDown, 1, "[int]", scrollOneLineDownEditor,
5248      NAME_scroll, "Scroll lines (1 line) downward"),
5249   SM(NAME_scrollOneLineUp, 1, "[int]", scrollOneLineUpEditor,
5250      NAME_scroll, "Scroll lines (1 line) upward"),
5251   SM(NAME_scrollTo, 2, T_scrollTo, scrollToEditor,
5252      NAME_scroll, "Set start of window to index"),
5253   SM(NAME_scrollUp, 1, "[int]", scrollUpEditor,
5254      NAME_scroll, "Scroll lines (1 screen) upward"),
5255   SM(NAME_scrollVertical, 3, T_scrollVertical, scrollVerticalEditor,
5256      NAME_scroll, "Trap scroll_bar request"),
5257   SM(NAME_showScrollBar, 2, T_showScrollBar, showScrollBarEditor,
5258      NAME_scroll, "Control visibility of the <-scroll_bar"),
5259   SM(NAME_bubbleScrollBar, 1, "scroll_bar", bubbleScrollBarEditor,
5260      NAME_scroll, "Update bubble of given scroll_bar object"),
5261   SM(NAME_findCutBuffer, 1, "[int]", findCutBufferEditor,
5262      NAME_search, "Find string in X-cut buffer"),
5263   SM(NAME_isearchBackward, 0, NULL, isearchBackwardEditor,
5264      NAME_search, "Start incremental search backward"),
5265   SM(NAME_isearchForward, 0, NULL, isearchForwardEditor,
5266      NAME_search, "Start incremental search forward"),
5267   SM(NAME_internalMark, 1, "[int]", internalMarkEditor,
5268      NAME_caret, "Mark for program-use"),
5269   SM(NAME_selectLine, 2, T_selectLine, selectLineEditor,
5270      NAME_selection, "Select given line number"),
5271   SM(NAME_selection, 3, T_selection, selectionEditor,
5272      NAME_selection, "Make [from, to) the selection"),
5273   SM(NAME_mark, 2, T_mark, markEditor,
5274      NAME_selection, "Set mark and region-status"),
5275   SM(NAME_markWholeBuffer, 0, NULL, markWholeBufferEditor,
5276      NAME_selection, "Set point at start and mark at end of buffer"),
5277   SM(NAME_selectionExtend, 1, "to=int", selectionExtendEditor,
5278      NAME_selection, "Extend the selection"),
5279   SM(NAME_selectionToCutBuffer, 1, "buffer=[0..9]", selectionToCutBufferEditor,
5280      NAME_selection, "Copy the selection to an X-cut buffer"),
5281   SM(NAME_sort, 2, T_fromADintD_toADintD, sortEditor,
5282      NAME_sort, "Sort range [from, to) by line"),
5283   SM(NAME_gosmacsTranspose, 0, NULL, gosmacsTransposeEditor,
5284      NAME_transpose, "Transpose characters before caret"),
5285   SM(NAME_transposeChars, 0, NULL, transposeCharsEditor,
5286      NAME_transpose, "Transpose characters around caret"),
5287   SM(NAME_transposeLines, 0, NULL, transposeLinesEditor,
5288      NAME_transpose, "Transpose line with line above"),
5289   SM(NAME_transposeTerms, 0, NULL, transposeTermsEditor,
5290      NAME_transpose, "Transpose Prolog terms around point"),
5291   SM(NAME_transposeWord, 0, NULL, transposeWordEditor,
5292      NAME_transpose, "Transpose words around caret"),
5293   SM(NAME_undo, 0, NULL, undoEditor,
5294      NAME_undo, "Undo last interactive command"),
5295   SM(NAME_marginWidth, 1, "pixels=int", marginWidthEditor,
5296      NAME_visualisation, "Set width of annotation margin"),
5297 
5298   SM(NAME_cursorUp, 2, T_linesADintD_columnADintD, cursorUpEditor,
5299      NAME_event, "Handle cursor up-arrow"),
5300   SM(NAME_cursorDown, 2, T_linesADintD_columnADintD, cursorDownEditor,
5301      NAME_event, "Handle cursor down-arrow"),
5302   SM(NAME_cursorLeft, 1, "[int]", cursorLeftEditor,
5303      NAME_event, "Handle cursor left-arrow"),
5304   SM(NAME_cursorRight, 1, "[int]", cursorRightEditor,
5305      NAME_event, "Handle cursor right-arrow"),
5306   SM(NAME_cursorEnd, 1, "[int]", cursorEndEditor,
5307      NAME_event, "Handle 'end'-key"),
5308   SM(NAME_cursorHome, 1, "[int]", cursorHomeEditor,
5309      NAME_event, "Handle 'home'-key"),
5310   SM(NAME_cursorPageUp, 1, "[int]", cursorPageUpEditor,
5311      NAME_event, "Handle 'page-up'-key"),
5312   SM(NAME_cursorPageDown, 1, "[int]", cursorPageDownEditor,
5313      NAME_event, "Handle 'page-down'-key")
5314 };
5315 
5316 /* Get Methods */
5317 
5318 static getdecl get_editor[] =
5319 { GM(NAME_contains, 0, "visual", NULL, getContainsEditor,
5320      DEFAULT, "Visuals contained (fails)"),
5321   GM(NAME_convert, 1, "editor", "view", getConvertEditor,
5322      DEFAULT, "The `view <-editor'"),
5323   GM(NAME_master, 0, "editor|view", NULL, getMasterEditor,
5324      DEFAULT, "Principal visual I'm part of (self or view)"),
5325   GM(NAME_keyBinding, 1, "action=name|code", "key=name|event_id",
5326      getKeyBindingEditor,
5327      NAME_accelerator, "Function for specified key"),
5328   GM(NAME_tabStops, 0, "vector*", NULL, getTabStopsEditor,
5329      NAME_appearance, "Vector with tab-stop positions in pixels (or @nil)"),
5330   GM(NAME_wrap, 0, "{none,character,word}", NULL, getWrapEditor,
5331      NAME_appearance, "Wrap mode for long lines"),
5332   GM(NAME_height, 0, "character=int", NULL, getHeightEditor,
5333      NAME_area, "Height in character units"),
5334   GM(NAME_size, 0, "characters=size", NULL, getSizeEditor,
5335      NAME_area, "Size in character units"),
5336   GM(NAME_width, 0, "characters=int", NULL, getWidthEditor,
5337      NAME_area, "Width in character units"),
5338   GM(NAME_column, 1, "column=0..", "index=[int]", getColumnEditor,
5339      NAME_caret, "Column point is at"),
5340   GM(NAME_upDownColumn, 0, "column=int", NULL, getUpDownColumnEditor,
5341      NAME_caret, "Saved X-infor for ->cursor_up/->cursor_down"),
5342   GM(NAME_indentation, 2, "column=int", T_indentation, getIndentationEditor,
5343      NAME_indentation, "Column of first non-blank character"),
5344   GM(NAME_FetchFunction, 0, "alien:FetchFunction", NULL,
5345      getFetchFunctionEditor,
5346      NAME_internal, "Pointer to C-function to fetch char"),
5347   GM(NAME_MarginFunction, 0, "alien:MarginFunction", NULL,
5348      getMarginFunctionEditor,
5349      NAME_internal, "Pointer to C-function to fetch margins"),
5350   GM(NAME_RewindFunction, 0, "alien:RewindFunction", NULL,
5351      getRewindFunctionEditor,
5352      NAME_internal, "Pointer to C-function to rewind object"),
5353   GM(NAME_ScanFunction, 0, "alien:ScanFunction", NULL, getScanFunctionEditor,
5354      NAME_internal, "Pointer to C-function to scan for char-type"),
5355   GM(NAME_SeekFunction, 0, "alien:SeekFunction", NULL, getSeekFunctionEditor,
5356      NAME_internal, "Pointer to C-function to seek to position"),
5357   GM(NAME_lineNumber, 1, "line=int", "index=[int]", getLineNumberEditor,
5358      NAME_line, "Line number point is at"),
5359   GM(NAME_firstLine, 0, "line=string", NULL, getFirstLineEditor,
5360      NAME_read, "New string with text of first window line"),
5361   GM(NAME_line, 1, "line=string", "index=[int]", getLineEditor,
5362      NAME_read, "New string with text of current line"),
5363   GM(NAME_readLine, 0, "line=string", NULL, getReadLineEditor,
5364      NAME_read, "As <-line, moves caret to next"),
5365   GM(NAME_word, 1, "word=string", "index=[int]", getWordEditor,
5366      NAME_read, "New string with text of current word"),
5367   GM(NAME_first, 0, "line=int", NULL, getFirstEditor,
5368      NAME_scroll, "Line-number (1-based) of the first line on the window"),
5369   GM(NAME_length, 0, "int", NULL, getLengthEditor,
5370      NAME_scroll, "Length of contents (# characters)"),
5371   GM(NAME_linesVisible, 0, "point", NULL, getLinesVisibleEditor,
5372      NAME_scroll, "New point with first and last visible line"),
5373   GM(NAME_start, 1, "int", "[int]", getStartEditor,
5374      NAME_scroll, "Start of nth-1 visible line (for scroll_bar)"),
5375   GM(NAME_view, 0, "int", NULL, getViewEditor,
5376      NAME_scroll, "Length of view (for scroll_bar)"),
5377   GM(NAME_selected, 0, "string", NULL, getSelectedEditor,
5378      NAME_selection, "New string with contents of selection"),
5379   GM(NAME_selection, 0, "point", NULL, getSelectionEditor,
5380      NAME_selection, "New point with start and end of selection"),
5381   GM(NAME_selectionEnd, 0, "int", NULL, getSelectionEndEditor,
5382      NAME_selection, "Index for end of selection"),
5383   GM(NAME_selectionStart, 0, "int", NULL, getSelectionStartEditor,
5384      NAME_selection, "Index for start of selection"),
5385   GM(NAME_internalMark, 0, "int", NULL, getInternalMarkEditor,
5386      NAME_caret, "Mark for program use"),
5387   GM(NAME_showLabel, 0, "bool", NULL, getShowLabelEditor,
5388      NAME_appearance, "Bool indicating if label is visible"),
5389   GM(NAME_marginWidth, 0, "pixels=int", NULL, getMarginWidthEditor,
5390      NAME_visualisation, "Width of annotation margin"),
5391   GM(NAME_dabbrevCandidates, 2, "chain*", T_dabbrevCandidates,
5392      getDabbrevCandidatesEditor, NAME_complete,
5393      "Get alternative dabbrev candidates")
5394 };
5395 
5396 /* Resources */
5397 
5398 static classvardecl rc_editor[] =
5399 { RC(NAME_background, "colour|pixmap", "white",
5400      "Colour/fill pattern of the background"),
5401   RC(NAME_caretModifier, "modifier", "",
5402      "Modify caret using this modifier"),
5403   RC(NAME_cursor, "cursor", UXWIN("xterm", "win_ibeam"),
5404      "Default cursor"),
5405   RC(NAME_exactCase, "bool", "@off",
5406      "Search/replace case"),
5407   RC(NAME_fillMode, "bool", "@off",
5408      "If @on, auto-fill"),
5409   RC(NAME_autoFillRegex, "regex*", "regex('[^\n]*\t *')",
5410      "If not @nil, skip this"),
5411   RC(NAME_font, "font", "fixed",
5412      "Default font"),
5413   RC(NAME_labelFont, "font", "bold",
5414      "Font used to display the label"),
5415   RC(NAME_indentIncrement, "int", "2",
5416      "Indent/undent amount"),
5417   RC(NAME_isearchStyle, "style",
5418      UXWIN("when(@colour_display,\n"
5419 	   "     style(background := green),\n"
5420 	   "     style(background:= @grey25_image))",
5421 	   "@_isearch_style"),
5422      "Style for incremental search"),
5423   RC(NAME_isearchOtherStyle, "style",
5424      "when(@colour_display,\n"
5425      "     style(background := pale_turquoise),\n"
5426      "     style(background:= @grey12_image))",
5427      "Style for `other matches' in incremental search"),
5428   RC(NAME_keyBinding, "string", "",
5429      "`Key = selector' binding list"),
5430   RC(NAME_pen, "0..", UXWIN("0", "1"),
5431      "Thickness of box around editor"),
5432   RC(NAME_rightMargin, "int", "72",
5433      "Auto-fill margin width"),
5434   RC(NAME_selectModifier, "modifier", "s",
5435      "Modify selection using this modifier"),
5436   RC(NAME_selectionStyle, "[style]",
5437      UXWIN("when(@colour_display,\n"
5438 	   "     style(background := yellow),\n"
5439 	   "     style(highlight := @on))",
5440 	   "@_select_style"),
5441      "Style for <-selection"),
5442   RC(NAME_insertDeletesSelection, "bool", "@on",
5443      "->insert_self and ->paste delete the selection"),
5444   RC(NAME_caretMovesOnSelect, "bool", "@on",
5445      "The caret is moved if a selection is made"),
5446   RC(NAME_autoCopy, "bool", "@on",
5447      "Automatically copy selected text to the clipboard"),
5448   RC(NAME_showOpenBracket, "bool", "@on",
5449      "Show open-bracket when inserting close-bracket"),
5450   RC(NAME_size, "size", "size(40,20)",
5451      "Default size in `characters x lines'"),
5452   RC(NAME_tabDistance, "int", "8",
5453      "Distance between tab stops (characters)")
5454 };
5455 
5456 /* Class Declaration */
5457 
5458 static Name editor_termnames[] =
5459 	{ NAME_textBuffer, NAME_width, NAME_height, NAME_marginWidth };
5460 
5461 ClassDecl(editor_decls,
5462           var_editor, send_editor, get_editor, rc_editor,
5463           4, editor_termnames,
5464           "$Rev$");
5465 
5466 status
makeClassEditor(Class class)5467 makeClassEditor(Class class)
5468 { declareClass(class, &editor_decls);
5469 
5470   setCloneFunctionClass(class, cloneEditor);
5471   setLoadStoreFunctionClass(class, loadFdEditor, storeEditor);
5472   setRedrawFunctionClass(class, RedrawAreaEditor);
5473   delegateClass(class, NAME_textBuffer);
5474   delegateClass(class, NAME_margin);
5475 
5476   succeed;
5477 }
5478 
5479 		/********************************
5480 		*            KILLING		*
5481 		********************************/
5482 
5483 static Vector
TextKillRing(void)5484 TextKillRing(void)
5485 { static Vector	ring;			/* @text_kill_ring */
5486 
5487   if ( !ring )
5488   { ring = globalObject(NAME_textKillRing, ClassVector, EAV);
5489     fillVector(ring, NIL, ZERO, toInt(9));
5490   }
5491 
5492   return ring;
5493 }
5494 
5495 
5496 static status
appendKill(CharArray ca)5497 appendKill(CharArray ca)
5498 { Vector ring = TextKillRing();
5499   CharArray old = getElementVector(ring, ZERO);
5500 
5501   if ( isNil(old) )
5502     elementVector(ring, ZERO, ca);
5503   else
5504     elementVector(ring, ZERO, getAppendCharArray(old, ca));
5505 
5506   succeed;
5507 }
5508 
5509 
5510 static status
prependKill(CharArray ca)5511 prependKill(CharArray ca)
5512 { Vector ring = TextKillRing();
5513   CharArray old = getElementVector(ring, ZERO);
5514 
5515   if ( isNil(old) )
5516     elementVector(ring, ZERO, ca);
5517   else
5518     elementVector(ring, ZERO, getAppendCharArray(ca, old));
5519 
5520   succeed;
5521 }
5522 
5523 
5524 static status
newKill(CharArray ca)5525 newKill(CharArray ca)
5526 { Vector ring = TextKillRing();
5527 
5528   shiftVector(ring, ONE);
5529   elementVector(ring, ZERO, ca);
5530 
5531   succeed;
5532 }
5533 
5534 
5535 static CharArray
killRegister(Int which)5536 killRegister(Int which)
5537 { CharArray ca;
5538  Vector ring;
5539 
5540   if ( isDefault(which) )
5541     which = ZERO;
5542 
5543   if ( (ring=TextKillRing()) &&
5544        (ca = getElementVector(ring, 0)) &&
5545        notNil(ca) )
5546     answer(ca);
5547 
5548   fail;
5549 }
5550