xref: /csrg-svn/usr.bin/pascal/pdx/sym/tree.c (revision 5531)
1*5531Slinton /* Copyright (c) 1982 Regents of the University of California */
2*5531Slinton 
3*5531Slinton static char sccsid[] = "@(#)tree.c 1.1 01/18/82";
4*5531Slinton 
5*5531Slinton /*
6*5531Slinton  * This module contains the interface between the SYM routines and
7*5531Slinton  * the parse tree routines.  It would be nice if such a crude
8*5531Slinton  * interface were not necessary, but some parts of tree building are
9*5531Slinton  * language and hence SYM-representation dependent.  It's probably
10*5531Slinton  * better to have tree-representation dependent code here than vice versa.
11*5531Slinton  */
12*5531Slinton 
13*5531Slinton #include "defs.h"
14*5531Slinton #include "tree.h"
15*5531Slinton #include "sym.h"
16*5531Slinton #include "btypes.h"
17*5531Slinton #include "classes.h"
18*5531Slinton #include "sym.rep"
19*5531Slinton #include "tree/tree.rep"
20*5531Slinton 
21*5531Slinton typedef char *ARGLIST;
22*5531Slinton 
23*5531Slinton #define nextarg(arglist, type)	((type *) (arglist += sizeof(type)))[-1]
24*5531Slinton 
25*5531Slinton LOCAL SYM *mkstring();
26*5531Slinton LOCAL SYM *namenode();
27*5531Slinton 
28*5531Slinton /*
29*5531Slinton  * Determine the type of a parse tree.  While we're at, check
30*5531Slinton  * the parse tree out.
31*5531Slinton  */
32*5531Slinton 
33*5531Slinton SYM *treetype(p, ap)
34*5531Slinton register NODE *p;
35*5531Slinton register ARGLIST ap;
36*5531Slinton {
37*5531Slinton 	switch(p->op) {
38*5531Slinton 		case O_NAME: {
39*5531Slinton 			SYM *s;
40*5531Slinton 
41*5531Slinton 			s = nextarg(ap, SYM *);
42*5531Slinton 			s = which(s);
43*5531Slinton 			return namenode(p, s);
44*5531Slinton 			/* NOTREACHED */
45*5531Slinton 		}
46*5531Slinton 
47*5531Slinton 		case O_WHICH:
48*5531Slinton 			p->nameval = nextarg(ap, SYM *);
49*5531Slinton 			p->nameval = which(p->nameval);
50*5531Slinton 			return NIL;
51*5531Slinton 
52*5531Slinton 		case O_LCON:
53*5531Slinton 			return t_int;
54*5531Slinton 
55*5531Slinton 		case O_FCON:
56*5531Slinton 			return t_real;
57*5531Slinton 
58*5531Slinton 		case O_SCON: {
59*5531Slinton 			char *cpy;
60*5531Slinton 			SYM *s;
61*5531Slinton 
62*5531Slinton 			cpy = strdup(p->sconval);
63*5531Slinton 			p->sconval = cpy;
64*5531Slinton 			s = mkstring(p->sconval);
65*5531Slinton 			if (s == t_char) {
66*5531Slinton 				p->op = O_LCON;
67*5531Slinton 				p->lconval = p->sconval[0];
68*5531Slinton 			}
69*5531Slinton 			return s;
70*5531Slinton 		}
71*5531Slinton 
72*5531Slinton 		case O_INDIR:
73*5531Slinton 			p->left = nextarg(ap, NODE *);
74*5531Slinton 			chkclass(p->left, PTR);
75*5531Slinton 			return rtype(p->left->nodetype)->type;
76*5531Slinton 
77*5531Slinton 		case O_RVAL: {
78*5531Slinton 			NODE *p1, *q;
79*5531Slinton 
80*5531Slinton 			p1 = p->left;
81*5531Slinton 			p->nodetype = p1->nodetype;
82*5531Slinton 			if (p1->op == O_NAME) {
83*5531Slinton 				if (p1->nodetype->class == FUNC) {
84*5531Slinton 					p->op = O_CALL;
85*5531Slinton 					p->right = NIL;
86*5531Slinton 				} else if (p1->nameval->class == CONST) {
87*5531Slinton 					if (p1->nameval->type == t_real->type) {
88*5531Slinton 						p->op = O_FCON;
89*5531Slinton 						p->fconval = p1->nameval->symvalue.fconval;
90*5531Slinton 						p->nodetype = t_real;
91*5531Slinton 						dispose(p1);
92*5531Slinton 					} else {
93*5531Slinton 						p->op = O_LCON;
94*5531Slinton 						p->lconval = p1->nameval->symvalue.iconval;
95*5531Slinton 						p->nodetype = p1->nameval->type;
96*5531Slinton 						dispose(p1);
97*5531Slinton 					}
98*5531Slinton 				}
99*5531Slinton 			}
100*5531Slinton 			return p->nodetype;
101*5531Slinton 			/* NOTREACHED */
102*5531Slinton 		}
103*5531Slinton 
104*5531Slinton 		case O_CALL: {
105*5531Slinton 			SYM *s;
106*5531Slinton 
107*5531Slinton 			p->left = nextarg(ap, NODE *);
108*5531Slinton 			p->right = nextarg(ap, NODE *);
109*5531Slinton 			s = p->left->nodetype;
110*5531Slinton 			if (isblock(s) && isbuiltin(s)) {
111*5531Slinton 				p->op = (OP) s->symvalue.token.tokval;
112*5531Slinton 				tfree(p->left);
113*5531Slinton 				p->left = p->right;
114*5531Slinton 				p->right = NIL;
115*5531Slinton 			}
116*5531Slinton 			return s->type;
117*5531Slinton 		}
118*5531Slinton 
119*5531Slinton 		case O_ITOF:
120*5531Slinton 			return t_real;
121*5531Slinton 
122*5531Slinton 		case O_NEG: {
123*5531Slinton 			SYM *s;
124*5531Slinton 
125*5531Slinton 			p->left = nextarg(ap, NODE *);
126*5531Slinton 			s = p->left->nodetype;
127*5531Slinton 			if (!compatible(s, t_int)) {
128*5531Slinton 				if (!compatible(s, t_real)) {
129*5531Slinton 					trerror("%t is improper type", p->left);
130*5531Slinton 				} else {
131*5531Slinton 					p->op = O_NEGF;
132*5531Slinton 				}
133*5531Slinton 			}
134*5531Slinton 			return s;
135*5531Slinton 		}
136*5531Slinton 
137*5531Slinton 		case O_ADD:
138*5531Slinton 		case O_SUB:
139*5531Slinton 		case O_MUL:
140*5531Slinton 		case O_LT:
141*5531Slinton 		case O_LE:
142*5531Slinton 		case O_GT:
143*5531Slinton 		case O_GE:
144*5531Slinton 		case O_EQ:
145*5531Slinton 		case O_NE:
146*5531Slinton 		{
147*5531Slinton 			BOOLEAN t1real, t2real;
148*5531Slinton 			SYM *t1, *t2;
149*5531Slinton 
150*5531Slinton 			p->left = nextarg(ap, NODE *);
151*5531Slinton 			p->right = nextarg(ap, NODE *);
152*5531Slinton 			t1 = rtype(p->left->nodetype);
153*5531Slinton 			t2 = rtype(p->right->nodetype);
154*5531Slinton 			t1real = (t1 == t_real);
155*5531Slinton 			t2real = (t2 == t_real);
156*5531Slinton 			if (t1real || t2real) {
157*5531Slinton 				p->op++;
158*5531Slinton 				if (!t1real) {
159*5531Slinton 					p->left = build(O_ITOF, p->left);
160*5531Slinton 				} else if (!t2real) {
161*5531Slinton 					p->right = build(O_ITOF, p->right);
162*5531Slinton 				}
163*5531Slinton 			} else {
164*5531Slinton 				if (t1real) {
165*5531Slinton 					convert(&p->left, t_int, O_NOP);
166*5531Slinton 				}
167*5531Slinton 				if (t2real) {
168*5531Slinton 					convert(&p->right, t_int, O_NOP);
169*5531Slinton 				}
170*5531Slinton 			}
171*5531Slinton 			if (p->op >= O_LT) {
172*5531Slinton 				return t_boolean;
173*5531Slinton 			} else {
174*5531Slinton 				if (t1real || t2real) {
175*5531Slinton 					return t_real;
176*5531Slinton 				} else {
177*5531Slinton 					return t_int;
178*5531Slinton 				}
179*5531Slinton 			}
180*5531Slinton 			/* NOTREACHED */
181*5531Slinton 		}
182*5531Slinton 
183*5531Slinton 		case O_DIVF:
184*5531Slinton 			p->left = nextarg(ap, NODE *);
185*5531Slinton 			p->right = nextarg(ap, NODE *);
186*5531Slinton 			convert(&p->left, t_real, O_ITOF);
187*5531Slinton 			convert(&p->right, t_real, O_ITOF);
188*5531Slinton 			return t_real;
189*5531Slinton 
190*5531Slinton 		case O_DIV:
191*5531Slinton 		case O_MOD:
192*5531Slinton 			p->left = nextarg(ap, NODE *);
193*5531Slinton 			p->right = nextarg(ap, NODE *);
194*5531Slinton 			convert(&p->left, t_int, O_NOP);
195*5531Slinton 			convert(&p->right, t_int, O_NOP);
196*5531Slinton 			return t_int;
197*5531Slinton 
198*5531Slinton 		case O_AND:
199*5531Slinton 		case O_OR:
200*5531Slinton 			p->left = nextarg(ap, NODE *);
201*5531Slinton 			p->right = nextarg(ap, NODE *);
202*5531Slinton 			chkboolean(p->left);
203*5531Slinton 			chkboolean(p->right);
204*5531Slinton 			return t_boolean;
205*5531Slinton 
206*5531Slinton 		default:
207*5531Slinton 			return NIL;
208*5531Slinton 	}
209*5531Slinton }
210*5531Slinton 
211*5531Slinton /*
212*5531Slinton  * Create a node for a name.  The symbol for the name has already
213*5531Slinton  * been chosen, either implicitly with "which" or explicitly from
214*5531Slinton  * the dot routine.
215*5531Slinton  */
216*5531Slinton 
217*5531Slinton LOCAL SYM *namenode(p, s)
218*5531Slinton NODE *p;
219*5531Slinton SYM *s;
220*5531Slinton {
221*5531Slinton 	NODE *np;
222*5531Slinton 
223*5531Slinton 	p->nameval = s;
224*5531Slinton 	if (s->class == REF) {
225*5531Slinton 		np = alloc(1, NODE);
226*5531Slinton 		*np = *p;
227*5531Slinton 		p->op = O_INDIR;
228*5531Slinton 		p->left = np;
229*5531Slinton 		np->nodetype = s;
230*5531Slinton 	}
231*5531Slinton 	if (s->class == CONST || s->class == VAR || s->class == FVAR) {
232*5531Slinton 		return s->type;
233*5531Slinton 	} else {
234*5531Slinton 		return s;
235*5531Slinton 	}
236*5531Slinton }
237*5531Slinton 
238*5531Slinton /*
239*5531Slinton  * Convert a tree to a type via a conversion operator;
240*5531Slinton  * if this isn't possible generate an error.
241*5531Slinton  *
242*5531Slinton  * Note the tree is call by address, hence the #define below.
243*5531Slinton  */
244*5531Slinton 
245*5531Slinton LOCAL convert(tp, typeto, op)
246*5531Slinton NODE **tp;
247*5531Slinton SYM *typeto;
248*5531Slinton OP op;
249*5531Slinton {
250*5531Slinton #define tree	(*tp)
251*5531Slinton 
252*5531Slinton 	SYM *s;
253*5531Slinton 
254*5531Slinton 	s = rtype(tree->nodetype);
255*5531Slinton 	typeto = rtype(typeto);
256*5531Slinton 	if (typeto == t_real && compatible(s, t_int)) {
257*5531Slinton 		tree = build(op, tree);
258*5531Slinton 	} else if (!compatible(s, typeto)) {
259*5531Slinton 		trerror("%t is improper type");
260*5531Slinton 	} else if (op != O_NOP && s != typeto) {
261*5531Slinton 		tree = build(op, tree);
262*5531Slinton 	}
263*5531Slinton 
264*5531Slinton #undef tree
265*5531Slinton }
266*5531Slinton 
267*5531Slinton /*
268*5531Slinton  * Construct a node for the Pascal dot operator.
269*5531Slinton  *
270*5531Slinton  * If the left operand is not a record, but rather a procedure
271*5531Slinton  * or function, then we interpret the "." as referencing an
272*5531Slinton  * "invisible" variable; i.e. a variable within a dynamically
273*5531Slinton  * active block but not within the static scope of the current procedure.
274*5531Slinton  */
275*5531Slinton 
276*5531Slinton NODE *dot(record, field)
277*5531Slinton NODE *record;
278*5531Slinton SYM *field;
279*5531Slinton {
280*5531Slinton 	register NODE *p;
281*5531Slinton 	register SYM *s;
282*5531Slinton 
283*5531Slinton 	if (isblock(record->nodetype)) {
284*5531Slinton 		s = findsym(field, record->nodetype);
285*5531Slinton 		if (s == NIL) {
286*5531Slinton 			error("\"%s\" is not defined in \"%s\"",
287*5531Slinton 				field->symbol, record->nodetype->symbol);
288*5531Slinton 		}
289*5531Slinton 		p = alloc(1, NODE);
290*5531Slinton 		p->op = O_NAME;
291*5531Slinton 		p->nodetype = namenode(p, s);
292*5531Slinton 	} else {
293*5531Slinton 		s = findclass(field, FIELD);
294*5531Slinton 		if (s == NIL) {
295*5531Slinton 			error("\"%s\" is not a field", field->symbol);
296*5531Slinton 		}
297*5531Slinton 		field = s;
298*5531Slinton 		chkfield(record, field);
299*5531Slinton 		p = alloc(1, NODE);
300*5531Slinton 		p->op = O_ADD;
301*5531Slinton 		p->nodetype = field->type;
302*5531Slinton 		p->left = record;
303*5531Slinton 		p->right = build(O_LCON, (long) field->symvalue.offset);
304*5531Slinton 	}
305*5531Slinton 	return p;
306*5531Slinton }
307*5531Slinton 
308*5531Slinton /*
309*5531Slinton  * Return a tree corresponding to an array reference and do the
310*5531Slinton  * error checking.
311*5531Slinton  */
312*5531Slinton 
313*5531Slinton NODE *subscript(a, slist)
314*5531Slinton NODE *a, *slist;
315*5531Slinton {
316*5531Slinton 	register SYM *t;
317*5531Slinton 	register NODE *p;
318*5531Slinton 	SYM *etype, *atype, *eltype;
319*5531Slinton 	NODE *esub, *olda;
320*5531Slinton 
321*5531Slinton 	olda = a;
322*5531Slinton 	t = rtype(a->nodetype);
323*5531Slinton 	if (t->class != ARRAY) {
324*5531Slinton 		trerror("%t is not an array");
325*5531Slinton 	}
326*5531Slinton 	eltype = t->type;
327*5531Slinton 	p = slist;
328*5531Slinton 	t = t->chain;
329*5531Slinton 	for (; p != NIL && t != NIL; p = p->right, t = t->chain) {
330*5531Slinton 		esub = p->left;
331*5531Slinton 		etype = rtype(esub->nodetype);
332*5531Slinton 		atype = rtype(t);
333*5531Slinton 		if (!compatible(atype, etype)) {
334*5531Slinton 			trerror("subscript %t is the wrong type", esub);
335*5531Slinton 		}
336*5531Slinton 		a = build(O_INDEX, a, esub);
337*5531Slinton 		a->nodetype = eltype;
338*5531Slinton 	}
339*5531Slinton 	if (p != NIL) {
340*5531Slinton 		trerror("too many subscripts for %t", olda);
341*5531Slinton 	} else if (t != NIL) {
342*5531Slinton 		trerror("not enough subscripts for %t", olda);
343*5531Slinton 	}
344*5531Slinton 	return(a);
345*5531Slinton }
346*5531Slinton 
347*5531Slinton /*
348*5531Slinton  * Evaluate a subscript index.
349*5531Slinton  */
350*5531Slinton 
351*5531Slinton evalindex(s)
352*5531Slinton SYM *s;
353*5531Slinton {
354*5531Slinton 	long i;
355*5531Slinton 	long lb, ub;
356*5531Slinton 
357*5531Slinton 	s = rtype(s)->chain;
358*5531Slinton 	i = pop(long);
359*5531Slinton 	lb = s->symvalue.rangev.lower;
360*5531Slinton 	ub = s->symvalue.rangev.upper;
361*5531Slinton 	if (i < lb || i > ub) {
362*5531Slinton 		error("subscript out of range");
363*5531Slinton 	}
364*5531Slinton 	return(i - lb);
365*5531Slinton }
366*5531Slinton 
367*5531Slinton /*
368*5531Slinton  * Check that a record.field usage is proper.
369*5531Slinton  */
370*5531Slinton 
371*5531Slinton LOCAL chkfield(r, f)
372*5531Slinton NODE *r;
373*5531Slinton SYM *f;
374*5531Slinton {
375*5531Slinton 	register SYM *s;
376*5531Slinton 
377*5531Slinton 	chkclass(r, RECORD);
378*5531Slinton 
379*5531Slinton 	/*
380*5531Slinton 	 * Don't do this for compiled code.
381*5531Slinton 	 */
382*5531Slinton #	if (!isvax)
383*5531Slinton 		for (s = r->nodetype->chain; s != NIL; s = s->chain) {
384*5531Slinton 			if (s == f) {
385*5531Slinton 				break;
386*5531Slinton 			}
387*5531Slinton 		}
388*5531Slinton 		if (s == NIL) {
389*5531Slinton 			error("\"%s\" is not a field in specified record", f->symbol);
390*5531Slinton 		}
391*5531Slinton #	endif
392*5531Slinton }
393*5531Slinton 
394*5531Slinton /*
395*5531Slinton  * Check to see if a tree is boolean-valued, if not it's an error.
396*5531Slinton  */
397*5531Slinton 
398*5531Slinton chkboolean(p)
399*5531Slinton register NODE *p;
400*5531Slinton {
401*5531Slinton 	if (p->nodetype != t_boolean) {
402*5531Slinton 		trerror("found %t, expected boolean expression");
403*5531Slinton 	}
404*5531Slinton }
405*5531Slinton 
406*5531Slinton /*
407*5531Slinton  * Check to make sure the given tree has a type of the given class.
408*5531Slinton  */
409*5531Slinton 
410*5531Slinton LOCAL chkclass(p, class)
411*5531Slinton NODE *p;
412*5531Slinton int class;
413*5531Slinton {
414*5531Slinton 	SYM tmpsym;
415*5531Slinton 
416*5531Slinton 	tmpsym.class = class;
417*5531Slinton 	if (p->nodetype->class != class) {
418*5531Slinton 		trerror("%t is not a %s", p, classname(&tmpsym));
419*5531Slinton 	}
420*5531Slinton }
421*5531Slinton 
422*5531Slinton /*
423*5531Slinton  * Construct a node for the type of a string.  While we're at it,
424*5531Slinton  * scan the string for '' that collapse to ', and chop off the ends.
425*5531Slinton  */
426*5531Slinton 
427*5531Slinton LOCAL SYM *mkstring(str)
428*5531Slinton char *str;
429*5531Slinton {
430*5531Slinton 	register char *p, *q;
431*5531Slinton 	SYM *s, *t;
432*5531Slinton 	static SYM zerosym;
433*5531Slinton 
434*5531Slinton 	p = str;
435*5531Slinton 	q = str + 1;
436*5531Slinton 	while (*q != '\0') {
437*5531Slinton 		if (q[0] != '\'' || q[1] != '\'') {
438*5531Slinton 			*p = *q;
439*5531Slinton 			p++;
440*5531Slinton 		}
441*5531Slinton 		q++;
442*5531Slinton 	}
443*5531Slinton 	*--p = '\0';
444*5531Slinton 	if (p == str + 1) {
445*5531Slinton 		return t_char;
446*5531Slinton 	}
447*5531Slinton 	s = alloc(1, SYM);
448*5531Slinton 	*s = zerosym;
449*5531Slinton 	s->class = ARRAY;
450*5531Slinton 	s->type = t_char;
451*5531Slinton 	s->chain = alloc(1, SYM);
452*5531Slinton 	t = s->chain;
453*5531Slinton 	*t = zerosym;
454*5531Slinton 	t->class = RANGE;
455*5531Slinton 	t->type = t_int;
456*5531Slinton 	t->symvalue.rangev.lower = 1;
457*5531Slinton 	t->symvalue.rangev.upper = p - str + 1;
458*5531Slinton 	return s;
459*5531Slinton }
460*5531Slinton 
461*5531Slinton /*
462*5531Slinton  * Free up the space allocated for a string type.
463*5531Slinton  */
464*5531Slinton 
465*5531Slinton unmkstring(s)
466*5531Slinton SYM *s;
467*5531Slinton {
468*5531Slinton 	dispose(s->chain);
469*5531Slinton }
470