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 "defs.h"
19 
20 typedef
21   struct shorts
22     {
23       struct shorts *next;
24       short value;
25     }
26   shorts;
27 
28 int tokensetsize;
29 short *lookaheads;
30 short *LAruleno;
31 unsigned *LA;
32 short *accessing_symbol;
33 core **state_table;
34 shifts **shift_table;
35 reductions **reduction_table;
36 short *goto_map;
37 short *from_state;
38 short *to_state;
39 
40 short **transpose(short int **R, int n);
41 
42 static int infinity;
43 static int maxrhs;
44 static int ngotos;
45 static unsigned *F;
46 static short **includes;
47 static shorts **lookback;
48 static short **R;
49 static short *INDEX;
50 static short *VERTICES;
51 static int top;
52 
53 
54 
55 void set_state_table (void);
56 void set_accessing_symbol (void);
57 void set_shift_table (void);
58 void set_reduction_table (void);
59 void set_maxrhs (void);
60 void initialize_LA (void);
61 void set_goto_map (void);
62 void initialize_F (void);
63 void build_relations (void);
64 void compute_FOLLOWS (void);
65 void compute_lookaheads (void);
66 void digraph (short int **relation);
67 void add_lookback_edge (int stateno, int ruleno, int gotono);
68 void traverse (register int i);
69 
lalr(void)70 void lalr(void)
71 {
72     tokensetsize = WORDSIZE(ntokens);
73 
74     set_state_table();
75     set_accessing_symbol();
76     set_shift_table();
77     set_reduction_table();
78     set_maxrhs();
79     initialize_LA();
80     set_goto_map();
81     initialize_F();
82     build_relations();
83     compute_FOLLOWS();
84     compute_lookaheads();
85 }
86 
87 
88 
set_state_table(void)89 void set_state_table(void)
90 {
91     register core *sp;
92 
93     state_table = NEW2(nstates, core *);
94     for (sp = first_state; sp; sp = sp->next)
95         state_table[sp->number] = sp;
96 }
97 
98 
99 
set_accessing_symbol(void)100 void set_accessing_symbol(void)
101 {
102     register core *sp;
103 
104     accessing_symbol = NEW2(nstates, short);
105     for (sp = first_state; sp; sp = sp->next)
106         accessing_symbol[sp->number] = sp->accessing_symbol;
107 }
108 
109 
110 
set_shift_table(void)111 void set_shift_table(void)
112 {
113     register shifts *sp;
114 
115     shift_table = NEW2(nstates, shifts *);
116     for (sp = first_shift; sp; sp = sp->next)
117         shift_table[sp->number] = sp;
118 }
119 
120 
121 
set_reduction_table(void)122 void set_reduction_table(void)
123 {
124     register reductions *rp;
125 
126     reduction_table = NEW2(nstates, reductions *);
127     for (rp = first_reduction; rp; rp = rp->next)
128         reduction_table[rp->number] = rp;
129 }
130 
131 
132 
set_maxrhs(void)133 void set_maxrhs(void)
134 {
135   register short *itemp;
136   register short *item_end;
137   register int length;
138   register int max;
139 
140   length = 0;
141   max = 0;
142   item_end = ritem + nitems;
143   for (itemp = ritem; itemp < item_end; itemp++)
144     {
145       if (*itemp >= 0)
146         {
147           length++;
148         }
149       else
150         {
151           if (length > max) max = length;
152           length = 0;
153         }
154     }
155 
156   maxrhs = max;
157 }
158 
159 
160 
initialize_LA(void)161 void initialize_LA(void)
162 {
163   register int i, j, k;
164   register reductions *rp;
165 
166   lookaheads = NEW2(nstates + 1, short);
167 
168   k = 0;
169   for (i = 0; i < nstates; i++)
170     {
171       lookaheads[i] = k;
172       rp = reduction_table[i];
173       if (rp)
174         k += rp->nreds;
175     }
176   lookaheads[nstates] = k;
177 
178   LA = NEW2(k * tokensetsize, unsigned);
179   LAruleno = NEW2(k, short);
180   lookback = NEW2(k, shorts *);
181 
182   k = 0;
183   for (i = 0; i < nstates; i++)
184     {
185       rp = reduction_table[i];
186       if (rp)
187         {
188           for (j = 0; j < rp->nreds; j++)
189             {
190               LAruleno[k] = rp->rules[j];
191               k++;
192             }
193         }
194     }
195 }
196 
197 
set_goto_map(void)198 void set_goto_map(void)
199 {
200   register shifts *sp;
201   register int i;
202   register int symbol;
203   register int k;
204   register short *temp_map;
205   register int state2;
206   register int state1;
207 
208   goto_map = NEW2(nvars + 1, short) - ntokens;
209   temp_map = NEW2(nvars + 1, short) - ntokens;
210 
211   ngotos = 0;
212   for (sp = first_shift; sp; sp = sp->next)
213     {
214       for (i = sp->nshifts - 1; i >= 0; i--)
215         {
216           symbol = accessing_symbol[sp->shift[i]];
217 
218           if (ISTOKEN(symbol)) break;
219 
220           if (ngotos == MAXSHORT)
221             fatal("too many gotos");
222 
223           ngotos++;
224           goto_map[symbol]++;
225         }
226     }
227 
228   k = 0;
229   for (i = ntokens; i < nsyms; i++)
230     {
231       temp_map[i] = k;
232       k += goto_map[i];
233     }
234 
235   for (i = ntokens; i < nsyms; i++)
236     goto_map[i] = temp_map[i];
237 
238   goto_map[nsyms] = ngotos;
239   temp_map[nsyms] = ngotos;
240 
241   from_state = NEW2(ngotos, short);
242   to_state = NEW2(ngotos, short);
243 
244   for (sp = first_shift; sp; sp = sp->next)
245     {
246       state1 = sp->number;
247       for (i = sp->nshifts - 1; i >= 0; i--)
248         {
249           state2 = sp->shift[i];
250           symbol = accessing_symbol[state2];
251 
252           if (ISTOKEN(symbol)) break;
253 
254           k = temp_map[symbol]++;
255           from_state[k] = state1;
256           to_state[k] = state2;
257         }
258     }
259 
260   FREE(temp_map + ntokens);
261 }
262 
263 
264 
265 /*  Map_goto maps a state/symbol pair into its numeric representation.        */
266 
267 int
map_goto(int state,int symbol)268 map_goto(int state, int symbol)
269 {
270     register int high;
271     register int low;
272     register int middle;
273     register int s;
274 
275     low = goto_map[symbol];
276     high = goto_map[symbol + 1];
277 
278     for (;;)
279     {
280         assert(low <= high);
281         middle = (low + high) >> 1;
282         s = from_state[middle];
283         if (s == state)
284             return (middle);
285         else if (s < state)
286             low = middle + 1;
287         else
288             high = middle - 1;
289     }
290 }
291 
292 
293 
initialize_F(void)294 void initialize_F(void)
295 {
296   register int i;
297   register int j;
298   register int k;
299   register shifts *sp;
300   register short *edge;
301   register unsigned *rowp;
302   register short *rp;
303   register short **reads;
304   register int nedges;
305   register int stateno;
306   register int symbol;
307   register int nwords;
308 
309   nwords = ngotos * tokensetsize;
310   F = NEW2(nwords, unsigned);
311 
312   reads = NEW2(ngotos, short *);
313   edge = NEW2(ngotos + 1, short);
314   nedges = 0;
315 
316   rowp = F;
317   for (i = 0; i < ngotos; i++)
318     {
319       stateno = to_state[i];
320       sp = shift_table[stateno];
321 
322       if (sp)
323         {
324           k = sp->nshifts;
325 
326           for (j = 0; j < k; j++)
327             {
328               symbol = accessing_symbol[sp->shift[j]];
329               if (ISVAR(symbol))
330                 break;
331               SETBIT(rowp, symbol);
332             }
333 
334           for (; j < k; j++)
335             {
336               symbol = accessing_symbol[sp->shift[j]];
337               if (nullable[symbol])
338                 edge[nedges++] = map_goto(stateno, symbol);
339             }
340 
341           if (nedges)
342             {
343               reads[i] = rp = NEW2(nedges + 1, short);
344 
345               for (j = 0; j < nedges; j++)
346                 rp[j] = edge[j];
347 
348               rp[nedges] = -1;
349               nedges = 0;
350             }
351         }
352 
353       rowp += tokensetsize;
354     }
355 
356   SETBIT(F, 0);
357   digraph(reads);
358 
359   for (i = 0; i < ngotos; i++)
360     {
361       if (reads[i])
362         FREE(reads[i]);
363     }
364 
365   FREE(reads);
366   FREE(edge);
367 }
368 
369 
370 
build_relations(void)371 void build_relations(void)
372 {
373   register int i;
374   register int j;
375   register int k;
376   register short *rulep;
377   register short *rp;
378   register shifts *sp;
379   register int length;
380   register int nedges;
381   register int done;
382   register int state1;
383   register int stateno;
384   register int symbol1;
385   register int symbol2;
386   register short *shortp;
387   register short *edge;
388   register short *states;
389   register short **new_includes;
390 
391   includes = NEW2(ngotos, short *);
392   edge = NEW2(ngotos + 1, short);
393   states = NEW2(maxrhs + 1, short);
394 
395   for (i = 0; i < ngotos; i++)
396     {
397       nedges = 0;
398       state1 = from_state[i];
399       symbol1 = accessing_symbol[to_state[i]];
400 
401       for (rulep = derives[symbol1]; *rulep >= 0; rulep++)
402         {
403           length = 1;
404           states[0] = state1;
405           stateno = state1;
406 
407           for (rp = ritem + rrhs[*rulep]; *rp >= 0; rp++)
408             {
409               symbol2 = *rp;
410               sp = shift_table[stateno];
411               k = sp->nshifts;
412 
413               for (j = 0; j < k; j++)
414                 {
415                   stateno = sp->shift[j];
416                   if (accessing_symbol[stateno] == symbol2) break;
417                 }
418 
419               states[length++] = stateno;
420             }
421 
422           add_lookback_edge(stateno, *rulep, i);
423 
424           length--;
425           done = 0;
426           while (!done)
427             {
428               done = 1;
429               rp--;
430               if (ISVAR(*rp))
431                 {
432                   stateno = states[--length];
433                   edge[nedges++] = map_goto(stateno, *rp);
434                   if (nullable[*rp] && length > 0) done = 0;
435                 }
436             }
437         }
438 
439       if (nedges)
440         {
441           includes[i] = shortp = NEW2(nedges + 1, short);
442           for (j = 0; j < nedges; j++)
443             shortp[j] = edge[j];
444           shortp[nedges] = -1;
445         }
446     }
447 
448   new_includes = transpose(includes, ngotos);
449 
450   for (i = 0; i < ngotos; i++)
451     if (includes[i])
452       FREE(includes[i]);
453 
454   FREE(includes);
455 
456   includes = new_includes;
457 
458   FREE(edge);
459   FREE(states);
460 }
461 
462 
add_lookback_edge(int stateno,int ruleno,int gotono)463 void add_lookback_edge(int stateno, int ruleno, int gotono)
464 {
465     register int i, k;
466     register int found;
467     register shorts *sp;
468 
469     i = lookaheads[stateno];
470     k = lookaheads[stateno + 1];
471     found = 0;
472     while (!found && i < k)
473     {
474         if (LAruleno[i] == ruleno)
475             found = 1;
476         else
477             ++i;
478     }
479     assert(found);
480 
481     sp = NEW(shorts);
482     sp->next = lookback[i];
483     sp->value = gotono;
484     lookback[i] = sp;
485 }
486 
487 
488 
489 short **
transpose(short int ** R,int n)490 transpose(short int **R, int n)
491 {
492   register short **new_R;
493   register short **temp_R;
494   register short *nedges;
495   register short *sp;
496   register int i;
497   register int k;
498 
499   nedges = NEW2(n, short);
500 
501   for (i = 0; i < n; i++)
502     {
503       sp = R[i];
504       if (sp)
505         {
506           while (*sp >= 0)
507             nedges[*sp++]++;
508         }
509     }
510 
511   new_R = NEW2(n, short *);
512   temp_R = NEW2(n, short *);
513 
514   for (i = 0; i < n; i++)
515     {
516       k = nedges[i];
517       if (k > 0)
518         {
519           sp = NEW2(k + 1, short);
520           new_R[i] = sp;
521           temp_R[i] = sp;
522           sp[k] = -1;
523         }
524     }
525 
526   FREE(nedges);
527 
528   for (i = 0; i < n; i++)
529     {
530       sp = R[i];
531       if (sp)
532         {
533           while (*sp >= 0)
534             *temp_R[*sp++]++ = i;
535         }
536     }
537 
538   FREE(temp_R);
539 
540   return (new_R);
541 }
542 
543 
544 
compute_FOLLOWS(void)545 void compute_FOLLOWS(void)
546 {
547   digraph(includes);
548 }
549 
550 
compute_lookaheads(void)551 void compute_lookaheads(void)
552 {
553   register int i, n;
554   register unsigned *fp1, *fp2, *fp3;
555   register shorts *sp, *next;
556   register unsigned *rowp;
557 
558   rowp = LA;
559   n = lookaheads[nstates];
560   for (i = 0; i < n; i++)
561     {
562       fp3 = rowp + tokensetsize;
563       for (sp = lookback[i]; sp; sp = sp->next)
564         {
565           fp1 = rowp;
566           fp2 = F + tokensetsize * sp->value;
567           while (fp1 < fp3)
568             *fp1++ |= *fp2++;
569         }
570       rowp = fp3;
571     }
572 
573   for (i = 0; i < n; i++)
574     for (sp = lookback[i]; sp; sp = next)
575       {
576         next = sp->next;
577         FREE(sp);
578       }
579 
580   FREE(lookback);
581   FREE(F);
582 }
583 
584 
digraph(short int ** relation)585 void digraph(short int **relation)
586 {
587   register int i;
588 
589   infinity = ngotos + 2;
590   INDEX = NEW2(ngotos + 1, short);
591   VERTICES = NEW2(ngotos + 1, short);
592   top = 0;
593 
594   R = relation;
595 
596   for (i = 0; i < ngotos; i++)
597     INDEX[i] = 0;
598 
599   for (i = 0; i < ngotos; i++)
600     {
601       if (INDEX[i] == 0 && R[i])
602         traverse(i);
603     }
604 
605   FREE(INDEX);
606   FREE(VERTICES);
607 }
608 
609 
610 
traverse(register int i)611 void traverse(register int i)
612 {
613   register unsigned *fp1;
614   register unsigned *fp2;
615   register unsigned *fp3;
616   register int j;
617   register short *rp;
618 
619   int height;
620   unsigned *base;
621 
622   VERTICES[++top] = i;
623   INDEX[i] = height = top;
624 
625   base = F + i * tokensetsize;
626   fp3 = base + tokensetsize;
627 
628   rp = R[i];
629   if (rp)
630     {
631       while ((j = *rp++) >= 0)
632         {
633           if (INDEX[j] == 0)
634             traverse(j);
635 
636           if (INDEX[i] > INDEX[j])
637             INDEX[i] = INDEX[j];
638 
639           fp1 = base;
640           fp2 = F + j * tokensetsize;
641 
642           while (fp1 < fp3)
643             *fp1++ |= *fp2++;
644         }
645     }
646 
647   if (INDEX[i] == height)
648     {
649       for (;;)
650         {
651           j = VERTICES[top--];
652           INDEX[j] = infinity;
653 
654           if (i == j)
655             break;
656 
657           fp1 = base;
658           fp2 = F + j * tokensetsize;
659 
660           while (fp1 < fp3)
661             *fp2++ = *fp1++;
662         }
663     }
664 }
665