xref: /csrg-svn/old/lex/sub2.c (revision 14494)
1*14494Ssam #ifndef lint
2*14494Ssam static char sccsid[] = "@(#)sub2.c	4.1 (Berkeley) 08/11/83";
3*14494Ssam #endif
4*14494Ssam 
5*14494Ssam # include "ldefs.c"
6*14494Ssam cfoll(v)
7*14494Ssam 	int v;
8*14494Ssam 	{
9*14494Ssam 	register int i,j,k;
10*14494Ssam 	char *p;
11*14494Ssam 	i = name[v];
12*14494Ssam 	if(i < NCH) i = 1;	/* character */
13*14494Ssam 	switch(i){
14*14494Ssam 		case 1: case RSTR: case RCCL: case RNCCL: case RNULLS:
15*14494Ssam 			for(j=0;j<tptr;j++)
16*14494Ssam 				tmpstat[j] = FALSE;
17*14494Ssam 			count = 0;
18*14494Ssam 			follow(v);
19*14494Ssam # ifdef PP
20*14494Ssam 			padd(foll,v);		/* packing version */
21*14494Ssam # endif
22*14494Ssam # ifndef PP
23*14494Ssam 			add(foll,v);		/* no packing version */
24*14494Ssam # endif
25*14494Ssam 			if(i == RSTR) cfoll(left[v]);
26*14494Ssam 			else if(i == RCCL || i == RNCCL){	/* compress ccl list */
27*14494Ssam 				for(j=1; j<NCH;j++)
28*14494Ssam 					symbol[j] = (i==RNCCL);
29*14494Ssam 				p = left[v];
30*14494Ssam 				while(*p)
31*14494Ssam 					symbol[*p++] = (i == RCCL);
32*14494Ssam 				p = pcptr;
33*14494Ssam 				for(j=1;j<NCH;j++)
34*14494Ssam 					if(symbol[j]){
35*14494Ssam 						for(k=0;p+k < pcptr; k++)
36*14494Ssam 							if(cindex[j] == *(p+k))
37*14494Ssam 								break;
38*14494Ssam 						if(p+k >= pcptr)*pcptr++ = cindex[j];
39*14494Ssam 						}
40*14494Ssam 				*pcptr++ = 0;
41*14494Ssam 				if(pcptr > pchar + pchlen)
42*14494Ssam 					error("Too many packed character classes");
43*14494Ssam 				left[v] = p;
44*14494Ssam 				name[v] = RCCL;	/* RNCCL eliminated */
45*14494Ssam # ifdef DEBUG
46*14494Ssam 				if(debug && *p){
47*14494Ssam 					printf("ccl %d: %d",v,*p++);
48*14494Ssam 					while(*p)
49*14494Ssam 						printf(", %d",*p++);
50*14494Ssam 					putchar('\n');
51*14494Ssam 					}
52*14494Ssam # endif
53*14494Ssam 				}
54*14494Ssam 			break;
55*14494Ssam 		case CARAT:
56*14494Ssam 			cfoll(left[v]);
57*14494Ssam 			break;
58*14494Ssam 		case STAR: case PLUS: case QUEST: case RSCON:
59*14494Ssam 			cfoll(left[v]);
60*14494Ssam 			break;
61*14494Ssam 		case BAR: case RCAT: case DIV: case RNEWE:
62*14494Ssam 			cfoll(left[v]);
63*14494Ssam 			cfoll(right[v]);
64*14494Ssam 			break;
65*14494Ssam # ifdef DEBUG
66*14494Ssam 		case FINAL:
67*14494Ssam 		case S1FINAL:
68*14494Ssam 		case S2FINAL:
69*14494Ssam 			break;
70*14494Ssam 		default:
71*14494Ssam 			warning("bad switch cfoll %d",v);
72*14494Ssam # endif
73*14494Ssam 		}
74*14494Ssam 	return;
75*14494Ssam 	}
76*14494Ssam # ifdef DEBUG
77*14494Ssam pfoll()
78*14494Ssam 	{
79*14494Ssam 	register int i,k,*p;
80*14494Ssam 	int j;
81*14494Ssam 	/* print sets of chars which may follow positions */
82*14494Ssam 	printf("pos\tchars\n");
83*14494Ssam 	for(i=0;i<tptr;i++)
84*14494Ssam 		if(p=foll[i]){
85*14494Ssam 			j = *p++;
86*14494Ssam 			if(j >= 1){
87*14494Ssam 				printf("%d:\t%d",i,*p++);
88*14494Ssam 				for(k=2;k<=j;k++)
89*14494Ssam 					printf(", %d",*p++);
90*14494Ssam 				putchar('\n');
91*14494Ssam 				}
92*14494Ssam 			}
93*14494Ssam 	return;
94*14494Ssam 	}
95*14494Ssam # endif
96*14494Ssam add(array,n)
97*14494Ssam   int **array;
98*14494Ssam   int n; {
99*14494Ssam 	register int i, *temp;
100*14494Ssam 	register char *ctemp;
101*14494Ssam 	temp = nxtpos;
102*14494Ssam 	ctemp = tmpstat;
103*14494Ssam 	array[n] = nxtpos;		/* note no packing is done in positions */
104*14494Ssam 	*temp++ = count;
105*14494Ssam 	for(i=0;i<tptr;i++)
106*14494Ssam 		if(ctemp[i] == TRUE)
107*14494Ssam 			*temp++ = i;
108*14494Ssam 	nxtpos = temp;
109*14494Ssam 	if(nxtpos >= positions+maxpos)
110*14494Ssam 		error("Too many positions %s",(maxpos== MAXPOS?"\nTry using %p num":""));
111*14494Ssam 	return;
112*14494Ssam 	}
113*14494Ssam follow(v)
114*14494Ssam   int v;
115*14494Ssam 	{
116*14494Ssam 	register int p;
117*14494Ssam 	if(v >= tptr-1)return;
118*14494Ssam 	p = parent[v];
119*14494Ssam 	if(p == 0) return;
120*14494Ssam 	switch(name[p]){
121*14494Ssam 			/* will not be CHAR RNULLS FINAL S1FINAL S2FINAL RCCL RNCCL */
122*14494Ssam 		case RSTR:
123*14494Ssam 			if(tmpstat[p] == FALSE){
124*14494Ssam 				count++;
125*14494Ssam 				tmpstat[p] = TRUE;
126*14494Ssam 				}
127*14494Ssam 			break;
128*14494Ssam 		case STAR: case PLUS:
129*14494Ssam 			first(v);
130*14494Ssam 			follow(p);
131*14494Ssam 			break;
132*14494Ssam 		case BAR: case QUEST: case RNEWE:
133*14494Ssam 			follow(p);
134*14494Ssam 			break;
135*14494Ssam 		case RCAT: case DIV:
136*14494Ssam 			if(v == left[p]){
137*14494Ssam 				if(nullstr[right[p]])
138*14494Ssam 					follow(p);
139*14494Ssam 				first(right[p]);
140*14494Ssam 				}
141*14494Ssam 			else follow(p);
142*14494Ssam 			break;
143*14494Ssam 		case RSCON: case CARAT:
144*14494Ssam 			follow(p);
145*14494Ssam 			break;
146*14494Ssam # ifdef DEBUG
147*14494Ssam 		default:
148*14494Ssam 			warning("bad switch follow %d",p);
149*14494Ssam # endif
150*14494Ssam 		}
151*14494Ssam 	return;
152*14494Ssam 	}
153*14494Ssam first(v)	/* calculate set of positions with v as root which can be active initially */
154*14494Ssam   int v; {
155*14494Ssam 	register int i;
156*14494Ssam 	register char *p;
157*14494Ssam 	i = name[v];
158*14494Ssam 	if(i < NCH)i = 1;
159*14494Ssam 	switch(i){
160*14494Ssam 		case 1: case RCCL: case RNCCL: case RNULLS: case FINAL: case S1FINAL: case S2FINAL:
161*14494Ssam 			if(tmpstat[v] == FALSE){
162*14494Ssam 				count++;
163*14494Ssam 				tmpstat[v] = TRUE;
164*14494Ssam 				}
165*14494Ssam 			break;
166*14494Ssam 		case BAR: case RNEWE:
167*14494Ssam 			first(left[v]);
168*14494Ssam 			first(right[v]);
169*14494Ssam 			break;
170*14494Ssam 		case CARAT:
171*14494Ssam 			if(stnum % 2 == 1)
172*14494Ssam 				first(left[v]);
173*14494Ssam 			break;
174*14494Ssam 		case RSCON:
175*14494Ssam 			i = stnum/2 +1;
176*14494Ssam 			p = right[v];
177*14494Ssam 			while(*p)
178*14494Ssam 				if(*p++ == i){
179*14494Ssam 					first(left[v]);
180*14494Ssam 					break;
181*14494Ssam 					}
182*14494Ssam 			break;
183*14494Ssam 		case STAR: case QUEST: case PLUS:  case RSTR:
184*14494Ssam 			first(left[v]);
185*14494Ssam 			break;
186*14494Ssam 		case RCAT: case DIV:
187*14494Ssam 			first(left[v]);
188*14494Ssam 			if(nullstr[left[v]])
189*14494Ssam 				first(right[v]);
190*14494Ssam 			break;
191*14494Ssam # ifdef DEBUG
192*14494Ssam 		default:
193*14494Ssam 			warning("bad switch first %d",v);
194*14494Ssam # endif
195*14494Ssam 		}
196*14494Ssam 	return;
197*14494Ssam 	}
198*14494Ssam cgoto(){
199*14494Ssam 	register int i, j, s;
200*14494Ssam 	int npos, curpos, n;
201*14494Ssam 	int tryit;
202*14494Ssam 	char tch[NCH];
203*14494Ssam 	int tst[NCH];
204*14494Ssam 	char *q;
205*14494Ssam 	/* generate initial state, for each start condition */
206*14494Ssam 	if(ratfor){
207*14494Ssam 		fprintf(fout,"blockdata\n");
208*14494Ssam 		fprintf(fout,"common /Lvstop/ vstop\n");
209*14494Ssam 		fprintf(fout,"define Svstop %d\n",nstates+1);
210*14494Ssam 		fprintf(fout,"integer vstop(Svstop)\n");
211*14494Ssam 		}
212*14494Ssam 	else fprintf(fout,"int yyvstop[] ={\n0,\n");
213*14494Ssam 	while(stnum < 2 || stnum/2 < sptr){
214*14494Ssam 		for(i = 0; i<tptr; i++) tmpstat[i] = 0;
215*14494Ssam 		count = 0;
216*14494Ssam 		if(tptr > 0)first(tptr-1);
217*14494Ssam 		add(state,stnum);
218*14494Ssam # ifdef DEBUG
219*14494Ssam 		if(debug){
220*14494Ssam 			if(stnum > 1)
221*14494Ssam 				printf("%s:\n",sname[stnum/2]);
222*14494Ssam 			pstate(stnum);
223*14494Ssam 			}
224*14494Ssam # endif
225*14494Ssam 		stnum++;
226*14494Ssam 		}
227*14494Ssam 	stnum--;
228*14494Ssam 	/* even stnum = might not be at line begin */
229*14494Ssam 	/* odd stnum  = must be at line begin */
230*14494Ssam 	/* even states can occur anywhere, odd states only at line begin */
231*14494Ssam 	for(s = 0; s <= stnum; s++){
232*14494Ssam 		tryit = FALSE;
233*14494Ssam 		cpackflg[s] = FALSE;
234*14494Ssam 		sfall[s] = -1;
235*14494Ssam 		acompute(s);
236*14494Ssam 		for(i=0;i<NCH;i++) symbol[i] = 0;
237*14494Ssam 		npos = *state[s];
238*14494Ssam 		for(i = 1; i<=npos; i++){
239*14494Ssam 			curpos = *(state[s]+i);
240*14494Ssam 			if(name[curpos] < NCH) symbol[name[curpos]] = TRUE;
241*14494Ssam 			else switch(name[curpos]){
242*14494Ssam 			case RCCL:
243*14494Ssam 				tryit = TRUE;
244*14494Ssam 				q = left[curpos];
245*14494Ssam 				while(*q){
246*14494Ssam 					for(j=1;j<NCH;j++)
247*14494Ssam 						if(cindex[j] == *q)
248*14494Ssam 							symbol[j] = TRUE;
249*14494Ssam 					q++;
250*14494Ssam 					}
251*14494Ssam 				break;
252*14494Ssam 			case RSTR:
253*14494Ssam 				symbol[right[curpos]] = TRUE;
254*14494Ssam 				break;
255*14494Ssam # ifdef DEBUG
256*14494Ssam 			case RNULLS:
257*14494Ssam 			case FINAL:
258*14494Ssam 			case S1FINAL:
259*14494Ssam 			case S2FINAL:
260*14494Ssam 				break;
261*14494Ssam 			default:
262*14494Ssam 				warning("bad switch cgoto %d state %d",curpos,s);
263*14494Ssam 				break;
264*14494Ssam # endif
265*14494Ssam 			}
266*14494Ssam 		}
267*14494Ssam # ifdef DEBUG
268*14494Ssam 		if(debug){
269*14494Ssam 			printf("State %d transitions on:\n\t",s);
270*14494Ssam 			charc = 0;
271*14494Ssam 			for(i = 1; i<NCH; i++){
272*14494Ssam 				if(symbol[i]) allprint(i);
273*14494Ssam 				if(charc > LINESIZE){
274*14494Ssam 					charc = 0;
275*14494Ssam 					printf("\n\t");
276*14494Ssam 					}
277*14494Ssam 				}
278*14494Ssam 			putchar('\n');
279*14494Ssam 			}
280*14494Ssam # endif
281*14494Ssam 		/* for each char, calculate next state */
282*14494Ssam 		n = 0;
283*14494Ssam 		for(i = 1; i<NCH; i++){
284*14494Ssam 			if(symbol[i]){
285*14494Ssam 				nextstate(s,i);		/* executed for each state, transition pair */
286*14494Ssam 				xstate = notin(stnum);
287*14494Ssam 				if(xstate == -2) warning("bad state  %d %o",s,i);
288*14494Ssam 				else if(xstate == -1){
289*14494Ssam 					if(stnum >= nstates)
290*14494Ssam 						error("Too many states %s",(nstates == NSTATES ? "\nTry using %n num":""));
291*14494Ssam 					add(state,++stnum);
292*14494Ssam # ifdef DEBUG
293*14494Ssam 					if(debug)pstate(stnum);
294*14494Ssam # endif
295*14494Ssam 					tch[n] = i;
296*14494Ssam 					tst[n++] = stnum;
297*14494Ssam 					}
298*14494Ssam 				else {		/* xstate >= 0 ==> state exists */
299*14494Ssam 					tch[n] = i;
300*14494Ssam 					tst[n++] = xstate;
301*14494Ssam 					}
302*14494Ssam 				}
303*14494Ssam 			}
304*14494Ssam 		tch[n] = 0;
305*14494Ssam 		tst[n] = -1;
306*14494Ssam 		/* pack transitions into permanent array */
307*14494Ssam 		if(n > 0) packtrans(s,tch,tst,n,tryit);
308*14494Ssam 		else gotof[s] = -1;
309*14494Ssam 		}
310*14494Ssam 	ratfor ? fprintf(fout,"end\n") : fprintf(fout,"0};\n");
311*14494Ssam 	return;
312*14494Ssam 	}
313*14494Ssam 	/*	Beware -- 70% of total CPU time is spent in this subroutine -
314*14494Ssam 		if you don't believe me - try it yourself ! */
315*14494Ssam nextstate(s,c)
316*14494Ssam   int s,c; {
317*14494Ssam 	register int j, *newpos;
318*14494Ssam 	register char *temp, *tz;
319*14494Ssam 	int *pos, i, *f, num, curpos, number;
320*14494Ssam 	/* state to goto from state s on char c */
321*14494Ssam 	num = *state[s];
322*14494Ssam 	temp = tmpstat;
323*14494Ssam 	pos = state[s] + 1;
324*14494Ssam 	for(i = 0; i<num; i++){
325*14494Ssam 		curpos = *pos++;
326*14494Ssam 		j = name[curpos];
327*14494Ssam 		if(j < NCH && j == c
328*14494Ssam 		|| j == RSTR && c == right[curpos]
329*14494Ssam 		|| j == RCCL && member(c,left[curpos])){
330*14494Ssam 			f = foll[curpos];
331*14494Ssam 			number = *f;
332*14494Ssam 			newpos = f+1;
333*14494Ssam 			for(j=0;j<number;j++)
334*14494Ssam 				temp[*newpos++] = 2;
335*14494Ssam 			}
336*14494Ssam 		}
337*14494Ssam 	j = 0;
338*14494Ssam 	tz = temp + tptr;
339*14494Ssam 	while(temp < tz){
340*14494Ssam 		if(*temp == 2){
341*14494Ssam 			j++;
342*14494Ssam 			*temp++ = 1;
343*14494Ssam 			}
344*14494Ssam 		else *temp++ = 0;
345*14494Ssam 		}
346*14494Ssam 	count = j;
347*14494Ssam 	return;
348*14494Ssam 	}
349*14494Ssam notin(n)
350*14494Ssam   int n;	{	/* see if tmpstat occurs previously */
351*14494Ssam 	register int *j,k;
352*14494Ssam 	register char *temp;
353*14494Ssam 	int i;
354*14494Ssam 	if(count == 0)
355*14494Ssam 		return(-2);
356*14494Ssam 	temp = tmpstat;
357*14494Ssam 	for(i=n;i>=0;i--){	/* for each state */
358*14494Ssam 		j = state[i];
359*14494Ssam 		if(count == *j++){
360*14494Ssam 			for(k=0;k<count;k++)
361*14494Ssam 				if(!temp[*j++])break;
362*14494Ssam 			if(k >= count)
363*14494Ssam 				return(i);
364*14494Ssam 			}
365*14494Ssam 		}
366*14494Ssam 	return(-1);
367*14494Ssam 	}
368*14494Ssam packtrans(st,tch,tst,cnt,tryit)
369*14494Ssam   int st, *tst, cnt,tryit;
370*14494Ssam   char *tch; {
371*14494Ssam 	/* pack transitions into nchar, nexts */
372*14494Ssam 	/* nchar is terminated by '\0', nexts uses cnt, followed by elements */
373*14494Ssam 	/* gotof[st] = index into nchr, nexts for state st */
374*14494Ssam 
375*14494Ssam 	/* sfall[st] =  t implies t is fall back state for st */
376*14494Ssam 	/*	        == -1 implies no fall back */
377*14494Ssam 
378*14494Ssam 	int cmin, cval, tcnt, diff, p, *ast;
379*14494Ssam 	register int i,j,k;
380*14494Ssam 	char *ach;
381*14494Ssam 	int go[NCH], temp[NCH], c;
382*14494Ssam 	int swork[NCH];
383*14494Ssam 	char cwork[NCH];
384*14494Ssam 	int upper;
385*14494Ssam 
386*14494Ssam 	rcount += cnt;
387*14494Ssam 	cmin = -1;
388*14494Ssam 	cval = NCH;
389*14494Ssam 	ast = tst;
390*14494Ssam 	ach = tch;
391*14494Ssam 	/* try to pack transitions using ccl's */
392*14494Ssam 	if(!optim)goto nopack;		/* skip all compaction */
393*14494Ssam 	if(tryit){	/* ccl's used */
394*14494Ssam 		for(i=1;i<NCH;i++){
395*14494Ssam 			go[i] = temp[i] = -1;
396*14494Ssam 			symbol[i] = 1;
397*14494Ssam 			}
398*14494Ssam 		for(i=0;i<cnt;i++){
399*14494Ssam 			go[tch[i]] = tst[i];
400*14494Ssam 			symbol[tch[i]] = 0;
401*14494Ssam 			}
402*14494Ssam 		for(i=0; i<cnt;i++){
403*14494Ssam 			c = match[tch[i]];
404*14494Ssam 			if(go[c] != tst[i] || c == tch[i])
405*14494Ssam 				temp[tch[i]] = tst[i];
406*14494Ssam 			}
407*14494Ssam 		/* fill in error entries */
408*14494Ssam 		for(i=1;i<NCH;i++)
409*14494Ssam 			if(symbol[i]) temp[i] = -2;	/* error trans */
410*14494Ssam 		/* count them */
411*14494Ssam 		k = 0;
412*14494Ssam 		for(i=1;i<NCH;i++)
413*14494Ssam 			if(temp[i] != -1)k++;
414*14494Ssam 		if(k <cnt){	/* compress by char */
415*14494Ssam # ifdef DEBUG
416*14494Ssam 			if(debug) printf("use compression  %d,  %d vs %d\n",st,k,cnt);
417*14494Ssam # endif
418*14494Ssam 			k = 0;
419*14494Ssam 			for(i=1;i<NCH;i++)
420*14494Ssam 				if(temp[i] != -1){
421*14494Ssam 					cwork[k] = i;
422*14494Ssam 					swork[k++] = (temp[i] == -2 ? -1 : temp[i]);
423*14494Ssam 					}
424*14494Ssam 			cwork[k] = 0;
425*14494Ssam # ifdef PC
426*14494Ssam 			ach = cwork;
427*14494Ssam 			ast = swork;
428*14494Ssam 			cnt = k;
429*14494Ssam 			cpackflg[st] = TRUE;
430*14494Ssam # endif
431*14494Ssam 			}
432*14494Ssam 		}
433*14494Ssam 	for(i=0; i<st; i++){	/* get most similar state */
434*14494Ssam 				/* reject state with more transitions, state already represented by a third state,
435*14494Ssam 					and state which is compressed by char if ours is not to be */
436*14494Ssam 		if(sfall[i] != -1) continue;
437*14494Ssam 		if(cpackflg[st] == 1) if(!(cpackflg[i] == 1)) continue;
438*14494Ssam 		p = gotof[i];
439*14494Ssam 		if(p == -1) /* no transitions */ continue;
440*14494Ssam 		tcnt = nexts[p];
441*14494Ssam 		if(tcnt > cnt) continue;
442*14494Ssam 		diff = 0;
443*14494Ssam 		k = 0;
444*14494Ssam 		j = 0;
445*14494Ssam 		upper = p + tcnt;
446*14494Ssam 		while(ach[j] && p < upper){
447*14494Ssam 			while(ach[j] < nchar[p] && ach[j]){diff++; j++; }
448*14494Ssam 			if(ach[j] == 0)break;
449*14494Ssam 			if(ach[j] > nchar[p]){diff=NCH;break;}
450*14494Ssam 			/* ach[j] == nchar[p] */
451*14494Ssam 			if(ast[j] != nexts[++p] || ast[j] == -1 || (cpackflg[st] && ach[j] != match[ach[j]]))diff++;
452*14494Ssam 			j++;
453*14494Ssam 			}
454*14494Ssam 		while(ach[j]){
455*14494Ssam 			diff++;
456*14494Ssam 			j++;
457*14494Ssam 			}
458*14494Ssam 		if(p < upper)diff = NCH;
459*14494Ssam 		if(diff < cval && diff < tcnt){
460*14494Ssam 			cval = diff;
461*14494Ssam 			cmin = i;
462*14494Ssam 			if(cval == 0)break;
463*14494Ssam 			}
464*14494Ssam 		}
465*14494Ssam 	/* cmin = state "most like" state st */
466*14494Ssam # ifdef DEBUG
467*14494Ssam 	if(debug)printf("select st %d for st %d diff %d\n",cmin,st,cval);
468*14494Ssam # endif
469*14494Ssam # ifdef PS
470*14494Ssam 	if(cmin != -1){ /* if we can use st cmin */
471*14494Ssam 		gotof[st] = nptr;
472*14494Ssam 		k = 0;
473*14494Ssam 		sfall[st] = cmin;
474*14494Ssam 		p = gotof[cmin]+1;
475*14494Ssam 		j = 0;
476*14494Ssam 		while(ach[j]){
477*14494Ssam 			/* if cmin has a transition on c, then so will st */
478*14494Ssam 			/* st may be "larger" than cmin, however */
479*14494Ssam 			while(ach[j] < nchar[p-1] && ach[j]){
480*14494Ssam 				k++;
481*14494Ssam 				nchar[nptr] = ach[j];
482*14494Ssam 				nexts[++nptr] = ast[j];
483*14494Ssam 				j++;
484*14494Ssam 				}
485*14494Ssam 			if(nchar[p-1] == 0)break;
486*14494Ssam 			if(ach[j] > nchar[p-1]){
487*14494Ssam 				warning("bad transition %d %d",st,cmin);
488*14494Ssam 				goto nopack;
489*14494Ssam 				}
490*14494Ssam 			/* ach[j] == nchar[p-1] */
491*14494Ssam 			if(ast[j] != nexts[p] || ast[j] == -1 || (cpackflg[st] && ach[j] != match[ach[j]])){
492*14494Ssam 				k++;
493*14494Ssam 				nchar[nptr] = ach[j];
494*14494Ssam 				nexts[++nptr] = ast[j];
495*14494Ssam 				}
496*14494Ssam 			p++;
497*14494Ssam 			j++;
498*14494Ssam 			}
499*14494Ssam 		while(ach[j]){
500*14494Ssam 			nchar[nptr] = ach[j];
501*14494Ssam 			nexts[++nptr] = ast[j++];
502*14494Ssam 			k++;
503*14494Ssam 			}
504*14494Ssam 		nexts[gotof[st]] = cnt = k;
505*14494Ssam 		nchar[nptr++] = 0;
506*14494Ssam 		}
507*14494Ssam 	else {
508*14494Ssam # endif
509*14494Ssam nopack:
510*14494Ssam 	/* stick it in */
511*14494Ssam 		gotof[st] = nptr;
512*14494Ssam 		nexts[nptr] = cnt;
513*14494Ssam 		for(i=0;i<cnt;i++){
514*14494Ssam 			nchar[nptr] = ach[i];
515*14494Ssam 			nexts[++nptr] = ast[i];
516*14494Ssam 			}
517*14494Ssam 		nchar[nptr++] = 0;
518*14494Ssam # ifdef PS
519*14494Ssam 		}
520*14494Ssam # endif
521*14494Ssam 	if(cnt < 1){
522*14494Ssam 		gotof[st] = -1;
523*14494Ssam 		nptr--;
524*14494Ssam 		}
525*14494Ssam 	else
526*14494Ssam 		if(nptr > ntrans)
527*14494Ssam 			error("Too many transitions %s",(ntrans==NTRANS?"\nTry using %a num":""));
528*14494Ssam 	return;
529*14494Ssam 	}
530*14494Ssam # ifdef DEBUG
531*14494Ssam pstate(s)
532*14494Ssam   int s; {
533*14494Ssam 	register int *p,i,j;
534*14494Ssam 	printf("State %d:\n",s);
535*14494Ssam 	p = state[s];
536*14494Ssam 	i = *p++;
537*14494Ssam 	if(i == 0) return;
538*14494Ssam 	printf("%4d",*p++);
539*14494Ssam 	for(j = 1; j<i; j++){
540*14494Ssam 		printf(", %4d",*p++);
541*14494Ssam 		if(j%30 == 0)putchar('\n');
542*14494Ssam 		}
543*14494Ssam 	putchar('\n');
544*14494Ssam 	return;
545*14494Ssam 	}
546*14494Ssam # endif
547*14494Ssam member(d,t)
548*14494Ssam   int d;
549*14494Ssam   char *t;	{
550*14494Ssam 	register int c;
551*14494Ssam 	register char *s;
552*14494Ssam 	c = d;
553*14494Ssam 	s = t;
554*14494Ssam 	c = cindex[c];
555*14494Ssam 	while(*s)
556*14494Ssam 		if(*s++ == c) return(1);
557*14494Ssam 	return(0);
558*14494Ssam 	}
559*14494Ssam # ifdef DEBUG
560*14494Ssam stprt(i)
561*14494Ssam   int i; {
562*14494Ssam 	register int p, t;
563*14494Ssam 	printf("State %d:",i);
564*14494Ssam 	/* print actions, if any */
565*14494Ssam 	t = atable[i];
566*14494Ssam 	if(t != -1)printf(" final");
567*14494Ssam 	putchar('\n');
568*14494Ssam 	if(cpackflg[i] == TRUE)printf("backup char in use\n");
569*14494Ssam 	if(sfall[i] != -1)printf("fall back state %d\n",sfall[i]);
570*14494Ssam 	p = gotof[i];
571*14494Ssam 	if(p == -1) return;
572*14494Ssam 	printf("(%d transitions)\n",nexts[p]);
573*14494Ssam 	while(nchar[p]){
574*14494Ssam 		charc = 0;
575*14494Ssam 		if(nexts[p+1] >= 0)
576*14494Ssam 			printf("%d\t",nexts[p+1]);
577*14494Ssam 		else printf("err\t");
578*14494Ssam 		allprint(nchar[p++]);
579*14494Ssam 		while(nexts[p] == nexts[p+1] && nchar[p]){
580*14494Ssam 			if(charc > LINESIZE){
581*14494Ssam 				charc = 0;
582*14494Ssam 				printf("\n\t");
583*14494Ssam 				}
584*14494Ssam 			allprint(nchar[p++]);
585*14494Ssam 			}
586*14494Ssam 		putchar('\n');
587*14494Ssam 		}
588*14494Ssam 	putchar('\n');
589*14494Ssam 	return;
590*14494Ssam 	}
591*14494Ssam # endif
592*14494Ssam acompute(s)	/* compute action list = set of poss. actions */
593*14494Ssam   int s; {
594*14494Ssam 	register int *p, i, j;
595*14494Ssam 	int cnt, m;
596*14494Ssam 	int temp[300], k, neg[300], n;
597*14494Ssam 	k = 0;
598*14494Ssam 	n = 0;
599*14494Ssam 	p = state[s];
600*14494Ssam 	cnt = *p++;
601*14494Ssam 	if(cnt > 300)
602*14494Ssam 		error("Too many positions for one state - acompute");
603*14494Ssam 	for(i=0;i<cnt;i++){
604*14494Ssam 		if(name[*p] == FINAL)temp[k++] = left[*p];
605*14494Ssam 		else if(name[*p] == S1FINAL){temp[k++] = left[*p];
606*14494Ssam 			if (left[*p] >NACTIONS) error("Too many right contexts");
607*14494Ssam 			extra[left[*p]] = 1;
608*14494Ssam 			}
609*14494Ssam 		else if(name[*p] == S2FINAL)neg[n++] = left[*p];
610*14494Ssam 		p++;
611*14494Ssam 		}
612*14494Ssam 	atable[s] = -1;
613*14494Ssam 	if(k < 1 && n < 1) return;
614*14494Ssam # ifdef DEBUG
615*14494Ssam 	if(debug) printf("final %d actions:",s);
616*14494Ssam # endif
617*14494Ssam 	/* sort action list */
618*14494Ssam 	for(i=0; i<k; i++)
619*14494Ssam 		for(j=i+1;j<k;j++)
620*14494Ssam 			if(temp[j] < temp[i]){
621*14494Ssam 				m = temp[j];
622*14494Ssam 				temp[j] = temp[i];
623*14494Ssam 				temp[i] = m;
624*14494Ssam 				}
625*14494Ssam 	/* remove dups */
626*14494Ssam 	for(i=0;i<k-1;i++)
627*14494Ssam 		if(temp[i] == temp[i+1]) temp[i] = 0;
628*14494Ssam 	/* copy to permanent quarters */
629*14494Ssam 	atable[s] = aptr;
630*14494Ssam # ifdef DEBUG
631*14494Ssam 	if(!ratfor)fprintf(fout,"/* actions for state %d */",s);
632*14494Ssam # endif
633*14494Ssam 	putc('\n',fout);
634*14494Ssam 	for(i=0;i<k;i++)
635*14494Ssam 		if(temp[i] != 0){
636*14494Ssam 			ratfor ? fprintf(fout,"data vstop(%d)/%d/\n",aptr,temp[i]) : fprintf(fout,"%d,\n",temp[i]);
637*14494Ssam # ifdef DEBUG
638*14494Ssam 			if(debug)
639*14494Ssam 				printf("%d ",temp[i]);
640*14494Ssam # endif
641*14494Ssam 			aptr++;
642*14494Ssam 			}
643*14494Ssam 	for(i=0;i<n;i++){		/* copy fall back actions - all neg */
644*14494Ssam 		ratfor ? fprintf(fout,"data vstop(%d)/%d/\n",aptr,neg[i]) : fprintf(fout,"%d,\n",neg[i]);
645*14494Ssam 		aptr++;
646*14494Ssam # ifdef DEBUG
647*14494Ssam 		if(debug)printf("%d ",neg[i]);
648*14494Ssam # endif
649*14494Ssam 		}
650*14494Ssam # ifdef DEBUG
651*14494Ssam 	if(debug)putchar('\n');
652*14494Ssam # endif
653*14494Ssam 	ratfor ? fprintf(fout,"data vstop (%d)/0/\n",aptr) : fprintf(fout,"0,\n");
654*14494Ssam 	aptr++;
655*14494Ssam 	return;
656*14494Ssam 	}
657*14494Ssam # ifdef DEBUG
658*14494Ssam pccl() {
659*14494Ssam 	/* print character class sets */
660*14494Ssam 	register int i, j;
661*14494Ssam 	printf("char class intersection\n");
662*14494Ssam 	for(i=0; i< ccount; i++){
663*14494Ssam 		charc = 0;
664*14494Ssam 		printf("class %d:\n\t",i);
665*14494Ssam 		for(j=1;j<NCH;j++)
666*14494Ssam 			if(cindex[j] == i){
667*14494Ssam 				allprint(j);
668*14494Ssam 				if(charc > LINESIZE){
669*14494Ssam 					printf("\n\t");
670*14494Ssam 					charc = 0;
671*14494Ssam 					}
672*14494Ssam 				}
673*14494Ssam 		putchar('\n');
674*14494Ssam 		}
675*14494Ssam 	charc = 0;
676*14494Ssam 	printf("match:\n");
677*14494Ssam 	for(i=0;i<NCH;i++){
678*14494Ssam 		allprint(match[i]);
679*14494Ssam 		if(charc > LINESIZE){
680*14494Ssam 			putchar('\n');
681*14494Ssam 			charc = 0;
682*14494Ssam 			}
683*14494Ssam 		}
684*14494Ssam 	putchar('\n');
685*14494Ssam 	return;
686*14494Ssam 	}
687*14494Ssam # endif
688*14494Ssam mkmatch(){
689*14494Ssam 	register int i;
690*14494Ssam 	char tab[NCH];
691*14494Ssam 	for(i=0; i<ccount; i++)
692*14494Ssam 		tab[i] = 0;
693*14494Ssam 	for(i=1;i<NCH;i++)
694*14494Ssam 		if(tab[cindex[i]] == 0)
695*14494Ssam 			tab[cindex[i]] = i;
696*14494Ssam 	/* tab[i] = principal char for new ccl i */
697*14494Ssam 	for(i = 1; i<NCH; i++)
698*14494Ssam 		match[i] = tab[cindex[i]];
699*14494Ssam 	return;
700*14494Ssam 	}
701*14494Ssam layout(){
702*14494Ssam 	/* format and output final program's tables */
703*14494Ssam 	register int i, j, k;
704*14494Ssam 	int  top, bot, startup, omin;
705*14494Ssam 	startup = 0;
706*14494Ssam 	for(i=0; i<outsize;i++)
707*14494Ssam 		verify[i] = advance[i] = 0;
708*14494Ssam 	omin = 0;
709*14494Ssam 	yytop = 0;
710*14494Ssam 	for(i=0; i<= stnum; i++){	/* for each state */
711*14494Ssam 		j = gotof[i];
712*14494Ssam 		if(j == -1){
713*14494Ssam 			stoff[i] = 0;
714*14494Ssam 			continue;
715*14494Ssam 			}
716*14494Ssam 		bot = j;
717*14494Ssam 		while(nchar[j])j++;
718*14494Ssam 		top = j - 1;
719*14494Ssam # if DEBUG
720*14494Ssam 		if (debug)
721*14494Ssam 			{
722*14494Ssam 			printf("State %d: (layout)\n", i);
723*14494Ssam 			for(j=bot; j<=top;j++)
724*14494Ssam 				{
725*14494Ssam 				printf("  %o", nchar[j]);
726*14494Ssam 				if (j%10==0) putchar('\n');
727*14494Ssam 				}
728*14494Ssam 			putchar('\n');
729*14494Ssam 			}
730*14494Ssam # endif
731*14494Ssam 		while(verify[omin+ZCH]) omin++;
732*14494Ssam 		startup = omin;
733*14494Ssam # if DEBUG
734*14494Ssam 		if (debug) printf("bot,top %d, %d startup begins %d\n",bot,top,startup);
735*14494Ssam # endif
736*14494Ssam 		if(chset){
737*14494Ssam 			do {
738*14494Ssam 				++startup;
739*14494Ssam 				if(startup > outsize - ZCH)
740*14494Ssam 					error("output table overflow");
741*14494Ssam 				for(j = bot; j<= top; j++){
742*14494Ssam 					k=startup+ctable[nchar[j]];
743*14494Ssam 					if(verify[k])break;
744*14494Ssam 					}
745*14494Ssam 				} while (j <= top);
746*14494Ssam # if DEBUG
747*14494Ssam 			if (debug) printf(" startup will be %d\n",startup);
748*14494Ssam # endif
749*14494Ssam 			/* have found place */
750*14494Ssam 			for(j = bot; j<= top; j++){
751*14494Ssam 				k = startup + ctable[nchar[j]];
752*14494Ssam 				if (ctable[nchar[j]]<=0)
753*14494Ssam 				 printf("j %d nchar %d ctable.nch %d\n",j,nchar[j],ctable[nchar[k]]);
754*14494Ssam 				verify[k] = i+1;			/* state number + 1*/
755*14494Ssam 				advance[k] = nexts[j+1]+1;		/* state number + 1*/
756*14494Ssam 				if(yytop < k) yytop = k;
757*14494Ssam 				}
758*14494Ssam 			}
759*14494Ssam 		else {
760*14494Ssam 			do {
761*14494Ssam 				++startup;
762*14494Ssam 				if(startup > outsize - ZCH)
763*14494Ssam 					error("output table overflow");
764*14494Ssam 				for(j = bot; j<= top; j++){
765*14494Ssam 					k = startup + nchar[j];
766*14494Ssam 					if(verify[k])break;
767*14494Ssam 					}
768*14494Ssam 				} while (j <= top);
769*14494Ssam 			/* have found place */
770*14494Ssam # if DEBUG
771*14494Ssam 	if (debug) printf(" startup going to be %d\n", startup);
772*14494Ssam # endif
773*14494Ssam 			for(j = bot; j<= top; j++){
774*14494Ssam 				k = startup + nchar[j];
775*14494Ssam 				verify[k] = i+1;			/* state number + 1*/
776*14494Ssam 				advance[k] = nexts[j+1]+1;		/* state number + 1*/
777*14494Ssam 				if(yytop < k) yytop = k;
778*14494Ssam 				}
779*14494Ssam 			}
780*14494Ssam 		stoff[i] = startup;
781*14494Ssam 		}
782*14494Ssam 
783*14494Ssam 	/* stoff[i] = offset into verify, advance for trans for state i */
784*14494Ssam 	/* put out yywork */
785*14494Ssam 	if(ratfor){
786*14494Ssam 		fprintf(fout, "define YYTOPVAL %d\n", yytop);
787*14494Ssam 		rprint(verify,"verif",yytop+1);
788*14494Ssam 		rprint(advance,"advan",yytop+1);
789*14494Ssam  		shiftr(stoff, stnum);
790*14494Ssam 		rprint(stoff,"stoff",stnum+1);
791*14494Ssam  		shiftr(sfall, stnum); upone(sfall, stnum+1);
792*14494Ssam 		rprint(sfall,"sfall",stnum+1);
793*14494Ssam 		bprint(extra,"extra",casecount+1);
794*14494Ssam 		bprint(match,"match",NCH);
795*14494Ssam  		shiftr(atable, stnum);
796*14494Ssam 		rprint(atable,"atable",stnum+1);
797*14494Ssam 		return;
798*14494Ssam 		}
799*14494Ssam 	fprintf(fout,"# define YYTYPE %s\n",stnum+1 > NCH ? "int" : "char");
800*14494Ssam 	fprintf(fout,"struct yywork { YYTYPE verify, advance; } yycrank[] ={\n");
801*14494Ssam 	for(i=0;i<=yytop;i+=4){
802*14494Ssam 		for(j=0;j<4;j++){
803*14494Ssam 			k = i+j;
804*14494Ssam 			if(verify[k])
805*14494Ssam 				fprintf(fout,"%d,%d,\t",verify[k],advance[k]);
806*14494Ssam 			else
807*14494Ssam 				fprintf(fout,"0,0,\t");
808*14494Ssam 			}
809*14494Ssam 		putc('\n',fout);
810*14494Ssam 		}
811*14494Ssam 	fprintf(fout,"0,0};\n");
812*14494Ssam 
813*14494Ssam 	/* put out yysvec */
814*14494Ssam 
815*14494Ssam 	fprintf(fout,"struct yysvf yysvec[] ={\n");
816*14494Ssam 	fprintf(fout,"0,\t0,\t0,\n");
817*14494Ssam 	for(i=0;i<=stnum;i++){	/* for each state */
818*14494Ssam 		if(cpackflg[i])stoff[i] = -stoff[i];
819*14494Ssam 		fprintf(fout,"yycrank+%d,\t",stoff[i]);
820*14494Ssam 		if(sfall[i] != -1)
821*14494Ssam 			fprintf(fout,"yysvec+%d,\t", sfall[i]+1);	/* state + 1 */
822*14494Ssam 		else fprintf(fout,"0,\t\t");
823*14494Ssam 		if(atable[i] != -1)
824*14494Ssam 			fprintf(fout,"yyvstop+%d,",atable[i]);
825*14494Ssam 		else fprintf(fout,"0,\t");
826*14494Ssam # ifdef DEBUG
827*14494Ssam 		fprintf(fout,"\t\t/* state %d */",i);
828*14494Ssam # endif
829*14494Ssam 		putc('\n',fout);
830*14494Ssam 		}
831*14494Ssam 	fprintf(fout,"0,\t0,\t0};\n");
832*14494Ssam 
833*14494Ssam 	/* put out yymatch */
834*14494Ssam 
835*14494Ssam 	fprintf(fout,"struct yywork *yytop = yycrank+%d;\n",yytop);
836*14494Ssam 	fprintf(fout,"struct yysvf *yybgin = yysvec+1;\n");
837*14494Ssam 	if(optim){
838*14494Ssam 		fprintf(fout,"char yymatch[] ={\n");
839*14494Ssam 		if (chset==0) /* no chset, put out in normal order */
840*14494Ssam 			{
841*14494Ssam 			for(i=0; i<NCH; i+=8){
842*14494Ssam 				for(j=0; j<8; j++){
843*14494Ssam 					int fbch;
844*14494Ssam 					fbch = match[i+j];
845*14494Ssam 					if(printable(fbch) && fbch != '\'' && fbch != '\\')
846*14494Ssam 						fprintf(fout,"'%c' ,",fbch);
847*14494Ssam 					else fprintf(fout,"0%-3o,",fbch);
848*14494Ssam 					}
849*14494Ssam 				putc('\n',fout);
850*14494Ssam 				}
851*14494Ssam 			}
852*14494Ssam 		else
853*14494Ssam 			{
854*14494Ssam 			int *fbarr;
855*14494Ssam 			fbarr = myalloc(2*NCH, sizeof(*fbarr));
856*14494Ssam 			if (fbarr==0)
857*14494Ssam 				error("No space for char table reverse",0);
858*14494Ssam 			for(i=0; i<ZCH; i++)
859*14494Ssam 				fbarr[i]=0;
860*14494Ssam 			for(i=0; i<NCH; i++)
861*14494Ssam 				fbarr[ctable[i]] = ctable[match[i]];
862*14494Ssam 			for(i=0; i<ZCH; i+=8)
863*14494Ssam 				{
864*14494Ssam 				for(j=0; j<8; j++)
865*14494Ssam 					fprintf(fout, "0%-3o,",fbarr[i+j]);
866*14494Ssam 				putc('\n',fout);
867*14494Ssam 				}
868*14494Ssam 			cfree(fbarr, 2*NCH, 1);
869*14494Ssam 			}
870*14494Ssam 		fprintf(fout,"0};\n");
871*14494Ssam 		}
872*14494Ssam 	/* put out yyextra */
873*14494Ssam 	fprintf(fout,"char yyextra[] ={\n");
874*14494Ssam 	for(i=0;i<casecount;i+=8){
875*14494Ssam 		for(j=0;j<8;j++)
876*14494Ssam 			fprintf(fout, "%d,", i+j<NACTIONS ?
877*14494Ssam 				extra[i+j] : 0);
878*14494Ssam 		putc('\n',fout);
879*14494Ssam 		}
880*14494Ssam 	fprintf(fout,"0};\n");
881*14494Ssam 	return;
882*14494Ssam 	}
883*14494Ssam rprint(a,s,n)
884*14494Ssam   char *s;
885*14494Ssam   int *a, n; {
886*14494Ssam 	register int i;
887*14494Ssam 	fprintf(fout,"block data\n");
888*14494Ssam 	fprintf(fout,"common /L%s/ %s\n",s,s);
889*14494Ssam 	fprintf(fout,"define S%s %d\n",s,n);
890*14494Ssam 	fprintf(fout,"integer %s (S%s)\n",s,s);
891*14494Ssam 	for(i=1; i<=n; i++)
892*14494Ssam 		{
893*14494Ssam 		if (i%8==1) fprintf(fout, "data ");
894*14494Ssam 		fprintf(fout, "%s (%d)/%d/",s,i,a[i]);
895*14494Ssam 		fprintf(fout, (i%8 && i<n) ? ", " : "\n");
896*14494Ssam 		}
897*14494Ssam 	fprintf(fout,"end\n");
898*14494Ssam 	}
899*14494Ssam shiftr(a, n)
900*14494Ssam 	int *a;
901*14494Ssam {
902*14494Ssam int i;
903*14494Ssam for(i=n; i>=0; i--)
904*14494Ssam 	a[i+1]=a[i];
905*14494Ssam }
906*14494Ssam upone(a,n)
907*14494Ssam 	int *a;
908*14494Ssam {
909*14494Ssam int i;
910*14494Ssam for(i=0; i<=n ; i++)
911*14494Ssam 	a[i]++;
912*14494Ssam }
913*14494Ssam bprint(a,s,n)
914*14494Ssam  char *s,  *a;
915*14494Ssam  int  n; {
916*14494Ssam 	register int i, j, k;
917*14494Ssam 	fprintf(fout,"block data\n");
918*14494Ssam 	fprintf(fout,"common /L%s/ %s\n",s,s);
919*14494Ssam 	fprintf(fout,"define S%s %d\n",s,n);
920*14494Ssam 	fprintf(fout,"integer %s (S%s)\n",s,s);
921*14494Ssam 	for(i=1;i<n;i+=8){
922*14494Ssam 		fprintf(fout,"data %s (%d)/%d/",s,i,a[i]);
923*14494Ssam 		for(j=1;j<8;j++){
924*14494Ssam 			k = i+j;
925*14494Ssam 			if(k < n)fprintf(fout,", %s (%d)/%d/",s,k,a[k]);
926*14494Ssam 			}
927*14494Ssam 		putc('\n',fout);
928*14494Ssam 		}
929*14494Ssam 	fprintf(fout,"end\n");
930*14494Ssam 	}
931*14494Ssam # ifdef PP
932*14494Ssam padd(array,n)
933*14494Ssam   int **array;
934*14494Ssam   int n; {
935*14494Ssam 	register int i, *j, k;
936*14494Ssam 	array[n] = nxtpos;
937*14494Ssam 	if(count == 0){
938*14494Ssam 		*nxtpos++ = 0;
939*14494Ssam 		return;
940*14494Ssam 		}
941*14494Ssam 	for(i=tptr-1;i>=0;i--){
942*14494Ssam 		j = array[i];
943*14494Ssam 		if(j && *j++ == count){
944*14494Ssam 			for(k=0;k<count;k++)
945*14494Ssam 				if(!tmpstat[*j++])break;
946*14494Ssam 			if(k >= count){
947*14494Ssam 				array[n] = array[i];
948*14494Ssam 				return;
949*14494Ssam 				}
950*14494Ssam 			}
951*14494Ssam 		}
952*14494Ssam 	add(array,n);
953*14494Ssam 	return;
954*14494Ssam 	}
955*14494Ssam # endif
956