1 /**************************************************************************/
2 /* */
3 /* OCaml */
4 /* */
5 /* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
6 /* */
7 /* Copyright 1996 Institut National de Recherche en Informatique et */
8 /* en Automatique. */
9 /* */
10 /* All rights reserved. This file is distributed under the terms of */
11 /* the GNU Lesser General Public License version 2.1, with the */
12 /* special exception on linking described in the file LICENSE. */
13 /* */
14 /**************************************************************************/
15
16 /* Based on public-domain code from Berkeley Yacc */
17
18 #include <string.h>
19 #include "defs.h"
20
21 /* The line size must be a positive integer. One hundred was chosen */
22 /* because few lines in Yacc input grammars exceed 100 characters. */
23 /* Note that if a line exceeds LINESIZE characters, the line buffer */
24 /* will be expanded to accomodate it. */
25
26 #define LINESIZE 100
27
28 char *cache;
29 int cinc, cache_size;
30
31 int ntags, tagmax;
32 char **tag_table;
33
34 char saw_eof, unionized;
35 char *cptr, *line;
36 int linesize;
37
38 bucket *goal;
39 int prec;
40 int gensym;
41 char last_was_action;
42
43 int maxitems;
44 bucket **pitem;
45
46 int maxrules;
47 bucket **plhs;
48
49 int name_pool_size;
50 char *name_pool;
51
52 char line_format[] = "# %d \"%s\"\n";
53
54
55
56 void start_rule (register bucket *bp, int s_lineno);
57
cachec(int c)58 void cachec(int c)
59 {
60 assert(cinc >= 0);
61 if (cinc >= cache_size)
62 {
63 cache_size += 256;
64 cache = REALLOC(cache, cache_size);
65 if (cache == 0) no_space();
66 }
67 cache[cinc] = c;
68 ++cinc;
69 }
70
71
get_line(void)72 void get_line(void)
73 {
74 register FILE *f = input_file;
75 register int c;
76 register int i;
77
78 if (saw_eof || (c = getc(f)) == EOF)
79 {
80 if (line) { FREE(line); line = 0; }
81 cptr = 0;
82 saw_eof = 1;
83 return;
84 }
85
86 if (line == 0 || linesize != (LINESIZE + 1))
87 {
88 if (line) FREE(line);
89 linesize = LINESIZE + 1;
90 line = MALLOC(linesize);
91 if (line == 0) no_space();
92 }
93
94 i = 0;
95 ++lineno;
96 for (;;)
97 {
98 line[i] = c;
99 if (++i >= linesize)
100 {
101 linesize += LINESIZE;
102 line = REALLOC(line, linesize);
103 if (line == 0) no_space();
104 }
105 if (c == '\n') {
106 if (i >= 2 && line[i-2] == '\r') {
107 line[i-2] = '\n'; i--;
108 }
109 line[i] = '\0'; cptr = line; return;
110 }
111 c = getc(f);
112 if (c == EOF) { saw_eof = 1; c = '\n'; }
113 }
114 }
115
116
117 char *
dup_line(void)118 dup_line(void)
119 {
120 register char *p, *s, *t;
121
122 if (line == 0) return (0);
123 s = line;
124 while (*s != '\n') ++s;
125 p = MALLOC(s - line + 1);
126 if (p == 0) no_space();
127
128 s = line;
129 t = p;
130 while ((*t++ = *s++) != '\n') continue;
131 return (p);
132 }
133
134
skip_comment(void)135 void skip_comment(void)
136 {
137 register char *s;
138
139 int st_lineno = lineno;
140 char *st_line = dup_line();
141 char *st_cptr = st_line + (cptr - line);
142
143 s = cptr + 2;
144 for (;;)
145 {
146 if (*s == '*' && s[1] == '/')
147 {
148 cptr = s + 2;
149 FREE(st_line);
150 return;
151 }
152 if (*s == '\n')
153 {
154 get_line();
155 if (line == 0)
156 unterminated_comment(st_lineno, st_line, st_cptr);
157 s = cptr;
158 }
159 else
160 ++s;
161 }
162 }
163
substring(char * str,int start,int len)164 char *substring (char *str, int start, int len)
165 {
166 int i;
167 char *buf = MALLOC (len+1);
168 if (buf == NULL) return NULL;
169 for (i = 0; i < len; i++){
170 buf[i] = str[start+i];
171 }
172 buf[i] = '\0'; /* PR#4796 */
173 return buf;
174 }
175
parse_line_directive(void)176 void parse_line_directive (void)
177 {
178 int i = 0, j = 0;
179 int line_number = 0;
180 char *file_name = NULL;
181
182 again:
183 if (line == 0) return;
184 if (line[i] != '#') return;
185 ++ i;
186 while (line[i] == ' ' || line[i] == '\t') ++ i;
187 if (line[i] < '0' || line[i] > '9') return;
188 while (line[i] >= '0' && line[i] <= '9'){
189 line_number = line_number * 10 + line[i] - '0';
190 ++ i;
191 }
192 while (line[i] == ' ' || line[i] == '\t') ++ i;
193 if (line[i] == '"'){
194 ++ i;
195 j = i;
196 while (line[j] != '"' && line[j] != '\0') ++j;
197 if (line[j] == '"'){
198 file_name = substring (line, i, j - i);
199 if (file_name == NULL) no_space ();
200 }
201 }
202 lineno = line_number - 1;
203 if (file_name != NULL){
204 if (virtual_input_file_name != NULL) FREE (virtual_input_file_name);
205 virtual_input_file_name = file_name;
206 }
207 get_line ();
208 goto again;
209 }
210
211 int
nextc(void)212 nextc(void)
213 {
214 register char *s;
215
216 if (line == 0)
217 {
218 get_line();
219 parse_line_directive ();
220 if (line == 0)
221 return (EOF);
222 }
223
224 s = cptr;
225 for (;;)
226 {
227 switch (*s)
228 {
229 case '\n':
230 get_line();
231 parse_line_directive ();
232 if (line == 0) return (EOF);
233 s = cptr;
234 break;
235
236 case ' ':
237 case '\t':
238 case '\f':
239 case '\r':
240 case '\v':
241 case ',':
242 case ';':
243 ++s;
244 break;
245
246 case '\\':
247 cptr = s;
248 return ('%');
249
250 case '/':
251 if (s[1] == '*')
252 {
253 cptr = s;
254 skip_comment();
255 s = cptr;
256 break;
257 }
258 else if (s[1] == '/')
259 {
260 get_line();
261 parse_line_directive ();
262 if (line == 0) return (EOF);
263 s = cptr;
264 break;
265 }
266 /* fall through */
267
268 default:
269 cptr = s;
270 return (*s);
271 }
272 }
273 }
274
275
276 int
keyword(void)277 keyword(void)
278 {
279 register int c;
280 char *t_cptr = cptr;
281
282 c = *++cptr;
283 if (isalpha(c))
284 {
285 cinc = 0;
286 for (;;)
287 {
288 if (isalpha(c))
289 {
290 if (isupper(c)) c = tolower(c);
291 cachec(c);
292 }
293 else if (isdigit(c) || c == '_' || c == '.' || c == '$')
294 cachec(c);
295 else
296 break;
297 c = *++cptr;
298 }
299 cachec(NUL);
300
301 if (strcmp(cache, "token") == 0 || strcmp(cache, "term") == 0)
302 return (TOKEN);
303 if (strcmp(cache, "type") == 0)
304 return (TYPE);
305 if (strcmp(cache, "left") == 0)
306 return (LEFT);
307 if (strcmp(cache, "right") == 0)
308 return (RIGHT);
309 if (strcmp(cache, "nonassoc") == 0 || strcmp(cache, "binary") == 0)
310 return (NONASSOC);
311 if (strcmp(cache, "start") == 0)
312 return (START);
313 if (strcmp(cache, "union") == 0)
314 return (UNION);
315 if (strcmp(cache, "ident") == 0)
316 return (IDENT);
317 }
318 else
319 {
320 ++cptr;
321 if (c == '{')
322 return (TEXT);
323 if (c == '%' || c == '\\')
324 return (MARK);
325 if (c == '<')
326 return (LEFT);
327 if (c == '>')
328 return (RIGHT);
329 if (c == '0')
330 return (TOKEN);
331 if (c == '2')
332 return (NONASSOC);
333 }
334 syntax_error(lineno, line, t_cptr);
335 /*NOTREACHED*/
336 return 0;
337 }
338
339
copy_ident(void)340 void copy_ident(void)
341 {
342 register int c;
343 register FILE *f = output_file;
344
345 c = nextc();
346 if (c == EOF) unexpected_EOF();
347 if (c != '"') syntax_error(lineno, line, cptr);
348 ++outline;
349 fprintf(f, "#ident \"");
350 for (;;)
351 {
352 c = *++cptr;
353 if (c == '\n')
354 {
355 fprintf(f, "\"\n");
356 return;
357 }
358 putc(c, f);
359 if (c == '"')
360 {
361 putc('\n', f);
362 ++cptr;
363 return;
364 }
365 }
366 }
367
368
copy_text(void)369 void copy_text(void)
370 {
371 register int c;
372 int quote;
373 register FILE *f = text_file;
374 int need_newline = 0;
375 int t_lineno = lineno;
376 char *t_line = dup_line();
377 char *t_cptr = t_line + (cptr - line - 2);
378
379 if (*cptr == '\n')
380 {
381 get_line();
382 if (line == 0)
383 unterminated_text(t_lineno, t_line, t_cptr);
384 }
385 fprintf(f, line_format, lineno, input_file_name);
386
387 loop:
388 c = *cptr++;
389 switch (c)
390 {
391 case '\n':
392 putc('\n', f);
393 need_newline = 0;
394 get_line();
395 if (line) goto loop;
396 unterminated_text(t_lineno, t_line, t_cptr);
397
398 case '"':
399 {
400 int s_lineno = lineno;
401 char *s_line = dup_line();
402 char *s_cptr = s_line + (cptr - line - 1);
403
404 quote = c;
405 putc(c, f);
406 for (;;)
407 {
408 c = *cptr++;
409 putc(c, f);
410 if (c == quote)
411 {
412 need_newline = 1;
413 FREE(s_line);
414 goto loop;
415 }
416 if (c == '\n')
417 unterminated_string(s_lineno, s_line, s_cptr);
418 if (c == '\\')
419 {
420 c = *cptr++;
421 putc(c, f);
422 if (c == '\n')
423 {
424 get_line();
425 if (line == 0)
426 unterminated_string(s_lineno, s_line, s_cptr);
427 }
428 }
429 }
430 }
431
432 case '\'':
433 putc(c, f);
434 if (cptr[0] != 0 && cptr[0] != '\\' && cptr[1] == '\'') {
435 fwrite(cptr, 1, 2, f);
436 cptr += 2;
437 } else
438 if (cptr[0] == '\\'
439 && isdigit((unsigned char) cptr[1])
440 && isdigit((unsigned char) cptr[2])
441 && isdigit((unsigned char) cptr[3])
442 && cptr[4] == '\'') {
443 fwrite(cptr, 1, 5, f);
444 cptr += 5;
445 } else
446 if (cptr[0] == '\\' && cptr[2] == '\'') {
447 fwrite(cptr, 1, 3, f);
448 cptr += 3;
449 }
450 goto loop;
451
452 case '(':
453 putc(c, f);
454 need_newline = 1;
455 c = *cptr;
456 if (c == '*')
457 {
458 int c_lineno = lineno;
459 char *c_line = dup_line();
460 char *c_cptr = c_line + (cptr - line - 1);
461
462 putc('*', f);
463 ++cptr;
464 for (;;)
465 {
466 c = *cptr++;
467 putc(c, f);
468 if (c == '*' && *cptr == ')')
469 {
470 putc(')', f);
471 ++cptr;
472 FREE(c_line);
473 goto loop;
474 }
475 if (c == '\n')
476 {
477 get_line();
478 if (line == 0)
479 unterminated_comment(c_lineno, c_line, c_cptr);
480 }
481 }
482 }
483 need_newline = 1;
484 goto loop;
485
486 case '%':
487 case '\\':
488 if (*cptr == '}')
489 {
490 if (need_newline) putc('\n', f);
491 ++cptr;
492 FREE(t_line);
493 return;
494 }
495 /* fall through */
496
497 default:
498 putc(c, f);
499 need_newline = 1;
500 goto loop;
501 }
502 }
503
504
copy_union(void)505 void copy_union(void)
506 {
507 register int c;
508 int quote;
509 int depth;
510 int u_lineno = lineno;
511 char *u_line = dup_line();
512 char *u_cptr = u_line + (cptr - line - 6);
513
514 if (unionized) over_unionized(cptr - 6);
515 unionized = 1;
516
517 if (!lflag)
518 fprintf(text_file, line_format, lineno, input_file_name);
519
520 fprintf(text_file, "typedef union");
521 if (dflag) fprintf(union_file, "typedef union");
522
523 depth = 1;
524 cptr++;
525
526 loop:
527 c = *cptr++;
528 putc(c, text_file);
529 if (dflag) putc(c, union_file);
530 switch (c)
531 {
532 case '\n':
533 get_line();
534 if (line == 0) unterminated_union(u_lineno, u_line, u_cptr);
535 goto loop;
536
537 case '{':
538 ++depth;
539 goto loop;
540
541 case '}':
542 --depth;
543 if (c == '}' && depth == 0) {
544 fprintf(text_file, " YYSTYPE;\n");
545 FREE(u_line);
546 return;
547 }
548 goto loop;
549
550 case '\'':
551 case '"':
552 {
553 int s_lineno = lineno;
554 char *s_line = dup_line();
555 char *s_cptr = s_line + (cptr - line - 1);
556
557 quote = c;
558 for (;;)
559 {
560 c = *cptr++;
561 putc(c, text_file);
562 if (dflag) putc(c, union_file);
563 if (c == quote)
564 {
565 FREE(s_line);
566 goto loop;
567 }
568 if (c == '\n')
569 unterminated_string(s_lineno, s_line, s_cptr);
570 if (c == '\\')
571 {
572 c = *cptr++;
573 putc(c, text_file);
574 if (dflag) putc(c, union_file);
575 if (c == '\n')
576 {
577 get_line();
578 if (line == 0)
579 unterminated_string(s_lineno, s_line, s_cptr);
580 }
581 }
582 }
583 }
584
585 case '(':
586 c = *cptr;
587 if (c == '*')
588 {
589 int c_lineno = lineno;
590 char *c_line = dup_line();
591 char *c_cptr = c_line + (cptr - line - 1);
592
593 putc('*', text_file);
594 if (dflag) putc('*', union_file);
595 ++cptr;
596 for (;;)
597 {
598 c = *cptr++;
599 putc(c, text_file);
600 if (dflag) putc(c, union_file);
601 if (c == '*' && *cptr == ')')
602 {
603 putc(')', text_file);
604 if (dflag) putc(')', union_file);
605 ++cptr;
606 FREE(c_line);
607 goto loop;
608 }
609 if (c == '\n')
610 {
611 get_line();
612 if (line == 0)
613 unterminated_comment(c_lineno, c_line, c_cptr);
614 }
615 }
616 }
617 goto loop;
618
619 default:
620 goto loop;
621 }
622 }
623
624
625 int
hexval(int c)626 hexval(int c)
627 {
628 if (c >= '0' && c <= '9')
629 return (c - '0');
630 if (c >= 'A' && c <= 'F')
631 return (c - 'A' + 10);
632 if (c >= 'a' && c <= 'f')
633 return (c - 'a' + 10);
634 return (-1);
635 }
636
637
638 bucket *
get_literal(void)639 get_literal(void)
640 {
641 register int c, quote;
642 register int i;
643 register int n;
644 register char *s;
645 register bucket *bp;
646 int s_lineno = lineno;
647 char *s_line = dup_line();
648 char *s_cptr = s_line + (cptr - line);
649
650 quote = *cptr++;
651 cinc = 0;
652 for (;;)
653 {
654 c = *cptr++;
655 if (c == quote) break;
656 if (c == '\n') unterminated_string(s_lineno, s_line, s_cptr);
657 if (c == '\\')
658 {
659 char *c_cptr = cptr - 1;
660
661 c = *cptr++;
662 switch (c)
663 {
664 case '\n':
665 get_line();
666 if (line == 0) unterminated_string(s_lineno, s_line, s_cptr);
667 continue;
668
669 case '0': case '1': case '2': case '3':
670 case '4': case '5': case '6': case '7':
671 n = c - '0';
672 c = *cptr;
673 if (IS_OCTAL(c))
674 {
675 n = (n << 3) + (c - '0');
676 c = *++cptr;
677 if (IS_OCTAL(c))
678 {
679 n = (n << 3) + (c - '0');
680 ++cptr;
681 }
682 }
683 if (n > MAXCHAR) illegal_character(c_cptr);
684 c = n;
685 break;
686
687 case 'x':
688 c = *cptr++;
689 n = hexval(c);
690 if (n < 0 || n >= 16)
691 illegal_character(c_cptr);
692 for (;;)
693 {
694 c = *cptr;
695 i = hexval(c);
696 if (i < 0 || i >= 16) break;
697 ++cptr;
698 n = (n << 4) + i;
699 if (n > MAXCHAR) illegal_character(c_cptr);
700 }
701 c = n;
702 break;
703
704 case 'a': c = 7; break;
705 case 'b': c = '\b'; break;
706 case 'f': c = '\f'; break;
707 case 'n': c = '\n'; break;
708 case 'r': c = '\r'; break;
709 case 't': c = '\t'; break;
710 case 'v': c = '\v'; break;
711 }
712 }
713 cachec(c);
714 }
715 FREE(s_line);
716
717 n = cinc;
718 s = MALLOC(n);
719 if (s == 0) no_space();
720
721 for (i = 0; i < n; ++i)
722 s[i] = cache[i];
723
724 cinc = 0;
725 if (n == 1)
726 cachec('\'');
727 else
728 cachec('"');
729
730 for (i = 0; i < n; ++i)
731 {
732 c = ((unsigned char *)s)[i];
733 if (c == '\\' || c == cache[0])
734 {
735 cachec('\\');
736 cachec(c);
737 }
738 else if (isprint(c))
739 cachec(c);
740 else
741 {
742 cachec('\\');
743 switch (c)
744 {
745 case 7: cachec('a'); break;
746 case '\b': cachec('b'); break;
747 case '\f': cachec('f'); break;
748 case '\n': cachec('n'); break;
749 case '\r': cachec('r'); break;
750 case '\t': cachec('t'); break;
751 case '\v': cachec('v'); break;
752 default:
753 cachec(((c >> 6) & 7) + '0');
754 cachec(((c >> 3) & 7) + '0');
755 cachec((c & 7) + '0');
756 break;
757 }
758 }
759 }
760
761 if (n == 1)
762 cachec('\'');
763 else
764 cachec('"');
765
766 cachec(NUL);
767 bp = lookup(cache);
768 bp->class = TERM;
769 if (n == 1 && bp->value == UNDEFINED)
770 bp->value = *(unsigned char *)s;
771 FREE(s);
772
773 return (bp);
774 }
775
776
777 int
is_reserved(char * name)778 is_reserved(char *name)
779 {
780 char *s;
781
782 if (strcmp(name, ".") == 0 ||
783 strcmp(name, "$accept") == 0 ||
784 strcmp(name, "$end") == 0)
785 return (1);
786
787 if (name[0] == '$' && name[1] == '$' && isdigit((unsigned char) name[2]))
788 {
789 s = name + 3;
790 while (isdigit((unsigned char) *s)) ++s;
791 if (*s == NUL) return (1);
792 }
793
794 return (0);
795 }
796
797
798 bucket *
get_name(void)799 get_name(void)
800 {
801 register int c;
802
803 cinc = 0;
804 for (c = *cptr; IS_IDENT(c); c = *++cptr)
805 cachec(c);
806 cachec(NUL);
807
808 if (is_reserved(cache)) used_reserved(cache);
809
810 return (lookup(cache));
811 }
812
813
814 int
get_number(void)815 get_number(void)
816 {
817 register int c;
818 register int n;
819
820 n = 0;
821 for (c = *cptr; isdigit(c); c = *++cptr)
822 n = 10*n + (c - '0');
823
824 return (n);
825 }
826
827
828 char *
get_tag(void)829 get_tag(void)
830 {
831 register int c;
832 register int i;
833 register char *s;
834 char *t_line = dup_line();
835 long bracket_depth;
836
837 cinc = 0;
838 bracket_depth = 0;
839 while (1) {
840 c = *++cptr;
841 if (c == EOF) unexpected_EOF();
842 if (c == '\n') syntax_error(lineno, line, cptr);
843 if (c == '>' && 0 == bracket_depth && cptr[-1] != '-') break;
844 if (c == '[') ++ bracket_depth;
845 if (c == ']') -- bracket_depth;
846 cachec(c);
847 }
848 ++cptr;
849 cachec(NUL);
850
851 for (i = 0; i < ntags; ++i)
852 {
853 if (strcmp(cache, tag_table[i]) == 0)
854 return (tag_table[i]);
855 }
856
857 if (ntags >= tagmax)
858 {
859 tagmax += 16;
860 tag_table = (char **)
861 (tag_table ? REALLOC(tag_table, tagmax*sizeof(char *))
862 : MALLOC(tagmax*sizeof(char *)));
863 if (tag_table == 0) no_space();
864 }
865
866 s = MALLOC(cinc);
867 if (s == 0) no_space();
868 strcpy(s, cache);
869 tag_table[ntags] = s;
870 ++ntags;
871 FREE(t_line);
872 return (s);
873 }
874
875
declare_tokens(int assoc)876 void declare_tokens(int assoc)
877 {
878 register int c;
879 register bucket *bp;
880 char *tag = 0;
881
882 if (assoc != TOKEN) ++prec;
883
884 c = nextc();
885 if (c == EOF) unexpected_EOF();
886 if (c == '<')
887 {
888 tag = get_tag();
889 c = nextc();
890 if (c == EOF) unexpected_EOF();
891 }
892
893 for (;;)
894 {
895 if (isalpha(c) || c == '_' || c == '.' || c == '$')
896 bp = get_name();
897 else if (c == '\'' || c == '"')
898 bp = get_literal();
899 else
900 return;
901
902 if (bp == goal) tokenized_start(bp->name);
903 bp->class = TERM;
904
905 if (tag)
906 {
907 if (bp->tag && tag != bp->tag)
908 retyped_warning(bp->name);
909 bp->tag = tag;
910 }
911
912 if (assoc == TOKEN)
913 {
914 bp->true_token = 1;
915 }
916 else
917 {
918 if (bp->prec && prec != bp->prec)
919 reprec_warning(bp->name);
920 bp->assoc = assoc;
921 bp->prec = prec;
922 }
923
924 if (strcmp(bp->name, "EOF") == 0)
925 bp->value = 0;
926
927 c = nextc();
928 if (c == EOF) unexpected_EOF();
929 if (isdigit(c))
930 {
931 int value = get_number();
932 if (bp->value != UNDEFINED && value != bp->value)
933 revalued_warning(bp->name);
934 bp->value = value;
935 c = nextc();
936 if (c == EOF) unexpected_EOF();
937 }
938 }
939 }
940
941
declare_types(void)942 void declare_types(void)
943 {
944 register int c;
945 register bucket *bp;
946 char *tag;
947
948 c = nextc();
949 if (c == EOF) unexpected_EOF();
950 if (c != '<') syntax_error(lineno, line, cptr);
951 tag = get_tag();
952
953 for (;;)
954 {
955 c = nextc();
956 if (isalpha(c) || c == '_' || c == '.' || c == '$')
957 bp = get_name();
958 else if (c == '\'' || c == '"')
959 bp = get_literal();
960 else
961 return;
962
963 if (bp->tag && tag != bp->tag)
964 retyped_warning(bp->name);
965 bp->tag = tag;
966 }
967 }
968
969
declare_start(void)970 void declare_start(void)
971 {
972 register int c;
973 register bucket *bp;
974 static int entry_counter = 0;
975
976 for (;;) {
977 c = nextc();
978 if (!isalpha(c) && c != '_' && c != '.' && c != '$') return;
979 bp = get_name();
980
981 if (bp->class == TERM)
982 terminal_start(bp->name);
983 bp->entry = ++entry_counter;
984 if (entry_counter == 256)
985 too_many_entries();
986 }
987 }
988
989
read_declarations(void)990 void read_declarations(void)
991 {
992 register int c, k;
993
994 cache_size = 256;
995 cache = MALLOC(cache_size);
996 if (cache == 0) no_space();
997
998 for (;;)
999 {
1000 c = nextc();
1001 if (c == EOF) unexpected_EOF();
1002 if (c != '%') syntax_error(lineno, line, cptr);
1003 switch (k = keyword())
1004 {
1005 case MARK:
1006 return;
1007
1008 case IDENT:
1009 copy_ident();
1010 break;
1011
1012 case TEXT:
1013 copy_text();
1014 break;
1015
1016 case UNION:
1017 copy_union();
1018 break;
1019
1020 case TOKEN:
1021 case LEFT:
1022 case RIGHT:
1023 case NONASSOC:
1024 declare_tokens(k);
1025 break;
1026
1027 case TYPE:
1028 declare_types();
1029 break;
1030
1031 case START:
1032 declare_start();
1033 break;
1034 }
1035 }
1036 }
1037
output_token_type(void)1038 void output_token_type(void)
1039 {
1040 bucket * bp;
1041 int n;
1042
1043 fprintf(interface_file, "type token =\n");
1044 if (!rflag) ++outline;
1045 fprintf(output_file, "type token =\n");
1046 n = 0;
1047 for (bp = first_symbol; bp; bp = bp->next) {
1048 if (bp->class == TERM && bp->true_token) {
1049 fprintf(interface_file, " | %s", bp->name);
1050 fprintf(output_file, " | %s", bp->name);
1051 if (bp->tag) {
1052 /* Print the type expression in parentheses to make sure
1053 that the constructor is unary */
1054 fprintf(interface_file, " of (%s)", bp->tag);
1055 fprintf(output_file, " of (%s)", bp->tag);
1056 }
1057 fprintf(interface_file, "\n");
1058 if (!rflag) ++outline;
1059 fprintf(output_file, "\n");
1060 n++;
1061 }
1062 }
1063 fprintf(interface_file, "\n");
1064 if (!rflag) ++outline;
1065 fprintf(output_file, "\n");
1066 }
1067
initialize_grammar(void)1068 void initialize_grammar(void)
1069 {
1070 nitems = 4;
1071 maxitems = 300;
1072 pitem = (bucket **) MALLOC(maxitems*sizeof(bucket *));
1073 if (pitem == 0) no_space();
1074 pitem[0] = 0;
1075 pitem[1] = 0;
1076 pitem[2] = 0;
1077 pitem[3] = 0;
1078
1079 nrules = 3;
1080 maxrules = 100;
1081 plhs = (bucket **) MALLOC(maxrules*sizeof(bucket *));
1082 if (plhs == 0) no_space();
1083 plhs[0] = 0;
1084 plhs[1] = 0;
1085 plhs[2] = 0;
1086 rprec = (short *) MALLOC(maxrules*sizeof(short));
1087 if (rprec == 0) no_space();
1088 rprec[0] = 0;
1089 rprec[1] = 0;
1090 rprec[2] = 0;
1091 rassoc = (char *) MALLOC(maxrules*sizeof(char));
1092 if (rassoc == 0) no_space();
1093 rassoc[0] = TOKEN;
1094 rassoc[1] = TOKEN;
1095 rassoc[2] = TOKEN;
1096 }
1097
1098
expand_items(void)1099 void expand_items(void)
1100 {
1101 maxitems += 300;
1102 pitem = (bucket **) REALLOC(pitem, maxitems*sizeof(bucket *));
1103 if (pitem == 0) no_space();
1104 }
1105
1106
expand_rules(void)1107 void expand_rules(void)
1108 {
1109 maxrules += 100;
1110 plhs = (bucket **) REALLOC(plhs, maxrules*sizeof(bucket *));
1111 if (plhs == 0) no_space();
1112 rprec = (short *) REALLOC(rprec, maxrules*sizeof(short));
1113 if (rprec == 0) no_space();
1114 rassoc = (char *) REALLOC(rassoc, maxrules*sizeof(char));
1115 if (rassoc == 0) no_space();
1116 }
1117
1118
advance_to_start(void)1119 void advance_to_start(void)
1120 {
1121 register int c;
1122 register bucket *bp;
1123 char *s_cptr;
1124 int s_lineno;
1125
1126 for (;;)
1127 {
1128 c = nextc();
1129 if (c != '%') break;
1130 s_cptr = cptr;
1131 switch (keyword())
1132 {
1133 case MARK:
1134 no_grammar();
1135
1136 case TEXT:
1137 copy_text();
1138 break;
1139
1140 case START:
1141 declare_start();
1142 break;
1143
1144 default:
1145 syntax_error(lineno, line, s_cptr);
1146 }
1147 }
1148
1149 c = nextc();
1150 if (!isalpha(c) && c != '_' && c != '.' && c != '_')
1151 syntax_error(lineno, line, cptr);
1152 bp = get_name();
1153 if (goal == 0)
1154 {
1155 if (bp->class == TERM)
1156 terminal_start(bp->name);
1157 goal = bp;
1158 }
1159
1160 s_lineno = lineno;
1161 c = nextc();
1162 if (c == EOF) unexpected_EOF();
1163 if (c != ':') syntax_error(lineno, line, cptr);
1164 start_rule(bp, s_lineno);
1165 ++cptr;
1166 }
1167
1168
1169 int at_first;
1170
start_rule(register bucket * bp,int s_lineno)1171 void start_rule(register bucket *bp, int s_lineno)
1172 {
1173 if (bp->class == TERM)
1174 terminal_lhs(s_lineno);
1175 bp->class = NONTERM;
1176 if (nrules >= maxrules)
1177 expand_rules();
1178 plhs[nrules] = bp;
1179 rprec[nrules] = UNDEFINED;
1180 rassoc[nrules] = TOKEN;
1181 at_first = 1;
1182 }
1183
1184
end_rule(void)1185 void end_rule(void)
1186 {
1187 if (!last_was_action) default_action_error();
1188
1189 last_was_action = 0;
1190 if (nitems >= maxitems) expand_items();
1191 pitem[nitems] = 0;
1192 ++nitems;
1193 ++nrules;
1194 }
1195
1196
insert_empty_rule(void)1197 void insert_empty_rule(void)
1198 {
1199 register bucket *bp, **bpp;
1200
1201 assert(cache);
1202 sprintf(cache, "$$%d", ++gensym);
1203 bp = make_bucket(cache);
1204 last_symbol->next = bp;
1205 last_symbol = bp;
1206 bp->tag = plhs[nrules]->tag;
1207 bp->class = NONTERM;
1208
1209 if ((nitems += 2) > maxitems)
1210 expand_items();
1211 bpp = pitem + nitems - 1;
1212 *bpp-- = bp;
1213 while ((bpp[0] = bpp[-1])) --bpp;
1214
1215 if (++nrules >= maxrules)
1216 expand_rules();
1217 plhs[nrules] = plhs[nrules-1];
1218 plhs[nrules-1] = bp;
1219 rprec[nrules] = rprec[nrules-1];
1220 rprec[nrules-1] = 0;
1221 rassoc[nrules] = rassoc[nrules-1];
1222 rassoc[nrules-1] = TOKEN;
1223 }
1224
1225
add_symbol(void)1226 void add_symbol(void)
1227 {
1228 register int c;
1229 register bucket *bp;
1230 int s_lineno = lineno;
1231 char *ecptr = cptr;
1232
1233 c = *cptr;
1234 if (c == '\'' || c == '"')
1235 bp = get_literal();
1236 else
1237 bp = get_name();
1238
1239 c = nextc();
1240 if (c == ':')
1241 {
1242 end_rule();
1243 start_rule(bp, s_lineno);
1244 ++cptr;
1245 return;
1246 }
1247
1248 if (last_was_action) syntax_error (lineno, line, ecptr);
1249 last_was_action = 0;
1250
1251 if (++nitems > maxitems)
1252 expand_items();
1253 pitem[nitems-1] = bp;
1254 }
1255
1256
copy_action(void)1257 void copy_action(void)
1258 {
1259 register int c;
1260 register int i, n;
1261 int depth;
1262 int quote;
1263 bucket *item;
1264 char *tagres;
1265 register FILE *f = action_file;
1266 int a_lineno = lineno;
1267 char *a_line = dup_line();
1268 char *a_cptr = a_line + (cptr - line);
1269
1270 if (last_was_action) syntax_error (lineno, line, cptr);
1271 last_was_action = 1;
1272
1273 /*
1274 fprintf(f, "(* Rule %d, file %s, line %d *)\n",
1275 nrules-2, input_file_name, lineno);
1276 */
1277 if (sflag)
1278 fprintf(f, "yyact.(%d) <- (fun __caml_parser_env ->\n", nrules-2);
1279 else
1280 fprintf(f, "; (fun __caml_parser_env ->\n");
1281
1282 n = 0;
1283 for (i = nitems - 1; pitem[i]; --i) ++n;
1284
1285 for (i = 1; i <= n; i++) {
1286 item = pitem[nitems + i - n - 1];
1287 if (item->class == TERM && !item->tag) continue;
1288 fprintf(f, " let _%d = ", i);
1289 if (item->tag)
1290 fprintf(f, "(Parsing.peek_val __caml_parser_env %d : %s) in\n", n - i,
1291 item->tag);
1292 else if (sflag)
1293 fprintf(f, "Parsing.peek_val __caml_parser_env %d in\n", n - i);
1294 else
1295 fprintf(f, "(Parsing.peek_val __caml_parser_env %d : '%s) in\n", n - i,
1296 item->name);
1297 }
1298 fprintf(f, " Obj.repr(\n");
1299 fprintf(f, line_format, lineno, input_file_name);
1300 for (i = 0; i < cptr - line; i++) fputc(' ', f);
1301 fputc ('(', f);
1302
1303 depth = 1;
1304 cptr++;
1305
1306 loop:
1307 c = *cptr;
1308 if (c == '$')
1309 {
1310 if (isdigit((unsigned char) cptr[1]))
1311 {
1312 ++cptr;
1313 i = get_number();
1314
1315 if (i <= 0 || i > n)
1316 unknown_rhs(i);
1317 item = pitem[nitems + i - n - 1];
1318 if (item->class == TERM && !item->tag)
1319 illegal_token_ref(i, item->name);
1320 fprintf(f, "_%d", i);
1321 goto loop;
1322 }
1323 }
1324 if (isalpha(c) || c == '_' || c == '$')
1325 {
1326 do
1327 {
1328 putc(c, f);
1329 c = *++cptr;
1330 } while (isalnum(c) || c == '_' || c == '$');
1331 goto loop;
1332 }
1333 if (c == '}' && depth == 1) {
1334 fprintf(f, ")\n# 0\n ");
1335 cptr++;
1336 tagres = plhs[nrules]->tag;
1337 if (tagres)
1338 fprintf(f, " : %s))\n", tagres);
1339 else if (sflag)
1340 fprintf(f, "))\n");
1341 else
1342 fprintf(f, " : '%s))\n", plhs[nrules]->name);
1343 if (sflag)
1344 fprintf(f, "\n");
1345 FREE(a_line);
1346 return;
1347 }
1348 putc(c, f);
1349 ++cptr;
1350 switch (c)
1351 {
1352 case '\n':
1353 get_line();
1354 if (line) goto loop;
1355 unterminated_action(a_lineno, a_line, a_cptr);
1356
1357 case '{':
1358 ++depth;
1359 goto loop;
1360
1361 case '}':
1362 --depth;
1363 goto loop;
1364
1365 case '"':
1366 {
1367 int s_lineno = lineno;
1368 char *s_line = dup_line();
1369 char *s_cptr = s_line + (cptr - line - 1);
1370
1371 quote = c;
1372 for (;;)
1373 {
1374 c = *cptr++;
1375 putc(c, f);
1376 if (c == quote)
1377 {
1378 FREE(s_line);
1379 goto loop;
1380 }
1381 if (c == '\n')
1382 unterminated_string(s_lineno, s_line, s_cptr);
1383 if (c == '\\')
1384 {
1385 c = *cptr++;
1386 putc(c, f);
1387 if (c == '\n')
1388 {
1389 get_line();
1390 if (line == 0)
1391 unterminated_string(s_lineno, s_line, s_cptr);
1392 }
1393 }
1394 }
1395 }
1396
1397 case '\'':
1398 if (cptr[0] != 0 && cptr[0] != '\\' && cptr[1] == '\'') {
1399 fwrite(cptr, 1, 2, f);
1400 cptr += 2;
1401 } else
1402 if (cptr[0] == '\\'
1403 && isdigit((unsigned char) cptr[1])
1404 && isdigit((unsigned char) cptr[2])
1405 && isdigit((unsigned char) cptr[3])
1406 && cptr[4] == '\'') {
1407 fwrite(cptr, 1, 5, f);
1408 cptr += 5;
1409 } else
1410 if (cptr[0] == '\\' && cptr[2] == '\'') {
1411 fwrite(cptr, 1, 3, f);
1412 cptr += 3;
1413 }
1414 goto loop;
1415
1416 case '(':
1417 c = *cptr;
1418 if (c == '*')
1419 {
1420 int c_lineno = lineno;
1421 char *c_line = dup_line();
1422 char *c_cptr = c_line + (cptr - line - 1);
1423
1424 putc('*', f);
1425 ++cptr;
1426 for (;;)
1427 {
1428 c = *cptr++;
1429 putc(c, f);
1430 if (c == '*' && *cptr == ')')
1431 {
1432 putc(')', f);
1433 ++cptr;
1434 FREE(c_line);
1435 goto loop;
1436 }
1437 if (c == '\n')
1438 {
1439 get_line();
1440 if (line == 0)
1441 unterminated_comment(c_lineno, c_line, c_cptr);
1442 }
1443 }
1444 }
1445 goto loop;
1446
1447 default:
1448 goto loop;
1449 }
1450 }
1451
1452
1453 int
mark_symbol(void)1454 mark_symbol(void)
1455 {
1456 register int c;
1457 register bucket *bp;
1458
1459 c = cptr[1];
1460 if (c == '%' || c == '\\')
1461 {
1462 cptr += 2;
1463 return (1);
1464 }
1465
1466 if (c == '=')
1467 cptr += 2;
1468 else if ((c == 'p' || c == 'P') &&
1469 ((c = cptr[2]) == 'r' || c == 'R') &&
1470 ((c = cptr[3]) == 'e' || c == 'E') &&
1471 ((c = cptr[4]) == 'c' || c == 'C') &&
1472 ((c = cptr[5], !IS_IDENT(c))))
1473 cptr += 5;
1474 else
1475 syntax_error(lineno, line, cptr);
1476
1477 c = nextc();
1478 if (isalpha(c) || c == '_' || c == '.' || c == '$')
1479 bp = get_name();
1480 else if (c == '\'' || c == '"')
1481 bp = get_literal();
1482 else
1483 {
1484 syntax_error(lineno, line, cptr);
1485 /*NOTREACHED*/
1486 }
1487
1488 if (rprec[nrules] != UNDEFINED && bp->prec != rprec[nrules])
1489 prec_redeclared();
1490
1491 rprec[nrules] = bp->prec;
1492 rassoc[nrules] = bp->assoc;
1493 return (0);
1494 }
1495
1496
read_grammar(void)1497 void read_grammar(void)
1498 {
1499 register int c;
1500
1501 initialize_grammar();
1502 advance_to_start();
1503
1504 for (;;)
1505 {
1506 c = nextc();
1507 if (c == '|' && at_first){
1508 ++cptr;
1509 c = nextc();
1510 }
1511 at_first = 0;
1512 if (c == EOF) break;
1513 if (isalpha(c) || c == '_' || c == '.' || c == '$' || c == '\'' ||
1514 c == '"')
1515 add_symbol();
1516 else if (c == '{' || c == '=')
1517 copy_action();
1518 else if (c == '|')
1519 {
1520 end_rule();
1521 start_rule(plhs[nrules-1], 0);
1522 ++cptr;
1523 }
1524 else if (c == '%')
1525 {
1526 if (mark_symbol()) break;
1527 }
1528 else
1529 syntax_error(lineno, line, cptr);
1530 }
1531 end_rule();
1532 }
1533
1534
free_tags(void)1535 void free_tags(void)
1536 {
1537 register int i;
1538
1539 if (tag_table == 0) return;
1540
1541 for (i = 0; i < ntags; ++i)
1542 {
1543 assert(tag_table[i]);
1544 FREE(tag_table[i]);
1545 }
1546 FREE(tag_table);
1547 }
1548
1549
pack_names(void)1550 void pack_names(void)
1551 {
1552 register bucket *bp;
1553 register char *p, *s, *t;
1554
1555 name_pool_size = 13; /* 13 == sizeof("$end") + sizeof("$accept") */
1556 for (bp = first_symbol; bp; bp = bp->next)
1557 name_pool_size += strlen(bp->name) + 1;
1558 name_pool = MALLOC(name_pool_size);
1559 if (name_pool == 0) no_space();
1560
1561 strcpy(name_pool, "$accept");
1562 strcpy(name_pool+8, "$end");
1563 t = name_pool + 13;
1564 for (bp = first_symbol; bp; bp = bp->next)
1565 {
1566 p = t;
1567 s = bp->name;
1568 while ((*t++ = *s++)) continue;
1569 FREE(bp->name);
1570 bp->name = p;
1571 }
1572 }
1573
1574
check_symbols(void)1575 void check_symbols(void)
1576 {
1577 register bucket *bp;
1578
1579 if (goal->class == UNKNOWN)
1580 undefined_goal(goal->name);
1581
1582 for (bp = first_symbol; bp; bp = bp->next)
1583 {
1584 if (bp->class == UNKNOWN)
1585 {
1586 undefined_symbol(bp->name);
1587 bp->class = TERM;
1588 }
1589 }
1590 }
1591
1592
pack_symbols(void)1593 void pack_symbols(void)
1594 {
1595 register bucket *bp;
1596 register bucket **v;
1597 register int i, j, k, n;
1598
1599 nsyms = 2;
1600 ntokens = 1;
1601 for (bp = first_symbol; bp; bp = bp->next)
1602 {
1603 ++nsyms;
1604 if (bp->class == TERM) ++ntokens;
1605 }
1606 start_symbol = ntokens;
1607 nvars = nsyms - ntokens;
1608
1609 symbol_name = (char **) MALLOC(nsyms*sizeof(char *));
1610 if (symbol_name == 0) no_space();
1611 symbol_value = (short *) MALLOC(nsyms*sizeof(short));
1612 if (symbol_value == 0) no_space();
1613 symbol_prec = (short *) MALLOC(nsyms*sizeof(short));
1614 if (symbol_prec == 0) no_space();
1615 symbol_assoc = MALLOC(nsyms);
1616 if (symbol_assoc == 0) no_space();
1617 symbol_tag = (char **) MALLOC(nsyms*sizeof(char *));
1618 if (symbol_tag == 0) no_space();
1619 symbol_true_token = (char *) MALLOC(nsyms*sizeof(char));
1620 if (symbol_true_token == 0) no_space();
1621
1622 v = (bucket **) MALLOC(nsyms*sizeof(bucket *));
1623 if (v == 0) no_space();
1624
1625 v[0] = 0;
1626 v[start_symbol] = 0;
1627
1628 i = 1;
1629 j = start_symbol + 1;
1630 for (bp = first_symbol; bp; bp = bp->next)
1631 {
1632 if (bp->class == TERM)
1633 v[i++] = bp;
1634 else
1635 v[j++] = bp;
1636 }
1637 assert(i == ntokens && j == nsyms);
1638
1639 for (i = 1; i < ntokens; ++i)
1640 v[i]->index = i;
1641
1642 goal->index = start_symbol + 1;
1643 k = start_symbol + 2;
1644 while (++i < nsyms)
1645 if (v[i] != goal)
1646 {
1647 v[i]->index = k;
1648 ++k;
1649 }
1650
1651 goal->value = 0;
1652 k = 1;
1653 for (i = start_symbol + 1; i < nsyms; ++i)
1654 {
1655 if (v[i] != goal)
1656 {
1657 v[i]->value = k;
1658 ++k;
1659 }
1660 }
1661
1662 k = 0;
1663 for (i = 1; i < ntokens; ++i)
1664 {
1665 n = v[i]->value;
1666 if (n > 256)
1667 {
1668 for (j = k++; j > 0 && symbol_value[j-1] > n; --j)
1669 symbol_value[j] = symbol_value[j-1];
1670 symbol_value[j] = n;
1671 }
1672 }
1673
1674 if (v[1]->value == UNDEFINED)
1675 v[1]->value = 256;
1676
1677 j = 0;
1678 n = 257;
1679 for (i = 2; i < ntokens; ++i)
1680 {
1681 if (v[i]->value == UNDEFINED)
1682 {
1683 while (j < k && n == symbol_value[j])
1684 {
1685 while (++j < k && n == symbol_value[j]) continue;
1686 ++n;
1687 }
1688 v[i]->value = n;
1689 ++n;
1690 }
1691 }
1692
1693 symbol_name[0] = name_pool + 8;
1694 symbol_value[0] = 0;
1695 symbol_prec[0] = 0;
1696 symbol_assoc[0] = TOKEN;
1697 symbol_tag[0] = "";
1698 symbol_true_token[0] = 0;
1699 for (i = 1; i < ntokens; ++i)
1700 {
1701 symbol_name[i] = v[i]->name;
1702 symbol_value[i] = v[i]->value;
1703 symbol_prec[i] = v[i]->prec;
1704 symbol_assoc[i] = v[i]->assoc;
1705 symbol_tag[i] = v[i]->tag;
1706 symbol_true_token[i] = v[i]->true_token;
1707 }
1708 symbol_name[start_symbol] = name_pool;
1709 symbol_value[start_symbol] = -1;
1710 symbol_prec[start_symbol] = 0;
1711 symbol_assoc[start_symbol] = TOKEN;
1712 symbol_tag[start_symbol] = "";
1713 symbol_true_token[start_symbol] = 0;
1714 for (++i; i < nsyms; ++i)
1715 {
1716 k = v[i]->index;
1717 symbol_name[k] = v[i]->name;
1718 symbol_value[k] = v[i]->value;
1719 symbol_prec[k] = v[i]->prec;
1720 symbol_assoc[k] = v[i]->assoc;
1721 symbol_tag[i] = v[i]->tag;
1722 symbol_true_token[i] = v[i]->true_token;
1723 }
1724
1725 FREE(v);
1726 }
1727
1728 static unsigned char caml_ident_start[32] =
1729 "\000\000\000\000\000\000\000\000\376\377\377\207\376\377\377\007\000\000\000\000\000\000\000\000\377\377\177\377\377\377\177\377";
1730 static unsigned char caml_ident_body[32] =
1731 "\000\000\000\000\200\000\377\003\376\377\377\207\376\377\377\007\000\000\000\000\000\000\000\000\377\377\177\377\377\377\177\377";
1732
1733 #define In_bitmap(bm,c) (bm[(unsigned char)(c) >> 3] & (1 << ((c) & 7)))
1734
is_polymorphic(char * s)1735 static int is_polymorphic(char * s)
1736 {
1737 while (*s != 0) {
1738 char c = *s++;
1739 if (c == '\'' || c == '#') return 1;
1740 if (c == '[') {
1741 c = *s;
1742 while (c == ' ' || c == '\t' || c == '\r' || c == '\n') c = *++s;
1743 if (c == '<' || c == '>') return 1;
1744 }
1745 if (In_bitmap(caml_ident_start, c)) {
1746 while (In_bitmap(caml_ident_body, *s)) s++;
1747 }
1748 }
1749 return 0;
1750 }
1751
make_goal(void)1752 void make_goal(void)
1753 {
1754 static char name[7] = "'\\xxx'";
1755 bucket * bp;
1756 bucket * bc;
1757
1758 goal = lookup("%entry%");
1759 ntotalrules = nrules - 2;
1760 for(bp = first_symbol; bp != 0; bp = bp->next) {
1761 if (bp->entry) {
1762 start_rule(goal, 0);
1763 if (nitems + 2> maxitems)
1764 expand_items();
1765 name[2] = '0' + ((bp->entry >> 6) & 7);
1766 name[3] = '0' + ((bp->entry >> 3) & 7);
1767 name[4] = '0' + (bp->entry & 7);
1768 bc = lookup(name);
1769 bc->class = TERM;
1770 bc->value = (unsigned char) bp->entry;
1771 pitem[nitems++] = bc;
1772 pitem[nitems++] = bp;
1773 if (bp->tag == NULL)
1774 entry_without_type(bp->name);
1775 if (is_polymorphic(bp->tag))
1776 polymorphic_entry_point(bp->name);
1777 fprintf(entry_file,
1778 "let %s (lexfun : Lexing.lexbuf -> token) (lexbuf : Lexing.lexbuf) =\n (Parsing.yyparse yytables %d lexfun lexbuf : %s)\n",
1779 bp->name, bp->entry, bp->tag);
1780 fprintf(interface_file,
1781 "val %s :\n (Lexing.lexbuf -> token) -> Lexing.lexbuf -> %s\n",
1782 bp->name,
1783 bp->tag);
1784 fprintf(action_file,
1785 "(* Entry %s *)\n", bp->name);
1786 if (sflag)
1787 fprintf(action_file,
1788 "yyact.(%d) <- (fun __caml_parser_env -> raise "
1789 "(Parsing.YYexit (Parsing.peek_val __caml_parser_env 0)))\n",
1790 ntotalrules);
1791 else
1792 fprintf(action_file,
1793 "; (fun __caml_parser_env -> raise "
1794 "(Parsing.YYexit (Parsing.peek_val __caml_parser_env 0)))\n");
1795 ntotalrules++;
1796 last_was_action = 1;
1797 end_rule();
1798 }
1799 }
1800 }
1801
pack_grammar(void)1802 void pack_grammar(void)
1803 {
1804 register int i, j;
1805 int assoc, prec;
1806
1807 ritem = (short *) MALLOC(nitems*sizeof(short));
1808 if (ritem == 0) no_space();
1809 rlhs = (short *) MALLOC(nrules*sizeof(short));
1810 if (rlhs == 0) no_space();
1811 rrhs = (short *) MALLOC((nrules+1)*sizeof(short));
1812 if (rrhs == 0) no_space();
1813 rprec = (short *) REALLOC(rprec, nrules*sizeof(short));
1814 if (rprec == 0) no_space();
1815 rassoc = REALLOC(rassoc, nrules);
1816 if (rassoc == 0) no_space();
1817
1818 ritem[0] = -1;
1819 ritem[1] = goal->index;
1820 ritem[2] = 0;
1821 ritem[3] = -2;
1822 rlhs[0] = 0;
1823 rlhs[1] = 0;
1824 rlhs[2] = start_symbol;
1825 rrhs[0] = 0;
1826 rrhs[1] = 0;
1827 rrhs[2] = 1;
1828
1829 j = 4;
1830 for (i = 3; i < nrules; ++i)
1831 {
1832 rlhs[i] = plhs[i]->index;
1833 rrhs[i] = j;
1834 assoc = TOKEN;
1835 prec = 0;
1836 while (pitem[j])
1837 {
1838 ritem[j] = pitem[j]->index;
1839 if (pitem[j]->class == TERM)
1840 {
1841 prec = pitem[j]->prec;
1842 assoc = pitem[j]->assoc;
1843 }
1844 ++j;
1845 }
1846 ritem[j] = -i;
1847 ++j;
1848 if (rprec[i] == UNDEFINED)
1849 {
1850 rprec[i] = prec;
1851 rassoc[i] = assoc;
1852 }
1853 }
1854 rrhs[i] = j;
1855
1856 FREE(plhs);
1857 FREE(pitem);
1858 }
1859
1860
print_grammar(void)1861 void print_grammar(void)
1862 {
1863 register int i, j, k;
1864 int spacing = 0;
1865 register FILE *f = verbose_file;
1866
1867 if (!vflag) return;
1868
1869 k = 1;
1870 for (i = 2; i < nrules; ++i)
1871 {
1872 if (rlhs[i] != rlhs[i-1])
1873 {
1874 if (i != 2) fprintf(f, "\n");
1875 fprintf(f, "%4d %s :", i - 2, symbol_name[rlhs[i]]);
1876 spacing = strlen(symbol_name[rlhs[i]]) + 1;
1877 }
1878 else
1879 {
1880 fprintf(f, "%4d ", i - 2);
1881 j = spacing;
1882 while (--j >= 0) putc(' ', f);
1883 putc('|', f);
1884 }
1885
1886 while (ritem[k] >= 0)
1887 {
1888 fprintf(f, " %s", symbol_name[ritem[k]]);
1889 ++k;
1890 }
1891 ++k;
1892 putc('\n', f);
1893 }
1894 }
1895
1896
reader(void)1897 void reader(void)
1898 {
1899 virtual_input_file_name = substring (input_file_name, 0,
1900 strlen (input_file_name));
1901 create_symbol_table();
1902 read_declarations();
1903 output_token_type();
1904 read_grammar();
1905 make_goal();
1906 free_symbol_table();
1907 free_tags();
1908 pack_names();
1909 check_symbols();
1910 pack_symbols();
1911 pack_grammar();
1912 free_symbols();
1913 print_grammar();
1914 }
1915