xref: /csrg-svn/old/pcc/ccom.vax/local.c (revision 9701)
1*9701Slinton static char *sccsid ="@(#)local.c	1.1 (Berkeley) 12/15/82";
2*9701Slinton # include "mfile1"
3*9701Slinton 
4*9701Slinton /*	this file contains code which is dependent on the target machine */
5*9701Slinton 
6*9701Slinton NODE *
7*9701Slinton cast( p, t ) register NODE *p; TWORD t; {
8*9701Slinton 	/* cast node p to type t */
9*9701Slinton 
10*9701Slinton 	p = buildtree( CAST, block( NAME, NIL, NIL, t, 0, (int)t ), p );
11*9701Slinton 	p->in.left->in.op = FREE;
12*9701Slinton 	p->in.op = FREE;
13*9701Slinton 	return( p->in.right );
14*9701Slinton 	}
15*9701Slinton 
16*9701Slinton NODE *
17*9701Slinton clocal(p) NODE *p; {
18*9701Slinton 
19*9701Slinton 	/* this is called to do local transformations on
20*9701Slinton 	   an expression tree preparitory to its being
21*9701Slinton 	   written out in intermediate code.
22*9701Slinton 	*/
23*9701Slinton 
24*9701Slinton 	/* the major essential job is rewriting the
25*9701Slinton 	   automatic variables and arguments in terms of
26*9701Slinton 	   REG and OREG nodes */
27*9701Slinton 	/* conversion ops which are not necessary are also clobbered here */
28*9701Slinton 	/* in addition, any special features (such as rewriting
29*9701Slinton 	   exclusive or) are easily handled here as well */
30*9701Slinton 
31*9701Slinton 	register struct symtab *q;
32*9701Slinton 	register NODE *r;
33*9701Slinton 	register o;
34*9701Slinton 	register m, ml;
35*9701Slinton 
36*9701Slinton 	switch( o = p->in.op ){
37*9701Slinton 
38*9701Slinton 	case NAME:
39*9701Slinton 		if( p->tn.rval < 0 ) { /* already processed; ignore... */
40*9701Slinton 			return(p);
41*9701Slinton 			}
42*9701Slinton 		q = &stab[p->tn.rval];
43*9701Slinton 		switch( q->sclass ){
44*9701Slinton 
45*9701Slinton 		case AUTO:
46*9701Slinton 		case PARAM:
47*9701Slinton 			/* fake up a structure reference */
48*9701Slinton 			r = block( REG, NIL, NIL, PTR+STRTY, 0, 0 );
49*9701Slinton 			r->tn.lval = 0;
50*9701Slinton 			r->tn.rval = (q->sclass==AUTO?STKREG:ARGREG);
51*9701Slinton 			p = stref( block( STREF, r, p, 0, 0, 0 ) );
52*9701Slinton 			break;
53*9701Slinton 
54*9701Slinton 		case ULABEL:
55*9701Slinton 		case LABEL:
56*9701Slinton 		case STATIC:
57*9701Slinton 			if( q->slevel == 0 ) break;
58*9701Slinton 			p->tn.lval = 0;
59*9701Slinton 			p->tn.rval = -q->offset;
60*9701Slinton 			break;
61*9701Slinton 
62*9701Slinton 		case REGISTER:
63*9701Slinton 			p->in.op = REG;
64*9701Slinton 			p->tn.lval = 0;
65*9701Slinton 			p->tn.rval = q->offset;
66*9701Slinton 			break;
67*9701Slinton 
68*9701Slinton 			}
69*9701Slinton 		break;
70*9701Slinton 
71*9701Slinton 	case PCONV:
72*9701Slinton 		/* do pointer conversions for char and longs */
73*9701Slinton 		ml = p->in.left->in.type;
74*9701Slinton 		if( ( ml==CHAR || ml==UCHAR || ml==SHORT || ml==USHORT ) && p->in.left->in.op != ICON ) break;
75*9701Slinton 
76*9701Slinton 		/* pointers all have the same representation; the type is inherited */
77*9701Slinton 
78*9701Slinton 	inherit:
79*9701Slinton 		p->in.left->in.type = p->in.type;
80*9701Slinton 		p->in.left->fn.cdim = p->fn.cdim;
81*9701Slinton 		p->in.left->fn.csiz = p->fn.csiz;
82*9701Slinton 		p->in.op = FREE;
83*9701Slinton 		return( p->in.left );
84*9701Slinton 
85*9701Slinton 	case SCONV:
86*9701Slinton 		m = (p->in.type == FLOAT || p->in.type == DOUBLE );
87*9701Slinton 		ml = (p->in.left->in.type == FLOAT || p->in.left->in.type == DOUBLE );
88*9701Slinton 		if( m != ml ) break;
89*9701Slinton 
90*9701Slinton 		/* now, look for conversions downwards */
91*9701Slinton 
92*9701Slinton 		m = p->in.type;
93*9701Slinton 		ml = p->in.left->in.type;
94*9701Slinton 		if( p->in.left->in.op == ICON ){ /* simulate the conversion here */
95*9701Slinton 			CONSZ val;
96*9701Slinton 			val = p->in.left->tn.lval;
97*9701Slinton 			switch( m ){
98*9701Slinton 			case CHAR:
99*9701Slinton 				p->in.left->tn.lval = (char) val;
100*9701Slinton 				break;
101*9701Slinton 			case UCHAR:
102*9701Slinton 				p->in.left->tn.lval = val & 0XFF;
103*9701Slinton 				break;
104*9701Slinton 			case USHORT:
105*9701Slinton 				p->in.left->tn.lval = val & 0XFFFFL;
106*9701Slinton 				break;
107*9701Slinton 			case SHORT:
108*9701Slinton 				p->in.left->tn.lval = (short)val;
109*9701Slinton 				break;
110*9701Slinton 			case UNSIGNED:
111*9701Slinton 				p->in.left->tn.lval = val & 0xFFFFFFFFL;
112*9701Slinton 				break;
113*9701Slinton 			case INT:
114*9701Slinton 				p->in.left->tn.lval = (int)val;
115*9701Slinton 				break;
116*9701Slinton 				}
117*9701Slinton 			p->in.left->in.type = m;
118*9701Slinton 			}
119*9701Slinton 		else {
120*9701Slinton 			/* meaningful ones are conversion of int to char, int to short,
121*9701Slinton 			   and short to char, and unsigned version of them */
122*9701Slinton 			if( m==CHAR || m==UCHAR ){
123*9701Slinton 				if( ml!=CHAR && ml!= UCHAR ) break;
124*9701Slinton 				}
125*9701Slinton 			else if( m==SHORT || m==USHORT ){
126*9701Slinton 				if( ml!=CHAR && ml!=UCHAR && ml!=SHORT && ml!=USHORT ) break;
127*9701Slinton 				}
128*9701Slinton 			}
129*9701Slinton 
130*9701Slinton 		/* clobber conversion */
131*9701Slinton 		if( tlen(p) == tlen(p->in.left) ) goto inherit;
132*9701Slinton 		p->in.op = FREE;
133*9701Slinton 		return( p->in.left );  /* conversion gets clobbered */
134*9701Slinton 
135*9701Slinton 	case PVCONV:
136*9701Slinton 	case PMCONV:
137*9701Slinton 		if( p->in.right->in.op != ICON ) cerror( "bad conversion", 0);
138*9701Slinton 		p->in.op = FREE;
139*9701Slinton 		return( buildtree( o==PMCONV?MUL:DIV, p->in.left, p->in.right ) );
140*9701Slinton 
141*9701Slinton 	case RS:
142*9701Slinton 	case ASG RS:
143*9701Slinton 		/* convert >> to << with negative shift count */
144*9701Slinton 		/* only if type of left operand is not unsigned */
145*9701Slinton 
146*9701Slinton 		if( ISUNSIGNED(p->in.left->in.type) ) break;
147*9701Slinton 		p->in.right = buildtree( UNARY MINUS, p->in.right, NIL );
148*9701Slinton 		if( p->in.op == RS ) p->in.op = LS;
149*9701Slinton 		else p->in.op = ASG LS;
150*9701Slinton 		break;
151*9701Slinton 
152*9701Slinton 	case FLD:
153*9701Slinton 		/* make sure that the second pass does not make the
154*9701Slinton 		   descendant of a FLD operator into a doubly indexed OREG */
155*9701Slinton 
156*9701Slinton 		if( p->in.left->in.op == UNARY MUL
157*9701Slinton 				&& (r=p->in.left->in.left)->in.op == PCONV)
158*9701Slinton 			if( r->in.left->in.op == PLUS || r->in.left->in.op == MINUS )
159*9701Slinton 				if( ISPTR(r->in.type) ) {
160*9701Slinton 					if( ISUNSIGNED(p->in.left->in.type) )
161*9701Slinton 						p->in.left->in.type = UCHAR;
162*9701Slinton 					else
163*9701Slinton 						p->in.left->in.type = CHAR;
164*9701Slinton 				}
165*9701Slinton 		break;
166*9701Slinton 		}
167*9701Slinton 
168*9701Slinton 	return(p);
169*9701Slinton 	}
170*9701Slinton 
171*9701Slinton andable( p ) NODE *p; {
172*9701Slinton 	return(1);  /* all names can have & taken on them */
173*9701Slinton 	}
174*9701Slinton 
175*9701Slinton cendarg(){ /* at the end of the arguments of a ftn, set the automatic offset */
176*9701Slinton 	autooff = AUTOINIT;
177*9701Slinton 	}
178*9701Slinton 
179*9701Slinton cisreg( t ) TWORD t; { /* is an automatic variable of type t OK for a register variable */
180*9701Slinton 
181*9701Slinton #ifdef TRUST_REG_CHAR_AND_REG_SHORT
182*9701Slinton 	if( t==INT || t==UNSIGNED || t==LONG || t==ULONG	/* tbl */
183*9701Slinton 		|| t==CHAR || t==UCHAR || t==SHORT 		/* tbl */
184*9701Slinton 		|| t==USHORT || ISPTR(t)) return(1);		/* tbl */
185*9701Slinton #else
186*9701Slinton 	if( t==INT || t==UNSIGNED || t==LONG || t==ULONG	/* wnj */
187*9701Slinton 		|| ISPTR(t)) return (1);			/* wnj */
188*9701Slinton #endif
189*9701Slinton 	return(0);
190*9701Slinton 	}
191*9701Slinton 
192*9701Slinton NODE *
193*9701Slinton offcon( off, t, d, s ) OFFSZ off; TWORD t; {
194*9701Slinton 
195*9701Slinton 	/* return a node, for structure references, which is suitable for
196*9701Slinton 	   being added to a pointer of type t, in order to be off bits offset
197*9701Slinton 	   into a structure */
198*9701Slinton 
199*9701Slinton 	register NODE *p;
200*9701Slinton 
201*9701Slinton 	/* t, d, and s are the type, dimension offset, and sizeoffset */
202*9701Slinton 	/* in general they  are necessary for offcon, but not on H'well */
203*9701Slinton 
204*9701Slinton 	p = bcon(0);
205*9701Slinton 	p->tn.lval = off/SZCHAR;
206*9701Slinton 	return(p);
207*9701Slinton 
208*9701Slinton 	}
209*9701Slinton 
210*9701Slinton 
211*9701Slinton static inwd	/* current bit offsed in word */;
212*9701Slinton static word	/* word being built from fields */;
213*9701Slinton 
214*9701Slinton incode( p, sz ) register NODE *p; {
215*9701Slinton 
216*9701Slinton 	/* generate initialization code for assigning a constant c
217*9701Slinton 		to a field of width sz */
218*9701Slinton 	/* we assume that the proper alignment has been obtained */
219*9701Slinton 	/* inoff is updated to have the proper final value */
220*9701Slinton 	/* we also assume sz  < SZINT */
221*9701Slinton 
222*9701Slinton 	if((sz+inwd) > SZINT) cerror("incode: field > int");
223*9701Slinton 	word |= ((unsigned)(p->tn.lval<<(32-sz))) >> (32-sz-inwd);
224*9701Slinton 	inwd += sz;
225*9701Slinton 	inoff += sz;
226*9701Slinton 	if(inoff%SZINT == 0) {
227*9701Slinton 		printf( "	.long	0x%x\n", word);
228*9701Slinton 		word = inwd = 0;
229*9701Slinton 		}
230*9701Slinton 	}
231*9701Slinton 
232*9701Slinton fincode( d, sz ) double d; {
233*9701Slinton 	/* output code to initialize space of size sz to the value d */
234*9701Slinton 	/* the proper alignment has been obtained */
235*9701Slinton 	/* inoff is updated to have the proper final value */
236*9701Slinton 	/* on the target machine, write it out in octal! */
237*9701Slinton 
238*9701Slinton 
239*9701Slinton 	printf("	%s	0%c%.20e\n", sz == SZDOUBLE ? ".double" : ".float",
240*9701Slinton 		sz == SZDOUBLE ? 'd' : 'f', d);
241*9701Slinton 	inoff += sz;
242*9701Slinton 	}
243*9701Slinton 
244*9701Slinton cinit( p, sz ) NODE *p; {
245*9701Slinton 	/* arrange for the initialization of p into a space of
246*9701Slinton 	size sz */
247*9701Slinton 	/* the proper alignment has been opbtained */
248*9701Slinton 	/* inoff is updated to have the proper final value */
249*9701Slinton 	ecode( p );
250*9701Slinton 	inoff += sz;
251*9701Slinton 	}
252*9701Slinton 
253*9701Slinton vfdzero( n ){ /* define n bits of zeros in a vfd */
254*9701Slinton 
255*9701Slinton 	if( n <= 0 ) return;
256*9701Slinton 
257*9701Slinton 	inwd += n;
258*9701Slinton 	inoff += n;
259*9701Slinton 	if( inoff%ALINT ==0 ) {
260*9701Slinton 		printf( "	.long	0x%x\n", word );
261*9701Slinton 		word = inwd = 0;
262*9701Slinton 		}
263*9701Slinton 	}
264*9701Slinton 
265*9701Slinton char *
266*9701Slinton exname( p ) char *p; {
267*9701Slinton 	/* make a name look like an external name in the local machine */
268*9701Slinton 
269*9701Slinton #ifndef FLEXNAMES
270*9701Slinton 	static char text[NCHNAM+1];
271*9701Slinton #else
272*9701Slinton 	static char text[BUFSIZ+1];
273*9701Slinton #endif
274*9701Slinton 
275*9701Slinton 	register i;
276*9701Slinton 
277*9701Slinton 	text[0] = '_';
278*9701Slinton #ifndef FLEXNAMES
279*9701Slinton 	for( i=1; *p&&i<NCHNAM; ++i ){
280*9701Slinton #else
281*9701Slinton 	for( i=1; *p; ++i ){
282*9701Slinton #endif
283*9701Slinton 		text[i] = *p++;
284*9701Slinton 		}
285*9701Slinton 
286*9701Slinton 	text[i] = '\0';
287*9701Slinton #ifndef FLEXNAMES
288*9701Slinton 	text[NCHNAM] = '\0';  /* truncate */
289*9701Slinton #endif
290*9701Slinton 
291*9701Slinton 	return( text );
292*9701Slinton 	}
293*9701Slinton 
294*9701Slinton ctype( type ){ /* map types which are not defined on the local machine */
295*9701Slinton 	switch( BTYPE(type) ){
296*9701Slinton 
297*9701Slinton 	case LONG:
298*9701Slinton 		MODTYPE(type,INT);
299*9701Slinton 		break;
300*9701Slinton 
301*9701Slinton 	case ULONG:
302*9701Slinton 		MODTYPE(type,UNSIGNED);
303*9701Slinton 		}
304*9701Slinton 	return( type );
305*9701Slinton 	}
306*9701Slinton 
307*9701Slinton noinit( t ) { /* curid is a variable which is defined but
308*9701Slinton 	is not initialized (and not a function );
309*9701Slinton 	This routine returns the stroage class for an uninitialized declaration */
310*9701Slinton 
311*9701Slinton 	return(EXTERN);
312*9701Slinton 
313*9701Slinton 	}
314*9701Slinton 
315*9701Slinton commdec( id ){ /* make a common declaration for id, if reasonable */
316*9701Slinton 	register struct symtab *q;
317*9701Slinton 	OFFSZ off, tsize();
318*9701Slinton 
319*9701Slinton 	q = &stab[id];
320*9701Slinton 	printf( "	.comm	%s,", exname( q->sname ) );
321*9701Slinton 	off = tsize( q->stype, q->dimoff, q->sizoff );
322*9701Slinton 	printf( CONFMT, off/SZCHAR );
323*9701Slinton 	printf( "\n" );
324*9701Slinton 	}
325*9701Slinton 
326*9701Slinton isitlong( cb, ce ){ /* is lastcon to be long or short */
327*9701Slinton 	/* cb is the first character of the representation, ce the last */
328*9701Slinton 
329*9701Slinton 	if( ce == 'l' || ce == 'L' ||
330*9701Slinton 		lastcon >= (1L << (SZINT-1) ) ) return (1);
331*9701Slinton 	return(0);
332*9701Slinton 	}
333*9701Slinton 
334*9701Slinton 
335*9701Slinton isitfloat( s ) char *s; {
336*9701Slinton 	double atof();
337*9701Slinton 	dcon = atof(s);
338*9701Slinton 	return( FCON );
339*9701Slinton 	}
340*9701Slinton 
341*9701Slinton ecode( p ) NODE *p; {
342*9701Slinton 
343*9701Slinton 	/* walk the tree and write out the nodes.. */
344*9701Slinton 
345*9701Slinton 	if( nerrors ) return;
346*9701Slinton 	p2tree( p );
347*9701Slinton 	p2compile( p );
348*9701Slinton 	}
349*9701Slinton 
350*9701Slinton #include <sys/types.h>
351*9701Slinton #include <a.out.h>
352*9701Slinton #include <stab.h>
353*9701Slinton extern int ddebug;
354*9701Slinton extern int gdebug;
355*9701Slinton 
356*9701Slinton fixarg(p)
357*9701Slinton struct symtab *p; {
358*9701Slinton 		pstab(p->sname, N_PSYM);
359*9701Slinton 		if (gdebug) printf("0,%d,%d\n", p->stype, argoff/SZCHAR);
360*9701Slinton 		poffs(p);
361*9701Slinton }
362*9701Slinton int	stabLCSYM;
363*9701Slinton 
364*9701Slinton outstab(p)
365*9701Slinton struct symtab *p; {
366*9701Slinton 	register TWORD ptype;
367*9701Slinton 	register char *pname;
368*9701Slinton 	register char pclass;
369*9701Slinton 	register int poffset;
370*9701Slinton 
371*9701Slinton 	if (!gdebug) return;
372*9701Slinton 
373*9701Slinton 	ptype = p->stype;
374*9701Slinton 	pname = p->sname;
375*9701Slinton 	pclass = p->sclass;
376*9701Slinton 	poffset = p->offset;
377*9701Slinton 
378*9701Slinton 	if (ISFTN(ptype)) {
379*9701Slinton 		return;
380*9701Slinton 	}
381*9701Slinton 
382*9701Slinton 	switch (pclass) {
383*9701Slinton 
384*9701Slinton 	case AUTO:
385*9701Slinton 		pstab(pname, N_LSYM);
386*9701Slinton 		printf("0,%d,%d\n", ptype, (-poffset)/SZCHAR);
387*9701Slinton 		poffs(p);
388*9701Slinton 		return;
389*9701Slinton 
390*9701Slinton 	case EXTDEF:
391*9701Slinton 	case EXTERN:
392*9701Slinton 		pstab(pname, N_GSYM);
393*9701Slinton 		printf("0,%d,0\n", ptype);
394*9701Slinton 		poffs(p);
395*9701Slinton 		return;
396*9701Slinton 
397*9701Slinton 	case STATIC:
398*9701Slinton #ifdef LCOMM
399*9701Slinton 		/* stabLCSYM is 1 during nidcl so we can get stab type right */
400*9701Slinton 		pstab(pname, stabLCSYM ? N_LCSYM : N_STSYM);
401*9701Slinton #else
402*9701Slinton 		pstab(pname, N_STSYM);
403*9701Slinton #endif
404*9701Slinton 		if (p->slevel > 1) {
405*9701Slinton 			printf("0,%d,L%d\n", ptype, poffset);
406*9701Slinton 		} else {
407*9701Slinton 			printf("0,%d,%s\n", ptype, exname(pname));
408*9701Slinton 		}
409*9701Slinton 		poffs(p);
410*9701Slinton 		return;
411*9701Slinton 
412*9701Slinton 	case REGISTER:
413*9701Slinton 		pstab(pname, N_RSYM);
414*9701Slinton 		printf("0,%d,%d\n", ptype, poffset);
415*9701Slinton 		poffs(p);
416*9701Slinton 		return;
417*9701Slinton 
418*9701Slinton 	case MOS:
419*9701Slinton 	case MOU:
420*9701Slinton 		pstab(pname, N_SSYM);
421*9701Slinton 		printf("0,%d,%d\n", ptype, poffset/SZCHAR);
422*9701Slinton 		poffs(p);
423*9701Slinton 		return;
424*9701Slinton 
425*9701Slinton 	case PARAM:
426*9701Slinton 		/* parameter stab entries are processed in dclargs() */
427*9701Slinton 		return;
428*9701Slinton 
429*9701Slinton 	default:
430*9701Slinton #ifndef FLEXNAMES
431*9701Slinton 		if (ddebug) printf("	No .stab for %.8s\n", pname);
432*9701Slinton #else
433*9701Slinton 		if (ddebug) printf("	No .stab for %s\n", pname);
434*9701Slinton #endif
435*9701Slinton 
436*9701Slinton 	}
437*9701Slinton }
438*9701Slinton 
439*9701Slinton pstab(name, type)
440*9701Slinton char *name;
441*9701Slinton int type; {
442*9701Slinton 	register int i;
443*9701Slinton 	register char c;
444*9701Slinton 	if (!gdebug) return;
445*9701Slinton 	/* locctr(PROG);  /* .stabs must appear in .text for c2 */
446*9701Slinton #ifdef ASSTRINGS
447*9701Slinton 	if ( name[0] == '\0')
448*9701Slinton 		printf("\t.stabn\t");
449*9701Slinton 	else
450*9701Slinton #ifndef FLEXNAMES
451*9701Slinton 		printf("\t.stabs\t\"%.8s\", ", name);
452*9701Slinton #else
453*9701Slinton 		printf("\t.stabs\t\"%s\", ", name);
454*9701Slinton #endif
455*9701Slinton #else
456*9701Slinton 	printf("	.stab	");
457*9701Slinton 	for(i=0; i<8; i++)
458*9701Slinton 		if (c = name[i]) printf("'%c,", c);
459*9701Slinton 		else printf("0,");
460*9701Slinton #endif
461*9701Slinton 	printf("0%o,", type);
462*9701Slinton }
463*9701Slinton 
464*9701Slinton #ifdef STABDOT
465*9701Slinton pstabdot(type, value)
466*9701Slinton 	int	type;
467*9701Slinton 	int	value;
468*9701Slinton {
469*9701Slinton 	if ( ! gdebug) return;
470*9701Slinton 	/* locctr(PROG);  /* .stabs must appear in .text for c2 */
471*9701Slinton 	printf("\t.stabd\t");
472*9701Slinton 	printf("0%o,0,0%o\n",type, value);
473*9701Slinton }
474*9701Slinton #endif
475*9701Slinton 
476*9701Slinton poffs(p)
477*9701Slinton register struct symtab *p; {
478*9701Slinton 	int s;
479*9701Slinton 	if (!gdebug) return;
480*9701Slinton 	if ((s = dimtab[p->sizoff]/SZCHAR) > 1) {
481*9701Slinton 		pstab(p->sname, N_LENG);
482*9701Slinton 		printf("1,0,%d\n", s);
483*9701Slinton 	}
484*9701Slinton }
485*9701Slinton 
486*9701Slinton extern char NULLNAME[8];
487*9701Slinton extern int  labelno;
488*9701Slinton extern int  fdefflag;
489*9701Slinton 
490*9701Slinton psline() {
491*9701Slinton 	static int lastlineno;
492*9701Slinton 	register char *cp, *cq;
493*9701Slinton 	register int i;
494*9701Slinton 
495*9701Slinton 	if (!gdebug) return;
496*9701Slinton 
497*9701Slinton 	cq = ititle;
498*9701Slinton 	cp = ftitle;
499*9701Slinton 
500*9701Slinton 	while ( *cq ) if ( *cp++ != *cq++ ) goto neq;
501*9701Slinton 	if ( *cp == '\0' ) goto eq;
502*9701Slinton 
503*9701Slinton neq:	for (i=0; i<100; i++)
504*9701Slinton 		ititle[i] = '\0';
505*9701Slinton 	cp = ftitle;
506*9701Slinton 	cq = ititle;
507*9701Slinton 	while ( *cp )
508*9701Slinton 		*cq++ = *cp++;
509*9701Slinton 	*cq = '\0';
510*9701Slinton 	*--cq = '\0';
511*9701Slinton #ifndef FLEXNAMES
512*9701Slinton 	for ( cp = ititle+1; *(cp-1); cp += 8 ) {
513*9701Slinton 		pstab(cp, N_SOL);
514*9701Slinton 		if (gdebug) printf("0,0,LL%d\n", labelno);
515*9701Slinton 		}
516*9701Slinton #else
517*9701Slinton 	pstab(ititle+1, N_SOL);
518*9701Slinton 	if (gdebug) printf("0,0,LL%d\n", labelno);
519*9701Slinton #endif
520*9701Slinton 	*cq = '"';
521*9701Slinton 	printf("LL%d:\n", labelno++);
522*9701Slinton 
523*9701Slinton eq:	if (lineno == lastlineno) return;
524*9701Slinton 	lastlineno = lineno;
525*9701Slinton 
526*9701Slinton 	if (fdefflag) {
527*9701Slinton #ifdef STABDOT
528*9701Slinton 		pstabdot(N_SLINE, lineno);
529*9701Slinton #else
530*9701Slinton 		pstab(NULLNAME, N_SLINE);
531*9701Slinton 		printf("0,%d,LL%d\n", lineno, labelno);
532*9701Slinton 		printf("LL%d:\n", labelno++);
533*9701Slinton #endif
534*9701Slinton 		}
535*9701Slinton 	}
536*9701Slinton 
537*9701Slinton plcstab(level) {
538*9701Slinton 	if (!gdebug) return;
539*9701Slinton #ifdef STABDOT
540*9701Slinton 	pstabdot(N_LBRAC, level);
541*9701Slinton #else
542*9701Slinton 	pstab(NULLNAME, N_LBRAC);
543*9701Slinton 	printf("0,%d,LL%d\n", level, labelno);
544*9701Slinton 	printf("LL%d:\n", labelno++);
545*9701Slinton #endif
546*9701Slinton 	}
547*9701Slinton 
548*9701Slinton prcstab(level) {
549*9701Slinton 	if (!gdebug) return;
550*9701Slinton #ifdef STABDOT
551*9701Slinton 	pstabdot(N_RBRAC, level);
552*9701Slinton #else
553*9701Slinton 	pstab(NULLNAME, N_RBRAC);
554*9701Slinton 	printf("0,%d,LL%d\n", level, labelno);
555*9701Slinton 	printf("LL%d:\n", labelno++);
556*9701Slinton #endif
557*9701Slinton 	}
558*9701Slinton 
559*9701Slinton pfstab(sname)
560*9701Slinton char *sname; {
561*9701Slinton 	if (!gdebug) return;
562*9701Slinton 	pstab(sname, N_FUN);
563*9701Slinton #ifndef FLEXNAMES
564*9701Slinton 	printf("0,%d,_%.7s\n", lineno, sname);
565*9701Slinton #else
566*9701Slinton 	printf("0,%d,_%s\n", lineno, sname);
567*9701Slinton #endif
568*9701Slinton }
569*9701Slinton 
570*9701Slinton #ifndef ONEPASS
571*9701Slinton tlen(p) NODE *p;
572*9701Slinton {
573*9701Slinton 	switch(p->in.type) {
574*9701Slinton 		case CHAR:
575*9701Slinton 		case UCHAR:
576*9701Slinton 			return(1);
577*9701Slinton 
578*9701Slinton 		case SHORT:
579*9701Slinton 		case USHORT:
580*9701Slinton 			return(2);
581*9701Slinton 
582*9701Slinton 		case DOUBLE:
583*9701Slinton 			return(8);
584*9701Slinton 
585*9701Slinton 		default:
586*9701Slinton 			return(4);
587*9701Slinton 		}
588*9701Slinton 	}
589*9701Slinton #endif
590