]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/yacc/mkpar.c
Inital import
[l4.git] / l4 / pkg / ocaml / contrib / yacc / mkpar.c
1 /***********************************************************************/
2 /*                                                                     */
3 /*                           Objective Caml                            */
4 /*                                                                     */
5 /*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         */
6 /*                                                                     */
7 /*  Copyright 1996 Institut National de Recherche en Informatique et   */
8 /*  en Automatique.  All rights reserved.  This file is distributed    */
9 /*  under the terms of the Q Public License version 1.0.               */
10 /*                                                                     */
11 /***********************************************************************/
12
13 /* Based on public-domain code from Berkeley Yacc */
14
15 /* $Id: mkpar.c 3573 2001-07-12 12:54:24Z doligez $ */
16
17
18 #include "defs.h"
19
20 action **parser;
21 int SRtotal;
22 int RRtotal;
23 short *SRconflicts;
24 short *RRconflicts;
25 short *defred;
26 short *rules_used;
27 short nunused;
28 short final_state;
29
30 static int SRcount;
31 static int RRcount;
32
33 void find_final_state (void);
34 void remove_conflicts (void);
35 void unused_rules (void);
36 void total_conflicts (void);
37 void defreds (void);
38
39 void make_parser(void)
40 {
41     register int i;
42
43     parser = NEW2(nstates, action *);
44     for (i = 0; i < nstates; i++)
45         parser[i] = parse_actions(i);
46
47     find_final_state();
48     remove_conflicts();
49     unused_rules();
50     if (SRtotal + RRtotal > 0) total_conflicts();
51     defreds();
52 }
53
54
55 action *
56 parse_actions(register int stateno)
57 {
58     register action *actions;
59
60     actions = get_shifts(stateno);
61     actions = add_reductions(stateno, actions);
62     return (actions);
63 }
64
65
66 action *
67 get_shifts(int stateno)
68 {
69     register action *actions, *temp;
70     register shifts *sp;
71     register short *to_state;
72     register int i, k;
73     register int symbol;
74
75     actions = 0;
76     sp = shift_table[stateno];
77     if (sp)
78     {
79         to_state = sp->shift;
80         for (i = sp->nshifts - 1; i >= 0; i--)
81         {
82             k = to_state[i];
83             symbol = accessing_symbol[k];
84             if (ISTOKEN(symbol))
85             {
86                 temp = NEW(action);
87                 temp->next = actions;
88                 temp->symbol = symbol;
89                 temp->number = k;
90                 temp->prec = symbol_prec[symbol];
91                 temp->action_code = SHIFT;
92                 temp->assoc = symbol_assoc[symbol];
93                 actions = temp;
94             }
95         }
96     }
97     return (actions);
98 }
99
100 action *
101 add_reductions(int stateno, register action *actions)
102 {
103     register int i, j, m, n;
104     register int ruleno, tokensetsize;
105     register unsigned *rowp;
106
107     tokensetsize = WORDSIZE(ntokens);
108     m = lookaheads[stateno];
109     n = lookaheads[stateno + 1];
110     for (i = m; i < n; i++)
111     {
112         ruleno = LAruleno[i];
113         rowp = LA + i * tokensetsize;
114         for (j = ntokens - 1; j >= 0; j--)
115         {
116             if (BIT(rowp, j))
117                 actions = add_reduce(actions, ruleno, j);
118         }
119     }
120     return (actions);
121 }
122
123
124 action *
125 add_reduce(register action *actions, register int ruleno, register int symbol)
126 {
127     register action *temp, *prev, *next;
128
129     prev = 0;
130     for (next = actions; next && next->symbol < symbol; next = next->next)
131         prev = next;
132
133     while (next && next->symbol == symbol && next->action_code == SHIFT)
134     {
135         prev = next;
136         next = next->next;
137     }
138
139     while (next && next->symbol == symbol &&
140             next->action_code == REDUCE && next->number < ruleno)
141     {
142         prev = next;
143         next = next->next;
144     }
145
146     temp = NEW(action);
147     temp->next = next;
148     temp->symbol = symbol;
149     temp->number = ruleno;
150     temp->prec = rprec[ruleno];
151     temp->action_code = REDUCE;
152     temp->assoc = rassoc[ruleno];
153
154     if (prev)
155         prev->next = temp;
156     else
157         actions = temp;
158
159     return (actions);
160 }
161
162
163 void find_final_state(void)
164 {
165     register int goal, i;
166     register short *to_state;
167     register shifts *p;
168
169     p = shift_table[0];
170     to_state = p->shift;
171     goal = ritem[1];
172     for (i = p->nshifts - 1; i >= 0; --i)
173     {
174         final_state = to_state[i];
175         if (accessing_symbol[final_state] == goal) break;
176     }
177 }
178
179
180 void unused_rules(void)
181 {
182     register int i;
183     register action *p;
184
185     rules_used = (short *) MALLOC(nrules*sizeof(short));
186     if (rules_used == 0) no_space();
187
188     for (i = 0; i < nrules; ++i)
189         rules_used[i] = 0;
190
191     for (i = 0; i < nstates; ++i)
192     {
193         for (p = parser[i]; p; p = p->next)
194         {
195             if (p->action_code == REDUCE && p->suppressed == 0)
196                 rules_used[p->number] = 1;
197         }
198     }
199
200     nunused = 0;
201     for (i = 3; i < nrules; ++i)
202         if (!rules_used[i]) ++nunused;
203
204     if (nunused){
205         if (nunused == 1)
206             fprintf(stderr, "1 rule never reduced\n");
207         else
208             fprintf(stderr, "%d rules never reduced\n", nunused);
209     }
210 }
211
212
213 void remove_conflicts(void)
214 {
215     register int i;
216     register int symbol;
217     register action *p, *pref;
218
219     SRtotal = 0;
220     RRtotal = 0;
221     SRconflicts = NEW2(nstates, short);
222     RRconflicts = NEW2(nstates, short);
223     pref = NULL;
224     for (i = 0; i < nstates; i++)
225     {
226         SRcount = 0;
227         RRcount = 0;
228         symbol = -1;
229         for (p = parser[i]; p; p = p->next)
230         {
231             if (p->symbol != symbol)
232             {
233                 pref = p;
234                 symbol = p->symbol;
235             }
236             else if (i == final_state && symbol == 0)
237             {
238                 SRcount++;
239                 p->suppressed = 1;
240             }
241             else if (pref->action_code == SHIFT)
242             {
243                 if (pref->prec > 0 && p->prec > 0)
244                 {
245                     if (pref->prec < p->prec)
246                     {
247                         pref->suppressed = 2;
248                         pref = p;
249                     }
250                     else if (pref->prec > p->prec)
251                     {
252                         p->suppressed = 2;
253                     }
254                     else if (pref->assoc == LEFT)
255                     {
256                         pref->suppressed = 2;
257                         pref = p;
258                     }
259                     else if (pref->assoc == RIGHT)
260                     {
261                         p->suppressed = 2;
262                     }
263                     else
264                     {
265                         pref->suppressed = 2;
266                         p->suppressed = 2;
267                     }
268                 }
269                 else
270                 {
271                     SRcount++;
272                     p->suppressed = 1;
273                 }
274             }
275             else
276             {
277                 RRcount++;
278                 p->suppressed = 1;
279             }
280         }
281         SRtotal += SRcount;
282         RRtotal += RRcount;
283         SRconflicts[i] = SRcount;
284         RRconflicts[i] = RRcount;
285     }
286 }
287
288
289 void total_conflicts(void)
290 {
291     if (SRtotal == 1)
292         fprintf(stderr, "1 shift/reduce conflict");
293     else if (SRtotal > 1)
294         fprintf(stderr, "%d shift/reduce conflicts", SRtotal);
295
296     if (SRtotal && RRtotal)
297         fprintf(stderr, ", ");
298
299     if (RRtotal == 1)
300         fprintf(stderr, "1 reduce/reduce conflict");
301     else if (RRtotal > 1)
302         fprintf(stderr, "%d reduce/reduce conflicts", RRtotal);
303
304     fprintf(stderr, ".\n");
305 }
306
307
308 int
309 sole_reduction(int stateno)
310 {
311     register int count, ruleno;
312     register action *p;
313
314     count = 0;
315     ruleno = 0; 
316     for (p = parser[stateno]; p; p = p->next)
317     {
318         if (p->action_code == SHIFT && p->suppressed == 0)
319             return (0);
320         else if (p->action_code == REDUCE && p->suppressed == 0)
321         {
322             if (ruleno > 0 && p->number != ruleno)
323                 return (0);
324             if (p->symbol != 1)
325                 ++count;
326             ruleno = p->number;
327         }
328     }
329
330     if (count == 0)
331         return (0);
332     return (ruleno);
333 }
334
335
336 void defreds(void)
337 {
338     register int i;
339
340     defred = NEW2(nstates, short);
341     for (i = 0; i < nstates; i++)
342         defred[i] = sole_reduction(i);
343 }
344  
345 void free_action_row(register action *p)
346 {
347   register action *q;
348
349   while (p)
350     {
351       q = p->next;
352       FREE(p);
353       p = q;
354     }
355 }
356
357 void free_parser(void)
358 {
359   register int i;
360
361   for (i = 0; i < nstates; i++)
362     free_action_row(parser[i]);
363
364   FREE(parser);
365 }
366