1: /* Copyright (c) Stichting Mathematisch Centrum, Amsterdam, 1984. */
2: static char rcsid[] = "$Header: move.c,v 2.4 85/08/22 16:05:16 timo Exp $";
3:
4: /*
5: * B editor -- Process arrow keys in four directions, plus TAB.
6: */
7:
8: #include "b.h"
9: #include "bobj.h"
10: #include "node.h"
11: #include "supr.h"
12: #include "gram.h"
13:
14: #define Left (-1)
15: #define Rite 1
16:
17:
18: /*
19: * Common code for PREVIOUS and NEXT commands.
20: */
21:
22: Hidden bool
23: prevnext(ep, direction)
24: environ *ep;
25: {
26: node n;
27: node n1;
28: int nch;
29: int i;
30: int len;
31: int sym;
32: string *rp;
33:
34: higher(ep);
35: switch (ep->mode) {
36: case VHOLE:
37: case FHOLE:
38: case ATBEGIN:
39: case ATEND:
40: if (direction == Left)
41: leftvhole(ep);
42: else
43: ritevhole(ep);
44: }
45:
46: for (;;) {
47: n = tree(ep->focus);
48: nch = nchildren(n);
49: rp = noderepr(n);
50:
51: switch (ep->mode) {
52:
53: case ATBEGIN:
54: case ATEND:
55: ep->mode = WHOLE;
56: continue;
57:
58: case VHOLE:
59: case FHOLE:
60: if (direction == Rite) {
61: if (ep->s1&1)
62: len = Fwidth(rp[ep->s1/2]);
63: else {
64: n1 = child(n, ep->s1/2);
65: len = width(n1);
66: }
67: }
68: if (direction == Rite ? ep->s2 >= len : ep->s2 <= 0) {
69: ep->mode = SUBSET;
70: ep->s2 = ep->s1;
71: return nextchar(ep, direction);
72: }
73: ep->s2 += direction;
74: return Yes;
75:
76: case SUBRANGE:
77: if (direction == Rite) {
78: if (ep->s1&1)
79: len = Fwidth(rp[ep->s1/2]);
80: else {
81: n1 = child(n, ep->s1/2);
82: len = width(n1);
83: }
84: }
85: if (direction == Left ? ep->s2 <= 0 : ep->s3 >= len-1) {
86: ep->mode = SUBSET;
87: ep->s2 = ep->s1;
88: return nextchar(ep, direction);
89: }
90: if (direction == Rite)
91: ep->s2 = ++ep->s3;
92: else
93: ep->s3 = --ep->s2;
94: return Yes;
95:
96: case SUBSET:
97: if (direction == Rite ? ep->s2 > 2*nch : ep->s1 <= 1) {
98: ep->mode = WHOLE;
99: continue;
100: }
101: if (direction == Rite)
102: ep->s1 = ++ep->s2;
103: else
104: ep->s2 = --ep->s1;
105: if (ep->s1&1) {
106: if (!Fw_positive(rp[ep->s1/2]) || allspaces(rp[ep->s1/2]))
107: continue;
108: }
109: else {
110: sym = symbol(n);
111: if (downi(&ep->focus, ep->s1/2)) {
112: n = tree(ep->focus);
113: if (((value)n)->type == Tex)
114: s_up(ep);
115: else {
116: if (ep->s1 == 2*nch && direction == Rite
117: && issublist(sym) && samelevel(sym, symbol(n))) {
118: ep->mode = SUBLIST;
119: ep->s3 = 1;
120: return Yes;
121: }
122: ep->mode = WHOLE;
123: if (width(n) == 0)
124: continue;
125: }
126: }
127: }
128: return Yes;
129:
130: case SUBLIST:
131: sym = symbol(n);
132: if (direction == Left) {
133: i = ichild(ep->focus);
134: if (!up(&ep->focus))
135: return No;
136: higher(ep);
137: n = tree(ep->focus);
138: if (i == nchildren(n) && samelevel(sym, symbol(n))) {
139: ep->s3 = 1;
140: return Yes;
141: }
142: ep->mode = SUBSET;
143: ep->s1 = ep->s2 = 2*i;
144: continue;
145: }
146: for (i = ep->s3; i > 0; --i)
147: if (!downrite(&ep->focus))
148: return No; /* Sorry... */
149: if (samelevel(sym, symbol(tree(ep->focus))))
150: ep->s3 = 1;
151: else
152: ep->mode = WHOLE;
153: return Yes;
154:
155: case WHOLE:
156: i = ichild(ep->focus);
157: if (!up(&ep->focus))
158: return No;
159: higher(ep);
160: ep->mode = SUBSET;
161: ep->s1 = ep->s2 = 2*i;
162: continue;
163:
164: default:
165: Abort();
166: }
167: }
168: /* Not reached */
169: }
170:
171: Visible bool leftarrow(ep)
172: environ *ep;
173: {
174: int w;
175: bool hole;
176:
177: if (narrow(ep)) {
178: while (narrow(ep))
179: ;
180: return Yes;
181: }
182: hole= ep->mode == WHOLE; /* Can't narrow and still WHOLE: */
183: /* a real hole which needs some hacking. */
184: if (!previous(ep))
185: return No;
186: if (hole) {
187: for (;;) {
188: w= focwidth(ep);
189: if (w >= 0 && w <= 1)
190: break;
191: if (!rnarrow(ep))
192: return No;
193: }
194: narrow(ep);
195: }
196: else {
197: while (rnarrow(ep))
198: ;
199: }
200: return Yes;
201: }
202:
203: Visible bool ritearrow(ep)
204: environ *ep;
205: {
206: while (narrow(ep))
207: ;
208: if (!next(ep))
209: return No;
210: while (narrow(ep))
211: ;
212: return Yes;
213: }
214:
215:
216: Visible bool
217: previous(ep)
218: environ *ep;
219: {
220: if (!prevnext(ep, Left))
221: return No;
222: return Yes;
223: }
224:
225:
226: Visible bool
227: next(ep)
228: environ *ep;
229: {
230: if (!prevnext(ep, Rite))
231: return No;
232: return Yes;
233: }
234:
235:
236: /*
237: * Position focus at next or previous char relative to current position.
238: * Assume current position given as SUBSET.
239: */
240:
241: Hidden bool
242: nextchar(ep, direction)
243: register environ *ep;
244: register int direction;
245: {
246: register int ich;
247: register int nch;
248: register node n;
249: node n1;
250: register int len;
251: string *rp;
252:
253: Assert(ep->mode == SUBSET);
254: for (;;) {
255: n = tree(ep->focus);
256: rp = noderepr(n);
257: nch = nchildren(n);
258: if (direction == Left)
259: ep->s2 = --ep->s1;
260: else
261: ep->s1 = ++ep->s2;
262: if (direction == Left ? ep->s1 < 1 : ep->s2 > 2*nch+1) {
263: ich = ichild(ep->focus);
264: if (!up(&ep->focus))
265: return No; /* *ep is garbage now! */
266: higher(ep);
267: ep->s1 = ep->s2 = 2*ich;
268: continue;
269: }
270: if (ep->s1&1) {
271: len = Fwidth(rp[ep->s1/2]);
272: if (len > 0) {
273: ep->mode = SUBRANGE;
274: ep->s2 = ep->s3 = direction == Left ? len-1 : 0;
275: return Yes;
276: }
277: continue;
278: }
279: n1 = child(n, ep->s1/2);
280: len = width(n1);
281: if (len == 0)
282: continue;
283: if (!downi(&ep->focus, ep->s1/2))
284: return No; /* Sorry... */
285: n = tree(ep->focus);
286: if (((value)n)->type == Tex) {
287: s_up(ep);
288: ep->mode = SUBRANGE;
289: ep->s2 = ep->s3 = direction == Left ? len-1 : 0;
290: return Yes;
291: }
292: if (direction == Left) {
293: nch = nchildren(n);
294: ep->s1 = ep->s2 = 2*(nch+1);
295: }
296: else
297: ep->s1 = ep->s2 = 0;
298: }
299: /* Not reached */
300: }
301:
302:
303: /*
304: * Up and down arrows.
305: */
306:
307: Hidden bool
308: updownarrow(ep, yincr)
309: environ *ep;
310: int yincr;
311: {
312: int y, x;
313:
314: while (narrow(ep))
315: ;
316: y= lineno(ep) + yincr;
317: x= colno(ep);
318: if (!gotoyx(ep, y, x))
319: return No;
320: gotofix(ep, y, x);
321: while (narrow(ep))
322: ;
323: return Yes;
324: }
325:
326: Visible bool
327: uparrow(ep)
328: environ *ep;
329: {
330: return updownarrow(ep, -1);
331: }
332:
333: Visible bool
334: downarrow(ep)
335: environ *ep;
336: {
337: return updownarrow(ep, 1);
338: }
339:
340: Visible bool
341: upline(ep)
342: register environ *ep;
343: {
344: register int y;
345:
346: y = lineno(ep);
347: if (y <= 0)
348: return No;
349: if (!gotoyx(ep, y-1, 0))
350: return No;
351: oneline(ep);
352: return Yes;
353: }
354:
355: Visible bool
356: downline(ep)
357: register environ *ep;
358: {
359: register int w;
360:
361: if (!parent(ep->focus) && ep->mode == ATEND)
362: return No; /* Superfluous? */
363: w = -focwidth(ep);
364: if (w <= 0)
365: w = 1;
366: if (!gotoyx(ep, lineno(ep) + w, 0))
367: return No;
368: oneline(ep);
369: return Yes;
370: }
371:
372:
373: /*
374: * ACCEPT command
375: * move to next Hole hole or to end of suggestion or to end of line.
376: */
377:
378:
379: Visible bool
380: accept(ep)
381: environ *ep;
382: {
383: int i;
384: string repr;
385:
386: shrink(ep);
387: switch (ep->mode) {
388: case ATBEGIN:
389: case ATEND:
390: case FHOLE:
391: case VHOLE:
392: ritevhole(ep);
393: }
394: if (symbol(tree(ep->focus)) == Hole)
395: ep->mode = ATEND;
396: switch (ep->mode) {
397: case ATBEGIN:
398: case SUBLIST:
399: case WHOLE:
400: i = 1;
401: break;
402: case ATEND:
403: i = 2*nchildren(tree(ep->focus)) + 2;
404: break;
405: case SUBRANGE:
406: case VHOLE:
407: case FHOLE:
408: i = ep->s1;
409: if (ep->s2 > 0 && i > 2*nchildren(tree(ep->focus)))
410: ++i; /* Kludge so after E?LSE: the focus moves to ELSE: ? */
411: break;
412: case SUBSET:
413: i = ep->s1 - 1;
414: break;
415: default:
416: Abort();
417: }
418: ep->mode = WHOLE;
419: for (;;) {
420: if (i/2 == nchildren(tree(ep->focus))) {
421: repr = noderepr(tree(ep->focus))[i/2];
422: if (Fw_positive(repr))
423: break;
424: }
425: if (tabstop(ep, i + 1))
426: return Yes;
427: i = 2*ichild(ep->focus) + 1;
428: if (!up(&ep->focus))
429: break;
430: higher(ep);
431: }
432: ep->mode = ATEND;
433: return Yes;
434: }
435:
436:
437: /*
438: * Find suitable tab stops for accept.
439: */
440:
441: Hidden bool
442: tabstop(ep, i)
443: environ *ep;
444: int i;
445: {
446: node n = tree(ep->focus);
447: int nch;
448: string repr;
449:
450: if (Type(n) == Tex)
451: return No;
452: nch = nchildren(n);
453: if (i/2 > nch)
454: return No;
455: if (symbol(n) == Hole) {
456: ep->mode = WHOLE;
457: return Yes;
458: }
459: if (i < 2) {
460: i = 2;
461: if (width(n) < 0) {
462: repr = noderepr(n)[0];
463: if (Fw_negative(repr)) {
464: ep->mode = ATBEGIN;
465: leftvhole(ep);
466: return Yes;
467: }
468: }
469: }
470: for (i /= 2; i <= nch; ++i) {
471: s_downi(ep, i);
472: if (tabstop(ep, 1))
473: return Yes;
474: s_up(ep);
475: }
476: return No;
477: }
Defined functions
next
defined in line
226; used 2 times
Defined variables
rcsid
defined in line
2;
never used
Defined macros
Left
defined in line
14; used 9 times
Rite
defined in line
15; used 8 times