1: /*
2: * Copyright (c) 1982 Regents of the University of California.
3: * All rights reserved. The Berkeley software License Agreement
4: * specifies the terms and conditions for redistribution.
5: */
6:
7: #ifndef lint
8: static char sccsid[] = "@(#)assyms.c 5.1 (Berkeley) 4/30/85";
9: #endif not lint
10:
11: #include <stdio.h>
12: #include <ctype.h>
13: #include "as.h"
14: #include "asscan.h"
15: #include "assyms.h"
16:
17: /*
18: * Managers for chunks of symbols allocated from calloc()
19: * We maintain a linked list of such chunks.
20: *
21: */
22: struct allocbox *allochead; /*head of chunk list*/
23: struct allocbox *alloctail; /*tail*/
24: struct allocbox *newbox; /*for creating a new chunk*/
25: struct symtab *nextsym; /*next symbol free*/
26: int symsleft; /*slots left in current chunk*/
27:
28: struct symtab **symptrs;
29: struct symtab **symdelim[NLOC + NLOC +1];
30: struct symtab **symptrub;
31: /*
32: * Managers for the dynamically extendable hash table
33: */
34: struct hashdallop *htab;
35:
36: Iptr *itab[NINST]; /*maps opcodes to instructions*/
37: /*
38: * Counts what went into the symbol table, so that the
39: * size of the symbol table can be computed.
40: */
41: int nsyms; /* total number in the symbol table */
42: int njxxx; /* number of jxxx entrys */
43: int nforgotten; /* number of symbols erroneously entered */
44: int nlabels; /* number of label entries */
45:
46: /*
47: * Managers of the symbol literal storage.
48: */
49: struct strpool *strplhead = 0;
50:
51: symtabinit()
52: {
53: allochead = 0;
54: alloctail = 0;
55: nextsym = 0;
56: symsleft = 0;
57: strpoolalloc(); /* get the first strpool storage area */
58: htab = 0;
59: htaballoc(); /* get the first part of the hash table */
60: }
61:
62: /*
63: * Install all known instructions in the symbol table
64: */
65: syminstall()
66: {
67: register Iptr ip;
68: register struct symtab **hp;
69: register char *p1, *p2;
70: register int i;
71:
72: for (i = 0; i < NINST; i++)
73: itab[i] = (Iptr*)BADPOINT;
74:
75: for (ip = (Iptr)instab; FETCHNAME(ip)[0]; ip++) {
76: p1 = FETCHNAME(ip);
77: p2 = yytext;
78: while (*p2++ = *p1++);
79: hp = lookup(0); /* 0 => don't install this*/
80: if (*hp==NULL) {
81: *hp = (struct symtab *)ip;
82: if ( (ip->s_tag!=INSTn)
83: && (ip->s_tag!=INST0)
84: && (ip->s_tag!=0))
85: continue; /* was pseudo-op */
86: if (itab[ip->i_eopcode] == (Iptr*)BADPOINT){
87: itab[ip->i_eopcode] =
88: (Iptr*)ClearCalloc(256, sizeof(Iptr));
89: for (i = 0; i < 256; i++)
90: itab[ip->i_eopcode][i] =
91: (Iptr)BADPOINT;
92: }
93: itab[ip->i_eopcode][ip->i_popcode] = ip;
94: }
95: }
96: } /*end of syminstall*/
97:
98: #define ISLABEL(sp) \
99: ( (!savelabels) \
100: && (sp->s_tag == LABELID) \
101: && (STRPLACE(sp) & STR_CORE) \
102: && (FETCHNAME(sp)[0] == 'L'))
103: /*
104: * Assign final values to symbols,
105: * and overwrite the index field with its relative position in
106: * the symbol table we give to the loader.
107: */
108: extern struct exec hdr;
109:
110: freezesymtab()
111: {
112: register struct symtab *sp;
113: long bs;
114: register int relpos = 0;
115: register struct symtab *ubsp;
116: register struct allocbox *allocwalk;
117:
118: DECLITERATE(allocwalk, sp, ubsp)
119: {
120: if (sp->s_tag >= IGNOREBOUND)
121: continue; /*totally ignore jxxx entries */
122: /*
123: * Ignore stabs, but give them a symbol table index
124: */
125: if (sp->s_type & STABFLAG)
126: goto assignindex;
127: if ((sp->s_type&XTYPE)==XUNDEF)
128: sp->s_type = XXTRN+XUNDEF;
129: else if ((sp->s_type&XTYPE)==XDATA)
130: sp->s_value += usedot[sp->s_index].e_xvalue;
131: else if ((sp->s_type&XTYPE)==XTEXT)
132: sp->s_value += usedot[sp->s_index].e_xvalue;
133: else if ((sp->s_type&XTYPE)==XBSS) {
134: bs = sp->s_value;
135: sp->s_value = hdr.a_bss + datbase;
136: hdr.a_bss += bs;
137: }
138: assignindex:
139: if (!ISLABEL(sp))
140: sp->s_index = relpos++;
141: }
142: }
143:
144: /*
145: * For all of the stabs that had their final value undefined during pass 1
146: * and during pass 2 assign a final value.
147: * We have already given stab entrys a initial approximation
148: * when we constsructed the sorted symbol table.
149: * Iteration order doesn't matter.
150: */
151:
152: stabfix()
153: {
154: register struct symtab *sp, **cosp;
155: register struct symtab *p;
156:
157: SYMITERATE(cosp, sp){
158: if(sp->s_ptype && (sp->s_type & STABFLAG)) {
159: p = sp->s_dest;
160: /*
161: * STABFLOATING indicates that the offset has been saved in s_desc, s_other
162: */
163: if(sp->s_tag == STABFLOATING) {
164: sp->s_value = ( ( ((unsigned char) sp->s_other) << 16) | ( (unsigned short) sp->s_desc ) );
165: sp->s_value = sp->s_value + p->s_value;
166: }
167: else sp->s_value = p->s_value;
168: sp->s_index = p->s_index;
169: sp->s_type = p->s_type;
170:
171:
172: }
173: }
174: }
175:
176: char *Calloc(number, size)
177: int number, size;
178: {
179: register char *newstuff;
180: char *sbrk();
181: newstuff = sbrk(number*size);
182: if ((int)newstuff == -1){
183: yyerror("Ran out of Memory");
184: delexit();
185: }
186: return(newstuff);
187: }
188:
189: char *ClearCalloc(number, size)
190: int number, size;
191: {
192: register char *newstuff; /* r11 */
193: register int length = number * size; /* r10 */
194: #ifdef lint
195: length = length;
196: #endif length
197: newstuff = Calloc(number, size);
198: asm("movc5 $0, (r0), $0, r10, (r11)");
199: return(newstuff);
200: }
201:
202: struct symtab *symalloc()
203: {
204: if (symsleft == 0){
205: newbox = (struct allocbox *)ClearCalloc(1,ALLOCQTY);
206: symsleft = SYMDALLOP;
207: nextsym = &newbox->symslots[0];
208: if (alloctail == 0){
209: allochead = alloctail = newbox;
210: } else {
211: alloctail->nextalloc = newbox;
212: alloctail = newbox;
213: }
214: }
215: --symsleft;
216: ++nsyms;
217: return(nextsym++);
218: }
219:
220: strpoolalloc()
221: {
222: register struct strpool *new;
223:
224: new = (struct strpool *)Calloc(1, sizeof (struct strpool));
225: new->str_nalloc = 0;
226: new->str_next = strplhead;
227: strplhead = new;
228: }
229:
230: symcmp(Pptr, Qptr)
231: struct symtab **Pptr, **Qptr;
232: {
233: register struct symtab *p = *Pptr;
234: register struct symtab *q = *Qptr;
235: if (p->s_index < q->s_index)
236: return(-1);
237: if (p->s_index > q->s_index)
238: return(1);
239: if (p->s_value < q->s_value)
240: return(-1);
241: if (p->s_value > q->s_value)
242: return(1);
243: /*
244: * Force jxxx entries to virtually preceed labels defined
245: * to follow the jxxxx instruction, so that bumping the
246: * jxxx instruction correctly fixes up the following labels
247: */
248: if (p->s_tag >= IGNOREBOUND) /*p points to a jxxx*/
249: return(-1);
250: if (q->s_tag >= IGNOREBOUND)
251: return(1);
252: /*
253: * both are now just plain labels; the relative order doesn't
254: * matter. Both can't be jxxxes, as they would have different
255: * values.
256: */
257: return(0);
258: } /*end of symcmp*/
259:
260: /*
261: * We construct the auxiliary table of pointers, symptrs and
262: * symdelim
263: * We also assign preliminary values to stab entries that did not yet
264: * have an absolute value (because they initially referred to
265: * forward references). We don't worry about .stabds, as they
266: * already have an estimated final value
267: */
268:
269: sortsymtab()
270: {
271: register struct symtab *sp;
272: register struct symtab **cowalk;
273: register struct allocbox *allocwalk;
274: struct symtab *ubsp;
275: int segno;
276: int slotno;
277: int symsin; /*number put into symptrs*/
278:
279: symptrs = (struct symtab **)Calloc(nsyms + 2, sizeof *symptrs);
280: /*
281: * Allocate one word at the beginning of the symptr array
282: * so that backwards scans through the symptr array will
283: * work correctly while scanning through the zeroth segment
284: */
285: *symptrs++ = 0;
286: cowalk = symptrs;
287: symsin = 0;
288: DECLITERATE(allocwalk, sp, ubsp) {
289: if (sp->s_ptype && (sp->s_type &STABFLAG)){
290: sp->s_value = sp->s_dest->s_value;
291: sp->s_index = sp->s_dest->s_index;
292: }
293: if (symsin >= nsyms)
294: yyerror("INTERNAL ERROR: overfilled symbol table indirection table");
295: *cowalk++ = sp;
296: symsin++;
297: }
298: if (symsin != nsyms)
299: yyerror("INTERNAL ERROR: installed %d syms, should have installed %d",
300: symsin, nsyms);
301: symptrub = &symptrs[nsyms ];
302: qsort(symptrs, nsyms, sizeof *symptrs, symcmp);
303: symdelim[0] = symptrs;
304: for (cowalk = symptrs, sp = *cowalk, segno = 0, slotno = 1;
305: segno < NLOC + NLOC;
306: segno++, slotno++){
307: for (; sp && sp->s_index == segno; sp = *++cowalk);
308: symdelim[slotno] = cowalk; /*forms the ub delimeter*/
309: }
310: } /*end of sortsymtab*/
311:
312: #ifdef DEBUG
313: dumpsymtab()
314: {
315: register int segno;
316: register struct symtab *sp, **cosp, *ub;
317: char *tagstring();
318:
319: printf("Symbol Table dump:\n");
320: for (segno = 0; segno < NLOC + NLOC; segno++){
321: printf("Segment number: %d\n", segno);
322: SEGITERATE(segno, 0, 0, cosp, sp, ub, ++){
323: printf("\tSeg: %d \"%s\" value: %d index: %d tag %s\n",
324: segno, FETCHNAME(sp),
325: sp->s_value, sp->s_index,
326: tagstring(sp->s_tag));
327: printf("\t\ttype: %d jxbump %d jxfear: %d\n",
328: sp->s_type, sp->s_jxbump, sp->s_jxfear);
329: }
330: printf("\n\n");
331: }
332: }
333:
334: static char tagbuff[4];
335:
336: char *tagstring(tag)
337: unsigned char tag;
338: {
339: switch(tag){
340: case JXACTIVE: return("active");
341: case JXNOTYET: return("notyet");
342: case JXALIGN: return("align");
343: case JXQUESTIONABLE: return("jxquestionable");
344: case JXINACTIVE: return("inactive");
345: case JXTUNNEL: return("tunnel");
346: case OBSOLETE: return("obsolete");
347: case IGNOREBOUND: return("ignorebound");
348: case STABFLOATING: return("stabfloating");
349: case STABFIXED: return("stabfixed");
350: case LABELID: return("labelid");
351: case OKTOBUMP: return("oktobump");
352: case ISET: return("iset");
353: case ILSYM: return("ilsym");
354: default: sprintf(tagbuff,"%d", tag);
355: return(tagbuff);
356: }
357: }
358: #endif DEBUG
359:
360: htaballoc()
361: {
362: register struct hashdallop *new;
363: new = (struct hashdallop *)ClearCalloc(1, sizeof (struct hashdallop));
364: if (htab == 0)
365: htab = new;
366: else { /* add AFTER the 1st slot */
367: new->h_next = htab->h_next;
368: htab->h_next = new;
369: }
370: }
371:
372: #define HASHCLOGGED (NHASH / 2)
373:
374: /*
375: * Lookup a symbol stored in extern yytext.
376: * All strings passed in via extern yytext had better have
377: * a trailing null. Strings are placed in yytext for hashing by
378: * syminstall() and by yylex();
379: *
380: * We take pains to avoid function calls; this functdion
381: * is called quite frequently, and the calls overhead
382: * in the vax contributes significantly to the overall
383: * execution speed of as.
384: */
385: struct symtab **lookup(instflg)
386: int instflg; /* 0: don't install */
387: {
388: static int initialprobe;
389: register struct symtab **hp;
390: register char *from;
391: register char *to;
392: register int len;
393: register int nprobes;
394: static struct hashdallop *hdallop;
395: static struct symtab **emptyslot;
396: static struct hashdallop *emptyhd;
397: static struct symtab **hp_ub;
398:
399: emptyslot = 0;
400: for (nprobes = 0, from = yytext;
401: *from;
402: nprobes <<= 2, nprobes += *from++)
403: continue;
404: nprobes += from[-1] << 5;
405: nprobes %= NHASH;
406: if (nprobes < 0)
407: nprobes += NHASH;
408:
409: initialprobe = nprobes;
410: for (hdallop = htab; hdallop != 0; hdallop = hdallop->h_next){
411: for (hp = &(hdallop->h_htab[initialprobe]),
412: nprobes = 1,
413: hp_ub = &(hdallop->h_htab[NHASH]);
414: (*hp) && (nprobes < NHASH);
415: hp += nprobes,
416: hp -= (hp >= hp_ub) ? NHASH:0,
417: nprobes += 2)
418: {
419: from = yytext;
420: to = FETCHNAME(*hp);
421: while (*from && *to)
422: if (*from++ != *to++)
423: goto nextprobe;
424: if (*to == *from) /*assert both are == 0*/
425: return(hp);
426: nextprobe: ;
427: }
428: if (*hp == 0 && emptyslot == 0 &&
429: hdallop->h_nused < HASHCLOGGED) {
430: emptyslot = hp;
431: emptyhd = hdallop;
432: }
433: }
434: if (emptyslot == 0) {
435: htaballoc();
436: hdallop = htab->h_next; /* aren't we smart! */
437: hp = &hdallop->h_htab[initialprobe];
438: } else {
439: hdallop = emptyhd;
440: hp = emptyslot;
441: }
442: if (instflg) {
443: *hp = symalloc();
444: hdallop->h_nused++;
445: for (from = yytext, len = 0; *from++; len++)
446: continue;
447: (*hp)->s_name = (char *)savestr(yytext, len + 1, STR_BOTH);
448: }
449: return(hp);
450: } /*end of lookup*/
451: /*
452: * save a string str with len in the places indicated by place
453: */
454: struct strdesc *savestr(str, len, place)
455: char *str;
456: int len;
457: int place;
458: {
459: reg struct strdesc *res;
460: int tlen;
461: /*
462: * Compute the total length of the record to live in core
463: */
464: tlen = sizeof(struct strdesc) - sizeof(res->sd_string);
465: if (place & STR_CORE)
466: tlen += len;
467: /*
468: * See if there is enough space for the record,
469: * and allocate the record.
470: */
471: if (tlen >= (STRPOOLDALLOP - strplhead->str_nalloc))
472: strpoolalloc();
473: res = (struct strdesc *)(strplhead->str_names + strplhead->str_nalloc);
474: /*
475: * Save the string information that is always present
476: */
477: res->sd_stroff = strfilepos;
478: res->sd_strlen = len;
479: res->sd_place = place;
480: /*
481: * Now, save the string itself. If str is null, then
482: * the characters have already been dumped to the file
483: */
484: if ((place & STR_CORE) && str)
485: movestr(res[0].sd_string, str, len);
486: if (place & STR_FILE){
487: if (str){
488: fwrite(str, 1, len, strfile);
489: }
490: strfilepos += len;
491: }
492: /*
493: * Adjust the in core string pool size
494: */
495: strplhead->str_nalloc += tlen;
496: return(res);
497: }
498: /*
499: * The relocation information is saved internally in an array of
500: * lists of relocation buffers. The relocation buffers are
501: * exactly the same size as a token buffer; if we use VM for the
502: * temporary file we reclaim this storage, otherwise we create
503: * them by mallocing.
504: */
505: #define RELBUFLG TOKBUFLG
506: #define NRELOC ((TOKBUFLG - \
507: (sizeof (int) + sizeof (struct relbufdesc *)) \
508: ) / (sizeof (struct relocation_info)))
509:
510: struct relbufdesc{
511: int rel_count;
512: struct relbufdesc *rel_next;
513: struct relocation_info rel_reloc[NRELOC];
514: };
515: extern struct relbufdesc *tok_free;
516: #define rel_free tok_free
517: static struct relbufdesc *rel_temp;
518: struct relocation_info r_can_1PC;
519: struct relocation_info r_can_0PC;
520:
521: initoutrel()
522: {
523: r_can_0PC.r_address = 0;
524: r_can_0PC.r_symbolnum = 0;
525: r_can_0PC.r_pcrel = 0;
526: r_can_0PC.r_length = 0;
527: r_can_0PC.r_extern = 0;
528:
529: r_can_1PC = r_can_0PC;
530: r_can_1PC.r_pcrel = 1;
531: }
532:
533: outrel(xp, reloc_how)
534: register struct exp *xp;
535: int reloc_how; /* TYPB..TYPH + (possibly)RELOC_PCREL */
536: {
537: struct relocation_info reloc;
538: register int x_type_mask;
539: int pcrel;
540:
541: x_type_mask = xp->e_xtype & ~XFORW;
542: pcrel = reloc_how & RELOC_PCREL;
543: reloc_how &= ~RELOC_PCREL;
544:
545: if (bitoff&07)
546: yyerror("Padding error");
547: if (x_type_mask == XUNDEF)
548: yyerror("Undefined reference");
549:
550: if ( (x_type_mask != XABS) || pcrel ) {
551: if (ty_NORELOC[reloc_how])
552: yyerror("Illegal Relocation of floating or large int number.");
553: reloc = pcrel ? r_can_1PC : r_can_0PC;
554: reloc.r_address = dotp->e_xvalue -
555: ( (dotp < &usedot[NLOC] || readonlydata) ? 0 : datbase );
556: reloc.r_length = ty_nlg[reloc_how];
557: switch(x_type_mask){
558: case XXTRN | XUNDEF:
559: reloc.r_symbolnum = xp->e_xname->s_index;
560: reloc.r_extern = 1;
561: break;
562: default:
563: if (readonlydata && (x_type_mask&~XXTRN) == XDATA)
564: x_type_mask = XTEXT | (x_type_mask&XXTRN);
565: reloc.r_symbolnum = x_type_mask;
566: break;
567: }
568: if ( (relfil == 0) || (relfil->rel_count >= NRELOC) ){
569: if (rel_free){
570: rel_temp = rel_free;
571: rel_free = rel_temp->rel_next;
572: } else {
573: rel_temp = (struct relbufdesc *)
574: Calloc(1,sizeof (struct relbufdesc));
575: }
576: rel_temp->rel_count = 0;
577: rel_temp->rel_next = relfil;
578: relfil = rusefile[dotp - &usedot[0]] = rel_temp;
579: }
580: relfil->rel_reloc[relfil->rel_count++] = reloc;
581: }
582: /*
583: * write the unrelocated value to the text file
584: */
585: dotp->e_xvalue += ty_nbyte[reloc_how];
586: if (pcrel)
587: xp->e_xvalue -= dotp->e_xvalue;
588: switch(reloc_how){
589: case TYPO:
590: case TYPQ:
591:
592: case TYPF:
593: case TYPD:
594: case TYPG:
595: case TYPH:
596: bignumwrite(xp->e_number, reloc_how);
597: break;
598:
599: default:
600: bwrite((char *)&(xp->e_xvalue), ty_nbyte[reloc_how], txtfil);
601: break;
602: }
603: }
604: /*
605: * Flush out all of the relocation information.
606: * Note that the individual lists of buffers are in
607: * reverse order, so we must reverse them
608: */
609: off_t closeoutrel(relocfile)
610: BFILE *relocfile;
611: {
612: int locindex;
613: u_long Closeoutrel();
614:
615: trsize = 0;
616: for (locindex = 0; locindex < NLOC; locindex++){
617: trsize += Closeoutrel(rusefile[locindex], relocfile);
618: }
619: drsize = 0;
620: for (locindex = 0; locindex < NLOC; locindex++){
621: drsize += Closeoutrel(rusefile[NLOC + locindex], relocfile);
622: }
623: return(trsize + drsize);
624: }
625:
626: u_long Closeoutrel(relfil, relocfile)
627: struct relbufdesc *relfil;
628: BFILE *relocfile;
629: {
630: u_long tail;
631: if (relfil == 0)
632: return(0L);
633: tail = Closeoutrel(relfil->rel_next, relocfile);
634: bwrite((char *)&relfil->rel_reloc[0],
635: relfil->rel_count * sizeof (struct relocation_info),
636: relocfile);
637: return(tail + relfil->rel_count * sizeof (struct relocation_info));
638: }
639:
640: #define NOUTSYMS (nsyms - njxxx - nforgotten - (savelabels ? 0 : nlabels))
641: int sizesymtab()
642: {
643: return (sizeof (struct nlist) * NOUTSYMS);
644: }
645: /*
646: * Write out n symbols to file f, beginning at p
647: * ignoring symbols that are obsolete, jxxx instructions, and
648: * possibly, labels
649: */
650: int symwrite(symfile)
651: BFILE *symfile;
652: {
653: int symsout; /*those actually written*/
654: int symsdesired = NOUTSYMS;
655: reg struct symtab *sp, *ub;
656: char *name; /* temp to save the name */
657: int totalstr;
658: /*
659: * We use sp->s_index to hold the length of the
660: * name; it isn't used for anything else
661: */
662: register struct allocbox *allocwalk;
663:
664: symsout = 0;
665: totalstr = sizeof(totalstr);
666: DECLITERATE(allocwalk, sp, ub) {
667: if (sp->s_tag >= IGNOREBOUND)
668: continue;
669: if (ISLABEL(sp))
670: continue;
671: symsout++;
672: name = sp->s_name; /* save pointer */
673: /*
674: * the length of the symbol table string
675: * always includes the trailing null;
676: * blast the pointer to its a.out value.
677: */
678: if (sp->s_name && (sp->s_index = STRLEN(sp))){
679: sp->s_nmx = totalstr;
680: totalstr += sp->s_index;
681: } else {
682: sp->s_nmx = 0;
683: }
684: if (sp->s_ptype != 0)
685: sp->s_type = sp->s_ptype;
686: else
687: sp->s_type = (sp->s_type & (~XFORW));
688: if (readonlydata && (sp->s_type&~N_EXT) == N_DATA)
689: sp->s_type = N_TEXT | (sp->s_type & N_EXT);
690: bwrite((char *)&sp->s_nm, sizeof (struct nlist), symfile);
691: sp->s_name = name; /* restore pointer */
692: }
693: if (symsout != symsdesired)
694: yyerror("INTERNAL ERROR: Wrote %d symbols, wanted to write %d symbols\n",
695: symsout, symsdesired);
696: /*
697: * Construct the string pool from the symbols that were written,
698: * possibly fetching from the string file if the string
699: * is not core resident.
700: */
701: bwrite(&totalstr, sizeof(totalstr), symfile);
702: symsout = 0;
703: DECLITERATE(allocwalk, sp, ub) {
704: if (sp->s_tag >= IGNOREBOUND)
705: continue;
706: if (ISLABEL(sp))
707: continue;
708: symsout++;
709: if (STRLEN(sp) > 0){
710: if (STRPLACE(sp) & STR_CORE){
711: bwrite(FETCHNAME(sp), STRLEN(sp), symfile);
712: } else if (STRPLACE(sp) & STR_FILE){
713: char rbuf[2048];
714: int left, nread;
715: fseek(strfile, STROFF(sp), 0);
716: for (left = STRLEN(sp); left > 0; left -= nread){
717: nread = fread(rbuf, sizeof(char),
718: min(sizeof(rbuf), left), strfile);
719: if (nread == 0)
720: break;
721: bwrite(rbuf, nread, symfile);
722: }
723: }
724: }
725: }
726: if (symsout != symsdesired)
727: yyerror("INTERNAL ERROR: Wrote %d strings, wanted %d\n",
728: symsout, symsdesired);
729: }