1/*	Id: init.c,v 1.78 2012/03/22 18:51:40 plunky Exp 	*/
2/*	$NetBSD: init.c,v 1.1.1.6 2012/03/26 14:26:48 plunky Exp $	*/
3
4/*
5 * Copyright (c) 2004, 2007 Anders Magnusson (ragge@ludd.ltu.se).
6 * All rights reserved.
7 *
8 * Redistribution and use in source and binary forms, with or without
9 * modification, are permitted provided that the following conditions
10 * are met:
11 * 1. Redistributions of source code must retain the above copyright
12 *    notice, this list of conditions and the following disclaimer.
13 * 2. Redistributions in binary form must reproduce the above copyright
14 *    notice, this list of conditions and the following disclaimer in the
15 *    documentation and/or other materials provided with the distribution.
16 * 3. The name of the author may not be used to endorse or promote products
17 *    derived from this software without specific prior written permission
18 *
19 * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
20 * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
21 * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
22 * IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
23 * INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
24 * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
25 * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
26 * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
27 * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
28 * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
29 */
30
31/*
32 * Copyright(C) Caldera International Inc. 2001-2002. All rights reserved.
33 *
34 * Redistribution and use in source and binary forms, with or without
35 * modification, are permitted provided that the following conditions
36 * are met:
37 *
38 * Redistributions of source code and documentation must retain the above
39 * copyright notice, this list of conditions and the following disclaimer.
40 * Redistributions in binary form must reproduce the above copyright
41 * notice, this list of conditions and the following disclaimer in the
42 * documentation and/or other materials provided with the distribution.
43 * All advertising materials mentioning features or use of this software
44 * must display the following acknowledgement:
45 * 	This product includes software developed or owned by Caldera
46 *	International, Inc.
47 * Neither the name of Caldera International, Inc. nor the names of other
48 * contributors may be used to endorse or promote products derived from
49 * this software without specific prior written permission.
50 *
51 * USE OF THE SOFTWARE PROVIDED FOR UNDER THIS LICENSE BY CALDERA
52 * INTERNATIONAL, INC. AND CONTRIBUTORS ``AS IS'' AND ANY EXPRESS OR
53 * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
54 * WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
55 * DISCLAIMED.  IN NO EVENT SHALL CALDERA INTERNATIONAL, INC. BE LIABLE
56 * FOR ANY DIRECT, INDIRECT INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
57 * DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
58 * OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
59 * HOWEVER CAUSED AND ON ANY THEORY OFLIABILITY, WHETHER IN CONTRACT,
60 * STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING
61 * IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
62 * POSSIBILITY OF SUCH DAMAGE.
63 */
64
65#include "pass1.h"
66#include <string.h>
67
68/*
69 * The following machine-dependent routines may be called during
70 * initialization:
71 *
72 * zbits(OFFSZ, int)	- sets int bits of zero at position OFFSZ.
73 * infld(CONSZ off, int fsz, CONSZ val)
74 *			- sets the bitfield val starting at off and size fsz.
75 * ninval(CONSZ off, int fsz, NODE *)
76 *			- prints an integer constant which may have
77 *			  a label associated with it, located at off and
78 *			  size fsz.
79 *
80 * Initialization may be of different kind:
81 * - Initialization at compile-time, all values are constants and laid
82 *   out in memory. Static or extern variables outside functions.
83 * - Initialization at run-time, written to their values as code.
84 *
85 * Currently run-time-initialized variables are only initialized by using
86 * move instructions.  An optimization might be to detect that it is
87 * initialized with constants and therefore copied from readonly memory.
88 */
89
90/*
91 * The base element(s) of an initialized variable is kept in a linked
92 * list, allocated while initialized.
93 *
94 * When a scalar is found, entries are popped of the instk until it's
95 * possible to find an entry for a new scalar; then onstk() is called
96 * to get the correct type and size of that scalar.
97 *
98 * If a right brace is found, pop the stack until a matching left brace
99 * were found while filling the elements with zeros.  This left brace is
100 * also marking where the current level is for designated initializations.
101 *
102 * Position entries are increased when traversing back down into the stack.
103 */
104
105/*
106 * Good-to-know entries from symtab:
107 *	soffset - # of bits from beginning of this structure.
108 */
109
110/*
111 * TO FIX:
112 * - Alignment of structs on like i386 char members.
113 */
114
115/*
116 * Struct used in array initialisation.
117 */
118static struct instk {
119	struct	instk *in_prev; /* linked list */
120	struct	symtab *in_lnk;	/* member in structure initializations */
121	struct	symtab *in_sym; /* symtab index */
122	union	dimfun *in_df;	/* dimenston of array */
123	TWORD	in_t;		/* type for this level */
124	int	in_n;		/* number of arrays seen so far */
125	int	in_fl;	/* flag which says if this level is controlled by {} */
126} *pstk, pbase;
127
128int doing_init, statinit;
129static struct symtab *csym;
130
131#ifdef PCC_DEBUG
132static void prtstk(struct instk *in);
133#endif
134
135/*
136 * Linked lists for initializations.
137 */
138struct ilist {
139	struct ilist *next;
140	CONSZ off;	/* bit offset of this entry */
141	int fsz;	/* bit size of this entry */
142	NODE *n;	/* node containing this data info */
143};
144
145struct llist {
146	SLIST_ENTRY(llist) next;
147	CONSZ begsz;	/* bit offset of this entry */
148	struct ilist *il;
149};
150static SLIST_HEAD(llh, llist) lpole;
151static CONSZ basesz;
152static int numents; /* # of array entries allocated */
153
154static struct initctx {
155	struct initctx *prev;
156	struct instk *pstk;
157	struct symtab *psym;
158	struct llh lpole;
159	CONSZ basesz;
160	int numents;
161} *inilnk;
162
163static struct ilist *
164getil(struct ilist *next, CONSZ b, int sz, NODE *n)
165{
166	struct ilist *il = tmpalloc(sizeof(struct ilist));
167
168	il->off = b;
169	il->fsz = sz;
170	il->n = n;
171	il->next = next;
172	return il;
173}
174
175/*
176 * Allocate a new struct defining a block of initializers appended to the
177 * end of the llist. Return that entry.
178 */
179static struct llist *
180getll(void)
181{
182	struct llist *ll;
183
184	ll = tmpalloc(sizeof(struct llist));
185	ll->begsz = numents * basesz;
186	ll->il = NULL;
187	SLIST_INSERT_LAST(&lpole, ll, next);
188	numents++;
189	return ll;
190}
191
192/*
193 * Return structure containing off bitnumber.
194 * Allocate more entries, if needed.
195 */
196static struct llist *
197setll(OFFSZ off)
198{
199	struct llist *ll = NULL;
200
201	/* Ensure that we have enough entries */
202	while (off >= basesz * numents)
203		 ll = getll();
204
205	if (ll != NULL && ll->begsz <= off && ll->begsz + basesz > off)
206		return ll;
207
208	SLIST_FOREACH(ll, &lpole, next)
209		if (ll->begsz <= off && ll->begsz + basesz > off)
210			break;
211	return ll; /* ``cannot fail'' */
212}
213char *astypnames[] = { 0, 0, "\t.byte", "\t.byte", "\t.short", "\t.short",
214	"\t.word", "\t.word", "\t.long", "\t.long", "\t.quad", "\t.quad",
215	"ERR", "ERR", "ERR",
216};
217
218void
219inval(CONSZ off, int fsz, NODE *p)
220{
221	struct symtab *sp;
222	CONSZ val;
223	TWORD t;
224
225	if (p->n_op != ICON && p->n_op != FCON) {
226		uerror("constant required");
227		return;
228	}
229	if (p->n_type == BOOL) {
230		if ((U_CONSZ)p->n_lval > 1)
231			p->n_lval = 1;
232		p->n_type = BOOL_TYPE;
233	}
234	if (ninval(off, fsz, p))
235		return; /* dealt with in local.c */
236	t = p->n_type;
237	if (t > BTMASK)
238		t = INTPTR;
239
240	val = (CONSZ)(p->n_lval & SZMASK(sztable[t]));
241	if (t <= ULONGLONG) {
242		sp = p->n_sp;
243		printf("%s ",astypnames[t]);
244		if (val || sp == NULL)
245			printf(CONFMT, val);
246		if (val && sp != NULL)
247			printf("+");
248		if (sp != NULL) {
249			if ((sp->sclass == STATIC && sp->slevel > 0)) {
250				printf(LABFMT, sp->soffset);
251			} else
252				printf("%s", sp->soname ?
253				    sp->soname : exname(sp->sname));
254		}
255		printf("\n");
256	} else
257		cerror("inval: unhandled type %d", (int)t);
258}
259
260#ifndef MYBFINIT
261
262static int inbits;
263static CONSZ xinval;
264/*
265 * Initialize a bitfield.
266 * XXX - use U_CONSZ?
267 */
268void
269infld(CONSZ off, int fsz, CONSZ val)
270{
271#ifdef PCC_DEBUG
272	if (idebug)
273		printf("infld off %lld, fsz %d, val %lld inbits %d\n",
274		    off, fsz, val, inbits);
275#endif
276	val &= SZMASK(fsz);
277#if TARGET_ENDIAN == TARGET_BE
278	while (fsz + inbits >= SZCHAR) {
279		int shsz = SZCHAR-inbits;
280		xinval = (xinval << shsz) | (val >> (fsz - shsz));
281		printf("%s " CONFMT "\n",
282		    astypnames[CHAR], xinval & SZMASK(SZCHAR));
283		fsz -= shsz;
284		val &= SZMASK(fsz);
285		xinval = inbits = 0;
286	}
287	if (fsz) {
288		xinval = (xinval << fsz) | val;
289		inbits += fsz;
290	}
291#else
292	while (fsz + inbits >= SZCHAR) {
293		int shsz = SZCHAR-inbits;
294		xinval |= (val << inbits);
295		printf("%s " CONFMT "\n",
296		    astypnames[CHAR], xinval & SZMASK(SZCHAR));
297		fsz -= shsz;
298		val >>= shsz;
299		xinval = inbits = 0;
300	}
301	if (fsz) {
302		xinval |= (val << inbits);
303		inbits += fsz;
304	}
305#endif
306}
307
308char *asspace = "\t.space";
309
310/*
311 * set fsz bits in sequence to zero.
312 */
313void
314zbits(OFFSZ off, int fsz)
315{
316	int m;
317
318#ifdef PCC_DEBUG
319	if (idebug)
320		printf("zbits off %lld, fsz %d inbits %d\n", off, fsz, inbits);
321#endif
322#if TARGET_ENDIAN == TARGET_BE
323	if ((m = (inbits % SZCHAR))) {
324		m = SZCHAR - m;
325		if (fsz < m) {
326			inbits += fsz;
327			xinval <<= fsz;
328			return;
329		} else {
330			fsz -= m;
331			xinval <<= m;
332			printf("%s " CONFMT "\n",
333			    astypnames[CHAR], xinval & SZMASK(SZCHAR));
334			xinval = inbits = 0;
335		}
336	}
337#else
338	if ((m = (inbits % SZCHAR))) {
339		m = SZCHAR - m;
340		if (fsz < m) {
341			inbits += fsz;
342			return;
343		} else {
344			fsz -= m;
345			printf("%s " CONFMT "\n",
346			    astypnames[CHAR], xinval & SZMASK(SZCHAR));
347			xinval = inbits = 0;
348		}
349	}
350#endif
351	if (fsz >= SZCHAR) {
352		printf("%s %d\n", asspace, fsz/SZCHAR);
353		fsz -= (fsz/SZCHAR) * SZCHAR;
354	}
355	if (fsz) {
356		xinval = 0;
357		inbits = fsz;
358	}
359}
360#endif
361
362/*
363 * beginning of initialization; allocate space to store initialized data.
364 * remember storage class for writeout in endinit().
365 * p is the newly declarated type.
366 */
367void
368beginit(struct symtab *sp)
369{
370	struct initctx *ict;
371	struct instk *is = &pbase;
372
373#ifdef PCC_DEBUG
374	if (idebug)
375		printf("beginit(%p), sclass %s\n", sp, scnames(sp->sclass));
376#endif
377
378	if (pstk) {
379#ifdef PCC_DEBUG
380		if (idebug)
381			printf("beginit: saving ctx pstk %p\n", pstk);
382#endif
383		/* save old context */
384		ict = tmpalloc(sizeof(struct initctx));
385		ict->prev = inilnk;
386		inilnk = ict;
387		ict->pstk = pstk;
388		ict->psym = csym;
389		ict->lpole = lpole;
390		ict->basesz = basesz;
391		ict->numents = numents;
392		is = tmpalloc(sizeof(struct instk));
393	}
394	csym = sp;
395
396	numents = 0; /* no entries in array list */
397	if (ISARY(sp->stype)) {
398		basesz = tsize(DECREF(sp->stype), sp->sdf+1, sp->sap);
399		if (basesz == 0) {
400			uerror("array has incomplete type");
401			basesz = SZINT;
402		}
403	} else
404		basesz = tsize(sp->stype, sp->sdf, sp->sap);
405	SLIST_INIT(&lpole);
406
407	/* first element */
408	if (ISSOU(sp->stype)) {
409		is->in_lnk = strmemb(sp->sap);
410	} else
411		is->in_lnk = NULL;
412	is->in_n = 0;
413	is->in_t = sp->stype;
414	is->in_sym = sp;
415	is->in_df = sp->sdf;
416	is->in_fl = 0;
417	is->in_prev = NULL;
418	pstk = is;
419	doing_init++;
420	if (sp->sclass == STATIC || sp->sclass == EXTDEF)
421		statinit++;
422}
423
424/*
425 * Push a new entry on the initializer stack.
426 * The new entry will be "decremented" to the new sub-type of the previous
427 * entry when called.
428 * Popping of entries is done elsewhere.
429 */
430static void
431stkpush(void)
432{
433	struct instk *is;
434	struct symtab *sq, *sp;
435	TWORD t;
436
437	if (pstk == NULL) {
438		sp = csym;
439		t = 0;
440	} else {
441		t = pstk->in_t;
442		sp = pstk->in_sym;
443	}
444
445#ifdef PCC_DEBUG
446	if (idebug) {
447		printf("stkpush: '%s' %s ", sp->sname, scnames(sp->sclass));
448		tprint(stdout, t, 0);
449	}
450#endif
451
452	/*
453	 * Figure out what the next initializer will be, and push it on
454	 * the stack.  If this is an array, just decrement type, if it
455	 * is a struct or union, extract the next element.
456	 */
457	is = tmpalloc(sizeof(struct instk));
458	is->in_fl = 0;
459	is->in_n = 0;
460	if (pstk == NULL) {
461		/* stack empty */
462		is->in_lnk = ISSOU(sp->stype) ? strmemb(sp->sap) : NULL;
463		is->in_t = sp->stype;
464		is->in_sym = sp;
465		is->in_df = sp->sdf;
466	} else if (ISSOU(t)) {
467		sq = pstk->in_lnk;
468		if (sq == NULL) {
469			uerror("excess of initializing elements");
470		} else {
471			is->in_lnk = ISSOU(sq->stype) ? strmemb(sq->sap) : NULL;
472			is->in_t = sq->stype;
473			is->in_sym = sq;
474			is->in_df = sq->sdf;
475		}
476	} else if (ISARY(t)) {
477		is->in_lnk = ISSOU(DECREF(t)) ? strmemb(pstk->in_sym->sap) : 0;
478		is->in_t = DECREF(t);
479		is->in_sym = sp;
480		if (pstk->in_df->ddim != NOOFFSET && pstk->in_df->ddim &&
481		    pstk->in_n >= pstk->in_df->ddim) {
482			werror("excess of initializing elements");
483			pstk->in_n--;
484		}
485		is->in_df = pstk->in_df+1;
486	} else
487		uerror("too many left braces");
488	is->in_prev = pstk;
489	pstk = is;
490
491#ifdef PCC_DEBUG
492	if (idebug) {
493		printf(" newtype ");
494		tprint(stdout, is->in_t, 0);
495		printf("\n");
496	}
497#endif
498}
499
500/*
501 * pop down to either next level that can handle a new initializer or
502 * to the next braced level.
503 */
504static void
505stkpop(void)
506{
507#ifdef PCC_DEBUG
508	if (idebug)
509		printf("stkpop\n");
510#endif
511	for (; pstk; pstk = pstk->in_prev) {
512		if (pstk->in_t == STRTY && pstk->in_lnk != NULL) {
513			pstk->in_lnk = pstk->in_lnk->snext;
514			if (pstk->in_lnk != NULL)
515				break;
516		}
517		if (ISSOU(pstk->in_t) && pstk->in_fl)
518			break; /* need } */
519		if (ISARY(pstk->in_t)) {
520			pstk->in_n++;
521			if (pstk->in_fl)
522				break;
523			if (pstk->in_df->ddim == NOOFFSET ||
524			    pstk->in_n < pstk->in_df->ddim)
525				break; /* ger more elements */
526		}
527	}
528#ifdef PCC_DEBUG
529	if (idebug > 1)
530		prtstk(pstk);
531#endif
532}
533
534/*
535 * Count how many elements an array may consist of.
536 */
537static int
538acalc(struct instk *is, int n)
539{
540	if (is == NULL || !ISARY(is->in_t))
541		return 0;
542	return acalc(is->in_prev, n * is->in_df->ddim) + n * is->in_n;
543}
544
545/*
546 * Find current bit offset of the top element on the stack from
547 * the beginning of the aggregate.
548 */
549static CONSZ
550findoff(void)
551{
552	struct instk *is;
553	OFFSZ off;
554
555#ifdef PCC_DEBUG
556	if (ISARY(pstk->in_t))
557		cerror("findoff on bad type %x", pstk->in_t);
558#endif
559
560	/*
561	 * Offset calculations. If:
562	 * - previous type is STRTY, soffset has in-struct offset.
563	 * - this type is ARY, offset is ninit*stsize.
564	 */
565	for (off = 0, is = pstk; is; is = is->in_prev) {
566		if (is->in_prev && is->in_prev->in_t == STRTY)
567			off += is->in_sym->soffset;
568		if (ISARY(is->in_t)) {
569			/* suesize is the basic type, so adjust */
570			TWORD t = is->in_t;
571			OFFSZ o;
572			while (ISARY(t))
573				t = DECREF(t);
574			if (ISPTR(t)) {
575				o = SZPOINT(t); /* XXX use tsize() */
576			} else {
577				o = tsize(t, is->in_sym->sdf, is->in_sym->sap);
578			}
579			off += o * acalc(is, 1);
580			while (is->in_prev && ISARY(is->in_prev->in_t)) {
581				if (is->in_prev->in_prev &&
582				    is->in_prev->in_prev->in_t == STRTY)
583					off += is->in_sym->soffset;
584				is = is->in_prev;
585			}
586		}
587	}
588#ifdef PCC_DEBUG
589	if (idebug>1) {
590		printf("findoff: off %lld\n", off);
591		prtstk(pstk);
592	}
593#endif
594	return off;
595}
596
597/*
598 * Insert the node p with size fsz at position off.
599 * Bit fields are already dealt with, so a node of correct type
600 * with correct alignment and correct bit offset is given.
601 */
602static void
603nsetval(CONSZ off, int fsz, NODE *p)
604{
605	struct llist *ll;
606	struct ilist *il;
607
608	if (idebug>1)
609		printf("setval: off %lld fsz %d p %p\n", off, fsz, p);
610
611	if (fsz == 0)
612		return;
613
614	ll = setll(off);
615	off -= ll->begsz;
616	if (ll->il == NULL) {
617		ll->il = getil(NULL, off, fsz, p);
618	} else {
619		il = ll->il;
620		if (il->off > off) {
621			ll->il = getil(ll->il, off, fsz, p);
622		} else {
623			for (il = ll->il; il->next; il = il->next)
624				if (il->off <= off && il->next->off > off)
625					break;
626			if (il->off == off) {
627				/* replace */
628				nfree(il->n);
629				il->n = p;
630			} else
631				il->next = getil(il->next, off, fsz, p);
632		}
633	}
634}
635
636/*
637 * take care of generating a value for the initializer p
638 * inoff has the current offset (last bit written)
639 * in the current word being generated
640 * Returns the offset.
641 */
642CONSZ
643scalinit(NODE *p)
644{
645	CONSZ woff;
646	NODE *q;
647	int fsz;
648
649#ifdef PCC_DEBUG
650	if (idebug > 2) {
651		printf("scalinit(%p)\n", p);
652		fwalk(p, eprint, 0);
653		prtstk(pstk);
654	}
655#endif
656
657	if (nerrors)
658		return 0;
659
660	p = optim(p);
661
662#ifdef notdef /* leave to the target to decide if useable */
663	if (csym->sclass != AUTO && p->n_op != ICON &&
664	    p->n_op != FCON && p->n_op != NAME)
665		cerror("scalinit not leaf");
666#endif
667
668	/* Out of elements? */
669	if (pstk == NULL) {
670		uerror("excess of initializing elements");
671		return 0;
672	}
673
674	/*
675	 * Get to the simple type if needed.
676	 */
677	while (ISSOU(pstk->in_t) || ISARY(pstk->in_t)) {
678		stkpush();
679		/* If we are doing auto struct init */
680		if (ISSOU(pstk->in_t) && ISSOU(p->n_type) &&
681		    suemeq(pstk->in_sym->sap, p->n_ap))
682			break;
683	}
684
685	if (ISSOU(pstk->in_t) == 0) {
686		/* let buildtree do typechecking (and casting) */
687		q = block(NAME, NIL,NIL, pstk->in_t, pstk->in_df,
688		    pstk->in_sym->sap);
689		p = buildtree(ASSIGN, q, p);
690		nfree(p->n_left);
691		q = p->n_right;
692		nfree(p);
693	} else
694		q = p;
695#ifndef WORD_ADDRESSED
696	if (csym->sclass != AUTO)
697		q = rmpconv(optim(rmpconv(q)));
698#endif
699	q = optim(q);
700
701	woff = findoff();
702
703	/* bitfield sizes are special */
704	if (pstk->in_sym->sclass & FIELD)
705		fsz = -(pstk->in_sym->sclass & FLDSIZ);
706	else
707		fsz = (int)tsize(pstk->in_t, pstk->in_sym->sdf,
708		    pstk->in_sym->sap);
709
710	nsetval(woff, fsz, q);
711
712	stkpop();
713#ifdef PCC_DEBUG
714	if (idebug > 2) {
715		printf("scalinit e(%p)\n", q);
716	}
717#endif
718	return woff;
719}
720
721/*
722 * Generate code to insert a value into a bitfield.
723 */
724static void
725insbf(OFFSZ off, int fsz, int val)
726{
727	struct symtab sym;
728	NODE *p, *r;
729	TWORD typ;
730
731#ifdef PCC_DEBUG
732	if (idebug > 1)
733		printf("insbf: off %lld fsz %d val %d\n", off, fsz, val);
734#endif
735
736	if (fsz == 0)
737		return;
738
739	/* small opt: do char instead of bf asg */
740	if ((off & (ALCHAR-1)) == 0 && fsz == SZCHAR)
741		typ = CHAR;
742	else
743		typ = INT;
744	/* Fake a struct reference */
745	p = buildtree(ADDROF, nametree(csym), NIL);
746	sym.stype = typ;
747	sym.squal = 0;
748	sym.sdf = 0;
749	sym.sap = NULL;
750	sym.soffset = (int)off;
751	sym.sclass = (char)(typ == INT ? FIELD | fsz : MOU);
752	r = xbcon(0, &sym, typ);
753	p = block(STREF, p, r, INT, 0, 0);
754	ecomp(buildtree(ASSIGN, stref(p), bcon(val)));
755}
756
757/*
758 * Clear a bitfield, starting at off and size fsz.
759 */
760static void
761clearbf(OFFSZ off, OFFSZ fsz)
762{
763	/* Pad up to the next even initializer */
764	if ((off & (ALCHAR-1)) || (fsz < SZCHAR)) {
765		int ba = (int)(((off + (SZCHAR-1)) & ~(SZCHAR-1)) - off);
766		if (ba > fsz)
767			ba = (int)fsz;
768		insbf(off, ba, 0);
769		off += ba;
770		fsz -= ba;
771	}
772	while (fsz >= SZCHAR) {
773		insbf(off, SZCHAR, 0);
774		off += SZCHAR;
775		fsz -= SZCHAR;
776	}
777	if (fsz)
778		insbf(off, fsz, 0);
779}
780
781/*
782 * final step of initialization.
783 * print out init nodes and generate copy code (if needed).
784 */
785void
786endinit(int seg)
787{
788	struct llist *ll;
789	struct ilist *il;
790	int fsz;
791	OFFSZ lastoff, tbit;
792
793#ifdef PCC_DEBUG
794	if (idebug)
795		printf("endinit()\n");
796#endif
797
798	/* Calculate total block size */
799	if (ISARY(csym->stype) && csym->sdf->ddim == NOOFFSET) {
800		tbit = numents*basesz; /* open-ended arrays */
801		csym->sdf->ddim = numents;
802		if (csym->sclass == AUTO) { /* Get stack space */
803			csym->soffset = NOOFFSET;
804			oalloc(csym, &autooff);
805		}
806	} else
807		tbit = tsize(csym->stype, csym->sdf, csym->sap);
808
809	/* Setup symbols */
810	if (csym->sclass != AUTO) {
811		locctr(seg ? UDATA : DATA, csym);
812		defloc(csym);
813	}
814
815	/* Traverse all entries and print'em out */
816	lastoff = 0;
817	SLIST_FOREACH(ll, &lpole, next) {
818		for (il = ll->il; il; il = il->next) {
819#ifdef PCC_DEBUG
820			if (idebug > 1) {
821				printf("off %lld size %d val %lld type ",
822				    ll->begsz+il->off, il->fsz, il->n->n_lval);
823				tprint(stdout, il->n->n_type, 0);
824				printf("\n");
825			}
826#endif
827			fsz = il->fsz;
828			if (csym->sclass == AUTO) {
829				struct symtab sym;
830				NODE *p, *r, *n;
831
832				if (ll->begsz + il->off > lastoff)
833					clearbf(lastoff,
834					    (ll->begsz + il->off) - lastoff);
835
836				/* Fake a struct reference */
837				p = buildtree(ADDROF, nametree(csym), NIL);
838				n = il->n;
839				sym.stype = n->n_type;
840				sym.squal = n->n_qual;
841				sym.sdf = n->n_df;
842				sym.sap = n->n_ap;
843				sym.soffset = (int)(ll->begsz + il->off);
844				sym.sclass = (char)(fsz < 0 ? FIELD | -fsz : 0);
845				r = xbcon(0, &sym, INT);
846				p = block(STREF, p, r, INT, 0, 0);
847				ecomp(buildtree(ASSIGN, stref(p), il->n));
848				if (fsz < 0)
849					fsz = -fsz;
850
851			} else {
852				if (ll->begsz + il->off > lastoff)
853					zbits(lastoff,
854					    (ll->begsz + il->off) - lastoff);
855				if (fsz < 0) {
856					fsz = -fsz;
857					infld(il->off, fsz, il->n->n_lval);
858				} else
859					inval(il->off, fsz, il->n);
860				tfree(il->n);
861			}
862			lastoff = ll->begsz + il->off + fsz;
863		}
864	}
865	if (csym->sclass == AUTO) {
866		clearbf(lastoff, tbit-lastoff);
867	} else
868		zbits(lastoff, tbit-lastoff);
869
870	doing_init--;
871	if (csym->sclass == STATIC || csym->sclass == EXTDEF)
872		statinit--;
873	endictx();
874}
875
876void
877endictx(void)
878{
879	struct initctx *ict = inilnk;
880
881	if (ict == NULL)
882		return;
883
884	pstk = ict->pstk;
885	csym = ict->psym;
886	lpole = ict->lpole;
887	basesz = ict->basesz;
888	numents = ict->numents;
889	inilnk = inilnk->prev;
890#ifdef PCC_DEBUG
891	if (idebug)
892		printf("endinit: restoring ctx pstk %p\n", pstk);
893#endif
894}
895
896/*
897 * process an initializer's left brace
898 */
899void
900ilbrace()
901{
902
903#ifdef PCC_DEBUG
904	if (idebug)
905		printf("ilbrace()\n");
906#endif
907
908	if (pstk == NULL)
909		return;
910
911	stkpush();
912	pstk->in_fl = 1; /* mark lbrace */
913#ifdef PCC_DEBUG
914	if (idebug > 1)
915		prtstk(pstk);
916#endif
917}
918
919/*
920 * called when a '}' is seen
921 */
922void
923irbrace()
924{
925#ifdef PCC_DEBUG
926	if (idebug)
927		printf("irbrace()\n");
928	if (idebug > 2)
929		prtstk(pstk);
930#endif
931
932	if (pstk == NULL)
933		return;
934
935	/* Got right brace, search for corresponding in the stack */
936	for (; pstk->in_prev != NULL; pstk = pstk->in_prev) {
937		if(!pstk->in_fl)
938			continue;
939
940		/* we have one now */
941
942		pstk->in_fl = 0;  /* cancel { */
943		if (ISARY(pstk->in_t))
944			pstk->in_n = pstk->in_df->ddim;
945		else if (pstk->in_t == STRTY) {
946			while (pstk->in_lnk != NULL &&
947			    pstk->in_lnk->snext != NULL)
948				pstk->in_lnk = pstk->in_lnk->snext;
949		}
950		stkpop();
951		return;
952	}
953}
954
955/*
956 * Create a new init stack based on given elements.
957 */
958static void
959mkstack(NODE *p)
960{
961
962#ifdef PCC_DEBUG
963	if (idebug) {
964		printf("mkstack: %p\n", p);
965		if (idebug > 1 && p)
966			fwalk(p, eprint, 0);
967	}
968#endif
969
970	if (p == NULL)
971		return;
972	mkstack(p->n_left);
973
974	switch (p->n_op) {
975	case LB: /* Array index */
976		if (p->n_right->n_op != ICON)
977			cerror("mkstack");
978		if (!ISARY(pstk->in_t))
979			uerror("array indexing non-array");
980		pstk->in_n = (int)p->n_right->n_lval;
981		nfree(p->n_right);
982		break;
983
984	case NAME:
985		if (pstk->in_lnk) {
986			for (; pstk->in_lnk; pstk->in_lnk = pstk->in_lnk->snext)
987				if (pstk->in_lnk->sname == (char *)p->n_sp)
988					break;
989			if (pstk->in_lnk == NULL)
990				uerror("member missing");
991		} else {
992			uerror("not a struct/union");
993		}
994		break;
995	default:
996		cerror("mkstack2");
997	}
998	nfree(p);
999	stkpush();
1000
1001}
1002
1003/*
1004 * Initialize a specific element, as per C99.
1005 */
1006void
1007desinit(NODE *p)
1008{
1009	int op = p->n_op;
1010
1011	if (pstk == NULL)
1012		stkpush(); /* passed end of array */
1013	while (pstk->in_prev && pstk->in_fl == 0)
1014		pstk = pstk->in_prev; /* Empty stack */
1015
1016	if (ISSOU(pstk->in_t))
1017		pstk->in_lnk = strmemb(pstk->in_sym->sap);
1018
1019	mkstack(p);	/* Setup for assignment */
1020
1021	/* pop one step if SOU, ilbrace will push */
1022	if (op == NAME || op == LB)
1023		pstk = pstk->in_prev;
1024
1025#ifdef PCC_DEBUG
1026	if (idebug > 1) {
1027		printf("desinit e\n");
1028		prtstk(pstk);
1029	}
1030#endif
1031}
1032
1033/*
1034 * Convert a string to an array of char/wchar for asginit.
1035 */
1036static void
1037strcvt(NODE *p)
1038{
1039	NODE *q = p;
1040	char *s;
1041	int i;
1042
1043#ifdef mach_arm
1044	/* XXX */
1045	if (p->n_op == UMUL && p->n_left->n_op == ADDROF)
1046		p = p->n_left->n_left;
1047#endif
1048
1049	for (s = p->n_sp->sname; *s != 0; ) {
1050		if (*s++ == '\\') {
1051			i = esccon(&s);
1052		} else
1053			i = (unsigned char)s[-1];
1054		asginit(bcon(i));
1055	}
1056	tfree(q);
1057}
1058
1059/*
1060 * Do an assignment to a struct element.
1061 */
1062void
1063asginit(NODE *p)
1064{
1065	int g;
1066
1067#ifdef PCC_DEBUG
1068	if (idebug)
1069		printf("asginit %p\n", p);
1070	if (idebug > 1 && p)
1071		fwalk(p, eprint, 0);
1072#endif
1073
1074	/* convert string to array of char/wchar */
1075	if (p && (DEUNSIGN(p->n_type) == ARY+CHAR ||
1076	    p->n_type == ARY+WCHAR_TYPE)) {
1077		struct instk *is;
1078		TWORD t;
1079
1080		t = p->n_type == ARY+WCHAR_TYPE ? ARY+WCHAR_TYPE : ARY+CHAR;
1081		/*
1082		 * ...but only if next element is ARY+CHAR, otherwise
1083		 * just fall through.
1084		 */
1085
1086		/* HACKHACKHACK */
1087		is = pstk;
1088
1089		if (pstk == NULL)
1090			stkpush();
1091		while (ISSOU(pstk->in_t) || ISARY(pstk->in_t))
1092			stkpush();
1093		if (pstk->in_prev &&
1094		    (DEUNSIGN(pstk->in_prev->in_t) == t ||
1095		    pstk->in_prev->in_t == t)) {
1096			pstk = pstk->in_prev;
1097			if ((g = pstk->in_fl) == 0)
1098				pstk->in_fl = 1; /* simulate ilbrace */
1099
1100			strcvt(p);
1101			if (g == 0)
1102				irbrace(); /* will fill with zeroes */
1103			return;
1104		} else
1105			pstk = is; /* no array of char */
1106		/* END HACKHACKHACK */
1107	}
1108
1109	if (p == NULL) { /* only end of compound stmt */
1110		irbrace();
1111	} else /* assign next element */
1112		scalinit(p);
1113}
1114
1115#ifdef PCC_DEBUG
1116void
1117prtstk(struct instk *in)
1118{
1119	int i, o = 0;
1120
1121	printf("init stack:\n");
1122	for (; in != NULL; in = in->in_prev) {
1123		for (i = 0; i < o; i++)
1124			printf("  ");
1125		printf("%p) '%s' ", in, in->in_sym->sname);
1126		tprint(stdout, in->in_t, 0);
1127		printf(" %s ", scnames(in->in_sym->sclass));
1128		if (in->in_df /* && in->in_df->ddim */)
1129		    printf("arydim=%d ", in->in_df->ddim);
1130		printf("ninit=%d ", in->in_n);
1131		if (BTYPE(in->in_t) == STRTY || ISARY(in->in_t))
1132			printf("stsize=%d ",
1133			    (int)tsize(in->in_t, in->in_df, in->in_sym->sap));
1134		if (in->in_fl) printf("{ ");
1135		printf("soff=%d ", in->in_sym->soffset);
1136		if (in->in_t == STRTY) {
1137			if (in->in_lnk)
1138				printf("curel %s ", in->in_lnk->sname);
1139			else
1140				printf("END struct");
1141		}
1142		printf("\n");
1143		o++;
1144	}
1145}
1146#endif
1147
1148/*
1149 * Do a simple initialization.
1150 * At block 0, just print out the value, at higher levels generate
1151 * appropriate code.
1152 */
1153void
1154simpleinit(struct symtab *sp, NODE *p)
1155{
1156	NODE *q, *r, *nt;
1157	TWORD t;
1158	int sz;
1159
1160	/* May be an initialization of an array of char by a string */
1161	if ((DEUNSIGN(p->n_type) == ARY+CHAR &&
1162	    DEUNSIGN(sp->stype) == ARY+CHAR) ||
1163	    (DEUNSIGN(p->n_type) == DEUNSIGN(ARY+WCHAR_TYPE) &&
1164	    DEUNSIGN(sp->stype) == DEUNSIGN(ARY+WCHAR_TYPE))) {
1165		/* Handle "aaa" as { 'a', 'a', 'a' } */
1166		beginit(sp);
1167		strcvt(p);
1168		if (csym->sdf->ddim == NOOFFSET)
1169			scalinit(bcon(0)); /* Null-term arrays */
1170		endinit(0);
1171		return;
1172	}
1173
1174	nt = nametree(sp);
1175	switch (sp->sclass) {
1176	case STATIC:
1177	case EXTDEF:
1178		q = nt;
1179		locctr(DATA, sp);
1180		defloc(sp);
1181#ifndef NO_COMPLEX
1182		if (ANYCX(q) || ANYCX(p)) {
1183			r = cxop(ASSIGN, q, p);
1184			/* XXX must unwind the code generated here */
1185			/* We can rely on correct code generated */
1186			p = r->n_left->n_right->n_left;
1187			r->n_left->n_right->n_left = bcon(0);
1188			tfree(r);
1189			r = p->n_left->n_right;
1190			sz = (int)tsize(r->n_type, r->n_df, r->n_ap);
1191			inval(0, sz, r);
1192			inval(0, sz, p->n_right->n_right);
1193			tfree(p);
1194			break;
1195		}
1196#endif
1197		p = optim(buildtree(ASSIGN, nt, p));
1198#ifndef WORD_ADDRESSED
1199		p = optim(rmpconv(p));
1200#endif
1201		q = p->n_right;
1202		t = q->n_type;
1203		sz = (int)tsize(t, q->n_df, q->n_ap);
1204		inval(0, sz, q);
1205		tfree(p);
1206		break;
1207
1208	case AUTO:
1209	case REGISTER:
1210		if (ISARY(sp->stype))
1211			cerror("no array init");
1212		q = nt;
1213#ifndef NO_COMPLEX
1214
1215		if (ANYCX(q) || ANYCX(p))
1216			r = cxop(ASSIGN, q, p);
1217		else
1218#endif
1219			r = buildtree(ASSIGN, q, p);
1220		ecomp(r);
1221		break;
1222
1223	default:
1224		uerror("illegal initialization");
1225	}
1226}
1227