1: /* Copyright (c) Stichting Mathematisch Centrum, Amsterdam, 1985. */
2:
3: /*
4: $Header: b2syn.c,v 1.4 85/08/22 16:56:25 timo Exp $
5: */
6:
7: #include "b.h"
8: #include "b0con.h"
9: #include "b1obj.h"
10: #include "b2key.h"
11: #include "b2syn.h"
12: #include "b3scr.h"
13: #include "b3env.h"
14: #include "b3err.h"
15:
16: #define TABSIZE 8 /* Number of spaces assumed for a tab on a file.
17: (Some editors insist on emitting tabs wherever
18: they can, and always assume 8 spaces for a tab.
19: Even when the editor can be instructed not to
20: do this, beginning users won't know about this,
21: so we'll always assume the default tab size.
22: Advanced users who used to instruct their editor
23: to set tab stops every 4 spaces will have to
24: unlearn this habit. But that's the price for
25: over-cleverness :-)
26: The indent increment is still 4 spaces!
27: When the B interpreter outputs text, it never uses
28: tabs but always emits 4 spaces for each indent level.
29: Note that the B editor also has a #defined constant
30: which sets the number of spaces for a tab on a file.
31: Finally the B editor *displays* indents as 3 spaces,
32: but *writes* them to the file as 4, so a neat
33: lay-out on the screen may look a bit garbled
34: when the file is printed. Sorry. */
35:
36: Visible txptr tx, ceol;
37:
38: Visible Procedure skipsp(tx) txptr *tx; {
39: while(Space(Char(*tx))) (*tx)++;
40: }
41:
42: Visible bool keymark(c) char c; {
43: return Cap(c) || Dig(c) || c=='\'' || c=='"';
44: }
45:
46: Hidden bool tagmark(c) char c; {
47: return Letter(c) || Dig(c) || c=='\'' || c=='"';
48: }
49:
50: Hidden bool keytagmark(c) char c; {
51: return keymark(c) || Letter(c);
52: }
53:
54: Visible bool is_expr(c) char c; {
55: return Letter(c) || c == '(' || Dig(c) || c == '.' ||
56: c == '\'' || c == '"' || c == '{' ||
57: c=='~' ||
58: c=='*' || c=='/' || c=='+' || c=='-' || c=='#';
59: }
60:
61: /* ******************************************************************** */
62: /* cr_text */
63: /* ******************************************************************** */
64:
65: Visible value cr_text(p, q) txptr p, q; {
66: /* Messes with the input line, which is a bit nasty,
67: but considered preferable to copying to a separate buffer */
68: value t;
69: char save= Char(q);
70: Char(q)= '\0';
71: t= mk_text(p);
72: Char(q)= save;
73: return t;
74: }
75:
76: /* ******************************************************************** */
77: /* find, findceol, req, findrel */
78: /* ******************************************************************** */
79:
80: #define Ptr (*ftx)
81: #define Nokeymark '+'
82:
83: Hidden bool E_number(tx) txptr tx; {
84: return Char(tx) == 'E' && Dig(Char(tx+1)) &&
85: (Dig(Char(tx-1)) || Char(tx-1) == '.');
86: }
87:
88: Hidden bool search(find_kw, s, q, ftx, ttx)
89: bool find_kw; string s; txptr q, *ftx, *ttx; {
90:
91: intlet parcnt= 0; bool outs= Yes, kw= No; char aq, lc= Nokeymark;
92: while (Ptr < q) {
93: if (outs) {
94: if (parcnt == 0) {
95: if (find_kw) {
96: if (Cap(Char(Ptr)) && !E_number(Ptr))
97: return Yes;
98: } else if (Char(Ptr) == *s) {
99: string t= s+1;
100: *ttx= Ptr+1;
101: while (*t && *ttx < q) {
102: if (*t != Char(*ttx)) break;
103: else { t++; (*ttx)++; }
104: }
105: if (*t);
106: else if (Cap(*s) &&
107: (kw || keymark(Char(*ttx))));
108: else return Yes;
109: }
110: }
111: switch (Char(Ptr)) {
112: case '(': case '{': case '[':
113: parcnt++; break;
114: case ')': case '}': case ']':
115: if (parcnt > 0) parcnt--; break;
116: case '\'': case '"':
117: if (!keytagmark(lc)) {
118: outs= No; aq= Char(Ptr);
119: }
120: break;
121: default:
122: break;
123: }
124: lc= Char(Ptr); kw= kw ? keymark(lc) : Cap(lc);
125: } else {
126: if (Char(Ptr) == aq)
127: { outs= Yes; kw= No; lc= Nokeymark; }
128: else if (Char(Ptr) == '`') {
129: Ptr++;
130: if (!search(No, "`", q, &Ptr, ttx)) return No;
131: }
132: }
133: Ptr++;
134: }
135: return No;
136: }
137:
138: /* ******************************************************************** */
139:
140: Visible bool find(s, q, ftx, ttx) string s; txptr q, *ftx, *ttx; {
141: return search(No, s, q, (*ftx= tx, ftx), ttx);
142: }
143:
144: Forward txptr lcol();
145:
146: Visible Procedure findceol() {
147: txptr q= lcol(), ttx;
148: if (!find("\\", q, &ceol, &ttx)) ceol= q;
149: }
150:
151: Visible Procedure req(s, q, ftx, ttx) string s; txptr q, *ftx, *ttx; {
152: if (!find(s, q, ftx, ttx)) {
153: parerr2(MESS(2400, "cannot find expected "), MESSMAKE(s));
154: *ftx= tx; *ttx= q;
155: }
156: }
157:
158: Hidden bool relsearch(s, q, ftx) string s; txptr q, *ftx; {
159: txptr ttx;
160: Ptr= tx;
161: while (search(No, s, q, &Ptr, &ttx))
162: switch (Char(Ptr)) {
163: case '<': if (Char(Ptr+1) == '<') Ptr= ++ttx;
164: else if (Char(Ptr-1) == '>') Ptr= ttx;
165: else return Yes;
166: break;
167: case '>': if (Char(Ptr+1) == '<') Ptr= ++ttx;
168: else if (Char(Ptr+1) == '>') Ptr= ++ttx;
169: else return Yes;
170: break;
171: case '=': return Yes;
172: default: return No;
173: }
174: return No;
175: }
176:
177: Visible bool findrel(q, ftx) txptr q, *ftx; {
178: txptr ttx;
179: Ptr= q;
180: if (relsearch("<", Ptr, &ttx)) Ptr= ttx;
181: if (relsearch(">", Ptr, &ttx)) Ptr= ttx;
182: if (relsearch("=", Ptr, &ttx)) Ptr= ttx;
183: return Ptr < q;
184: }
185:
186: /* ******************************************************************** */
187: /* tag, keyword, findkw */
188: /* ******************************************************************** */
189:
190: Visible bool is_tag(v) value *v; {
191: if (!Letter(Char(tx))) return No;
192: *v= tag();
193: return Yes;
194: }
195:
196: Visible value tag() {
197: txptr tx0= tx;
198: if (!Letter(Char(tx))) parerr(MESS(2401, "no tag where expected"));
199: while (tagmark(Char(tx))) tx++;
200: return cr_text(tx0, tx);
201: }
202:
203: Visible bool is_keyword(v) value *v; {
204: if (!Cap(Char(tx))) return No;
205: *v= keyword();
206: return Yes;
207: }
208:
209: Visible value keyword() {
210: txptr tx0= tx;
211: if (!Cap(Char(tx))) parerr(MESS(2402, "no keyword where expected"));
212: while (keymark(Char(tx))) tx++;
213: return cr_text(tx0, tx);
214: }
215:
216: Visible bool findkw(q, ftx) txptr q, *ftx; {
217: txptr ttx;
218: Ptr= tx;
219: return search(Yes, "", q, &Ptr, &ttx);
220: }
221:
222: /* ******************************************************************** */
223: /* upto, nothing, ateol, atkw, need */
224: /* ******************************************************************** */
225:
226: Visible Procedure upto(q, s) txptr q; string s; {
227: skipsp(&tx);
228: if (Text(q)) {
229: parerr2(MESS(2403, "something unexpected following "),
230: MESSMAKE(s));
231: tx= q;
232: }
233: }
234:
235: Visible bool nothing(q, s) txptr q; string s; {
236: if (!Text(q)) {
237: if (Char(tx-1) == ' ') tx--;
238: parerr2(MESS(2404, "nothing instead of expected "),
239: MESSMAKE(s));
240: return Yes;
241: }
242: return No;
243: }
244:
245: Hidden bool looked_ahead= No;
246: Visible intlet cur_ilev;
247:
248: Visible bool ateol() {
249: if (looked_ahead) return Yes;
250: skipsp(&tx);
251: return Eol(tx);
252: }
253:
254: Visible bool atkw(s) string s; {
255: txptr tx0= tx;
256: while (*s) if (*s++ != Char(tx0++)) return No;
257: if (keymark(Char(tx0))) return No;
258: tx= tx0;
259: return Yes;
260: }
261:
262: Visible Procedure need(s) string s; {
263: string t= s;
264: skipsp(&tx);
265: while (*t)
266: if (*t++ != Char(tx++)) {
267: tx--;
268: parerr2(MESS(2405, "according to the syntax I expected "),
269: MESSMAKE(s));
270: return;
271: }
272: }
273:
274: /* ******************************************************************** */
275: /* buffer handling */
276: /* ******************************************************************** */
277:
278: Visible txptr first_col;
279:
280: Visible txptr fcol() { /* the first position of the current line */
281: return first_col;
282: }
283:
284: Hidden txptr lcol() { /* the position beyond the last character of the line */
285: txptr ax= tx;
286: while (!Eol(ax)) ax++;
287: return ax;
288: }
289:
290: Visible intlet ilev() {
291: intlet i;
292: if (looked_ahead) {
293: looked_ahead= No;
294: return cur_ilev;
295: } else {
296: first_col= tx= getline();
297: looked_ahead= No;
298: lino++;
299: f_lino++;
300: i= 0;
301: while (Space(Char(tx)))
302: if (Char(tx++) == ' ') i++;
303: else i= (i/TABSIZE+1)*TABSIZE;
304: if (Char(tx) == '\\') return cur_ilev= 0;
305: if (Char(tx) == '\n') return cur_ilev= 0;
306: if (i%4 == 2)
307: parerr(MESS(2406, "cannot make out indentation; use tab to indent"));
308: return cur_ilev= (i+1)/4; /* small deviation accepted */
309: }
310: }
311:
312: Visible Procedure veli() { /* After a look-ahead call of ilev */
313: looked_ahead= Yes;
314: }
315:
316: Visible Procedure first_ilev() { /* initialise read buffer for new input */
317: looked_ahead= No;
318: VOID ilev();
319: findceol();
320: }
321:
322: /* ******************************************************************** */
323:
324: /* The reserved keywords that a user command may not begin with: */
325:
326: Visible value kwlist;
327:
328: Hidden string kwtab[] = {
329: K_SHARE, K_CHECK, K_CHOOSE, K_DELETE, K_DRAW, K_FAIL, K_FOR,
330: K_HOW_TO, K_IF, K_INSERT, K_PUT, K_QUIT, K_READ, K_REMOVE,
331: K_REPORT, K_RETURN, K_SELECT, K_SET_RANDOM, K_SUCCEED,
332: K_TEST, K_WHILE, K_WRITE, K_YIELD, K_ELSE,
333: ""
334: };
335:
336: Visible Procedure initsyn() {
337: value v;
338: string *kw;
339: kwlist= mk_elt();
340: for (kw= kwtab; **kw != '\0'; kw++) {
341: insert(v= mk_text(*kw), &kwlist);
342: release(v);
343: }
344: }
345:
346: Visible Procedure endsyn() {
347: release(kwlist); kwlist= Vnil;
348: }
349:
350: /* ******************************************************************** */
351: /* signs */
352: /* ******************************************************************** */
353:
354: Visible string textsign;
355:
356: Hidden bool la_denum(tx0) txptr tx0; {
357: char l, r;
358: switch (l= Char(++tx0)) {
359: case '/': r= '*'; break;
360: case '*': r= '/'; break;
361: default: return Yes;
362: }
363: do if (Char(++tx0) != r) return No; while (Char(++tx0) == l);
364: return Yes;
365: }
366:
367: #ifdef NOT_USED
368: Visible bool colon_sign() {
369: return Char(tx) == ':' ? (tx++, Yes) : No;
370: }
371: #endif
372:
373: bool comment_sign() {
374: return Char(tx) == '\\' ? (tx++, Yes) : No;
375: }
376:
377: Visible bool nwl_sign() {
378: return Char(tx) == '/' && !la_denum(tx-1) ? (tx++, Yes) : No;
379: }
380:
381: Visible bool open_sign() {
382: return Char(tx) == '(' ? (tx++, Yes) : No;
383: }
384:
385: #ifdef NOT_USED
386: Visible bool close_sign() {
387: return Char(tx) == ')' ? (tx++, Yes) : No;
388: }
389: #endif
390:
391: #ifdef NOT_USED
392: Visible bool comma_sign() {
393: return Char(tx) == ',' ? (tx++, Yes) : No;
394: }
395: #endif
396:
397: Visible bool point_sign() {
398: return Char(tx) == '.' ? (tx++, Yes) : No;
399: }
400:
401: Visible bool apostrophe_sign() {
402: return Char(tx) == '\'' ? (tx++, textsign= "'", Yes) : No;
403: }
404:
405: Visible bool quote_sign() {
406: return Char(tx) == '"' ? (tx++, textsign= "\"", Yes) : No;
407: }
408:
409: Visible bool conv_sign() {
410: return Char(tx) == '`' ? (tx++, Yes) : No;
411: }
412:
413: Visible bool curlyopen_sign() {
414: return Char(tx) == '{' ? (tx++, Yes) : No;
415: }
416:
417: Visible bool curlyclose_sign() {
418: return Char(tx) == '}' ? (tx++, Yes) : No;
419: }
420:
421: Visible bool sub_sign() {
422: return Char(tx) == '[' ? (tx++, Yes) : No;
423: }
424:
425: #ifdef NOT_USED
426: Visible bool bus_sign() {
427: return Char(tx) == ']' ? (tx++, Yes) : No;
428: }
429: #endif
430:
431: Visible bool behead_sign() {
432: return Char(tx) == '@' ? (tx++, textsign= "@", Yes) : No;
433: }
434:
435: Visible bool curtl_sign() {
436: return Char(tx) == '|' ? (tx++, textsign= "|", Yes) : No;
437: }
438:
439: Visible bool about_sign() {
440: return Char(tx) == '~' ? (tx++, textsign= "~", Yes) : No;
441: }
442:
443: Visible bool plus_sign() {
444: return Char(tx) == '+' ? (tx++, textsign= "+", Yes) : No;
445: }
446:
447: Visible bool minus_sign() {
448: return Char(tx) == '-' ? (tx++, textsign= "-", Yes) : No;
449: }
450:
451: Visible bool times_sign() {
452: return Char(tx) == '*' && la_denum(tx)
453: ? (tx++, textsign= "*", Yes) : No;
454: }
455:
456: Visible bool over_sign() {
457: return Char(tx) == '/' && la_denum(tx)
458: ? (tx++, textsign= "/", Yes) : No;
459: }
460:
461: Visible bool power_sign() {
462: return Char(tx) == '*' && Char(tx+1) == '*' && la_denum(tx+1)
463: ? (tx+= 2, textsign= "**", Yes) : No;
464: }
465:
466: Visible bool numtor_sign() {
467: return Char(tx) == '*' && Char(tx+1) == '/' && la_denum(tx+1)
468: ? (tx+= 2, textsign= "*/", Yes) : No;
469: }
470:
471: Visible bool denomtor_sign() {
472: return Char(tx) == '/' && Char(tx+1) == '*' && la_denum(tx+1)
473: ? (tx+= 2, textsign= "/*", Yes) : No;
474: }
475:
476: Visible bool join_sign() {
477: return Char(tx) == '^' && Char(tx+1) != '^'
478: ? (tx++, textsign= "^", Yes) : No;
479: }
480:
481: Visible bool reptext_sign() {
482: return Char(tx) == '^' && Char(tx+1) == '^'
483: ? (tx+= 2, textsign= "^^", Yes) : No;
484: }
485:
486: Visible bool leftadj_sign() {
487: return Char(tx) == '<' && Char(tx+1) == '<'
488: ? (tx+= 2, textsign= "<<", Yes) : No;
489: }
490:
491: Visible bool center_sign() {
492: return Char(tx) == '>' && Char(tx+1) == '<'
493: ? (tx+= 2, textsign= "><", Yes) : No;
494: }
495:
496: Visible bool rightadj_sign() {
497: return Char(tx) == '>' && Char(tx+1) == '>'
498: ? (tx+= 2, textsign= ">>", Yes) : No;
499: }
500:
501: Visible bool number_sign() {
502: return Char(tx) == '#' ? (tx++, textsign= "#", Yes) : No;
503: }
504:
505: Visible bool less_than_sign() {
506: return Char(tx) == '<' && Char(tx+1) != '=' &&
507: Char(tx+1) != '>' && Char(tx+1) != '<'
508: ? (tx++, Yes) : No;
509: }
510:
511: Visible bool at_most_sign() {
512: return Char(tx) == '<' && Char(tx+1) == '=' ? (tx+= 2, Yes) : No;
513: }
514:
515: Visible bool equals_sign() {
516: return Char(tx) == '=' ? (tx++, Yes) : No;
517: }
518:
519: Visible bool unequal_sign() {
520: return Char(tx) == '<' && Char(tx+1) == '>' ? (tx+= 2, Yes) : No;
521: }
522:
523: Visible bool at_least_sign() {
524: return Char(tx) == '>' && Char(tx+1) == '=' ? (tx+= 2, Yes) : No;
525: }
526:
527: Visible bool greater_than_sign() {
528: return Char(tx) == '>' && Char(tx+1) != '='
529: && Char(tx+1) != '>' && Char(tx+1) != '<'
530: ? (tx++, Yes) : No;
531: }
532:
533: Visible bool dyamon_sign() {
534: return plus_sign() || minus_sign() || number_sign();
535: }
536:
537: Visible bool dya_sign() {
538: return times_sign() || over_sign() || power_sign() ||
539: join_sign() || reptext_sign() ||
540: leftadj_sign() || center_sign() || rightadj_sign();
541: }
542:
543: Visible bool mon_sign() {
544: return about_sign() || numtor_sign() || denomtor_sign();
545: }
546:
547: Visible bool trim_sign() {
548: return behead_sign() || curtl_sign();
549: }
550:
551: Visible bool check_keyword() { return atkw(K_CHECK); }
552: Visible bool choose_keyword() { return atkw(K_CHOOSE); }
553: Visible bool delete_keyword() { return atkw(K_DELETE); }
554: Visible bool draw_keyword() { return atkw(K_DRAW); }
555: Visible bool insert_keyword() { return atkw(K_INSERT); }
556: Visible bool put_keyword() { return atkw(K_PUT); }
557: Visible bool read_keyword() { return atkw(K_READ); }
558: Visible bool remove_keyword() { return atkw(K_REMOVE); }
559: Visible bool setrandom_keyword() { return atkw(K_SET_RANDOM); }
560: Visible bool write_keyword() { return atkw(K_WRITE); }
561: Visible bool fail_keyword() { return atkw(K_FAIL); }
562: Visible bool quit_keyword() { return atkw(K_QUIT); }
563: Visible bool return_keyword() { return atkw(K_RETURN); }
564: Visible bool report_keyword() { return atkw(K_REPORT); }
565: Visible bool succeed_keyword() { return atkw(K_SUCCEED); }
566: Visible bool if_keyword() { return atkw(K_IF); }
567: Visible bool select_keyword() { return atkw(K_SELECT); }
568: Visible bool while_keyword() { return atkw(K_WHILE); }
569: Visible bool for_keyword() { return atkw(K_FOR); }
570: Visible bool else_keyword() { return atkw(K_ELSE); }
571: #ifdef NOT_USED
572: Visible bool and_keyword() { return atkw(K_AND); }
573: Visible bool or_keyword() { return atkw(K_OR); }
574: #endif
575: Visible bool not_keyword() { return atkw(K_NOT); }
576: Visible bool some_keyword() { return atkw(K_SOME); }
577: Visible bool each_keyword() { return atkw(K_EACH); }
578: Visible bool no_keyword() { return atkw(K_NO); }
579: Visible bool how_to_keyword() { return atkw(K_HOW_TO); }
580: Visible bool yield_keyword() { return atkw(K_YIELD); }
581: Visible bool test_keyword() { return atkw(K_TEST); }
582: Visible bool share_keyword() { return atkw(K_SHARE); }